Lol
This commit is contained in:
149
app/Main.hs
149
app/Main.hs
@@ -1,8 +1,151 @@
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Main where
|
||||
|
||||
import qualified MyLib (someFunc)
|
||||
import Control.Monad.Logger
|
||||
import Control.Monad.Reader
|
||||
import Control.Monad.IO.Class
|
||||
import Data.Bifunctor
|
||||
import Data.ByteString ( ByteString )
|
||||
import Data.Functor ( (<&>) )
|
||||
import Data.Maybe
|
||||
import Data.Semigroup ( (<>) )
|
||||
import Data.Text ( Text )
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.Encoding as E
|
||||
import Data.Traversable
|
||||
import Data.Versions
|
||||
import GHCup
|
||||
import GHCup.File
|
||||
import GHCup.Prelude
|
||||
import GHCup.Types
|
||||
import Haskus.Utils.Variant.Excepts
|
||||
import HPath
|
||||
import Options.Applicative
|
||||
import System.Console.Pretty
|
||||
import System.Exit
|
||||
|
||||
|
||||
|
||||
data Options = Options
|
||||
{ optVerbose :: Bool
|
||||
, optCache :: Bool
|
||||
, optCommand :: Command
|
||||
}
|
||||
|
||||
data Command
|
||||
= InstallGHC InstallGHCOptions
|
||||
| InstallCabal InstallCabalOptions
|
||||
|
||||
data InstallGHCOptions = InstallGHCOptions
|
||||
{
|
||||
ghcVer :: Maybe Version
|
||||
}
|
||||
|
||||
data InstallCabalOptions = InstallCabalOptions
|
||||
{
|
||||
cabalVer :: Maybe Version
|
||||
}
|
||||
|
||||
|
||||
opts :: Parser Options
|
||||
opts =
|
||||
Options
|
||||
<$> switch
|
||||
(short 'v' <> long "verbose" <> help "Whether to enable verbosity")
|
||||
<*> switch (short 'c' <> long "cache" <> help "Whether to cache downloads")
|
||||
<*> com
|
||||
|
||||
|
||||
com :: Parser Command
|
||||
com = subparser
|
||||
( command
|
||||
"install-ghc"
|
||||
( InstallGHC
|
||||
<$> (info (installGHCOpts <**> helper)
|
||||
(progDesc "Install a GHC version")
|
||||
)
|
||||
)
|
||||
<> command
|
||||
"install-cabal"
|
||||
( InstallCabal
|
||||
<$> (info (installCabalOpts <**> helper)
|
||||
(progDesc "Install a cabal-install version")
|
||||
)
|
||||
)
|
||||
)
|
||||
|
||||
installGHCOpts :: Parser InstallGHCOptions
|
||||
installGHCOpts = InstallGHCOptions <$> optional
|
||||
(option
|
||||
(eitherReader
|
||||
(\s -> bimap (const "Not a valid version") id . version . T.pack $ s)
|
||||
)
|
||||
(short 'v' <> long "version" <> metavar "VERSION" <> help
|
||||
"The GHC version to install"
|
||||
)
|
||||
)
|
||||
|
||||
|
||||
installCabalOpts :: Parser InstallCabalOptions
|
||||
installCabalOpts = InstallCabalOptions <$> optional
|
||||
(option
|
||||
(eitherReader
|
||||
(\s -> bimap (const "Not a valid version") id . version . T.pack $ s)
|
||||
)
|
||||
(short 'v' <> long "version" <> metavar "VERSION" <> help
|
||||
"The Cabal version to install"
|
||||
)
|
||||
)
|
||||
|
||||
|
||||
toSettings :: Options -> Settings
|
||||
toSettings Options{..} =
|
||||
let cache = optCache
|
||||
in Settings{..}
|
||||
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
putStrLn "Hello, Haskell!"
|
||||
MyLib.someFunc
|
||||
e <-
|
||||
customExecParser (prefs showHelpOnError) (info (opts <**> helper) idm)
|
||||
>>= \opt@Options {..} -> do
|
||||
let settings = toSettings opt
|
||||
-- wrapper to run effects with settings
|
||||
let run = flip runReaderT settings . runStderrLoggingT . runE
|
||||
@'[ FileError
|
||||
, ArchiveError
|
||||
, ProcessError
|
||||
, URLException
|
||||
, PlatformResultError
|
||||
, NoDownload
|
||||
, NoCompatibleArch
|
||||
, DistroNotFound
|
||||
, TagNotFound
|
||||
]
|
||||
|
||||
case optCommand of
|
||||
InstallGHC (InstallGHCOptions {..}) ->
|
||||
run
|
||||
$ do
|
||||
d <- liftIO $ ghcupBaseDir
|
||||
case ghcVer of
|
||||
Just ver -> liftE $ installTool (ToolRequest GHC ver)
|
||||
Nothing
|
||||
(OwnSpec availableDownloads)
|
||||
Nothing -> do
|
||||
ver <-
|
||||
getRecommended availableDownloads GHC
|
||||
?? TagNotFound Recommended GHC
|
||||
liftE $ installTool (ToolRequest GHC ver) Nothing (OwnSpec availableDownloads)
|
||||
InstallCabal (InstallCabalOptions {..}) -> undefined
|
||||
|
||||
pure ()
|
||||
|
||||
|
||||
-- print error, if any
|
||||
-- case e of
|
||||
-- Right () -> pure ()
|
||||
-- Left t -> die (color Red $ t)
|
||||
|
||||
Reference in New Issue
Block a user