ghcup-hs/app/Main.hs

178 lines
5.4 KiB
Haskell
Raw Normal View History

2020-02-22 18:21:10 +00:00
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE OverloadedStrings #-}
2020-02-24 13:56:13 +00:00
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
2020-02-22 18:21:10 +00:00
2020-01-11 20:15:05 +00:00
module Main where
2020-02-22 18:21:10 +00:00
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 ( (<>) )
2020-02-24 13:56:13 +00:00
import Data.String.QQ
2020-02-22 18:21:10 +00:00
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
2020-02-24 13:56:13 +00:00
2020-02-22 18:21:10 +00:00
data Options = Options
{ optVerbose :: Bool
2020-02-24 14:09:38 +00:00
, optCache :: Bool
2020-02-22 18:21:10 +00:00
, optCommand :: Command
}
data Command
= InstallGHC InstallGHCOptions
| InstallCabal InstallCabalOptions
data InstallGHCOptions = InstallGHCOptions
2020-02-24 14:09:38 +00:00
{ ghcVer :: Maybe Version
2020-02-22 18:21:10 +00:00
}
data InstallCabalOptions = InstallCabalOptions
2020-02-24 14:09:38 +00:00
{ cabalVer :: Maybe Version
2020-02-22 18:21:10 +00:00
}
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
2020-02-24 13:56:13 +00:00
toSettings Options {..} = let cache = optCache in Settings { .. }
2020-02-22 18:21:10 +00:00
2020-02-24 13:56:13 +00:00
-- TODO: something better than Show instance for errors
2020-01-11 20:15:05 +00:00
main :: IO ()
main = do
2020-02-24 13:56:13 +00:00
-- logger interpreter
let runLogger = runStderrLoggingT
customExecParser (prefs showHelpOnError) (info (opts <**> helper) idm)
>>= \opt@Options {..} -> do
let settings = toSettings opt
-- wrapper to run effects with settings
2020-02-24 14:09:38 +00:00
let runInstTool =
runLogger
. flip runReaderT settings
. runE
@'[ FileError
, ArchiveError
, ProcessError
, URLException
, PlatformResultError
, NoDownload
, NoCompatibleArch
, DistroNotFound
, TagNotFound
, AlreadyInstalled
, NotInstalled
]
2020-02-24 13:56:13 +00:00
case optCommand of
2020-02-22 18:21:10 +00:00
InstallGHC (InstallGHCOptions {..}) ->
2020-02-24 13:56:13 +00:00
void
2020-02-24 14:09:38 +00:00
$ (runInstTool $ do
2020-02-24 13:56:13 +00:00
v <- maybe
( getRecommended availableDownloads GHC
?? TagNotFound Recommended GHC
)
pure
ghcVer
liftE $ installTool (ToolRequest GHC v)
Nothing
(OwnSpec availableDownloads)
)
>>= \case
2020-02-24 14:09:38 +00:00
VRight _ -> runLogger $ $(logInfo) ([s|GHC installation successful|])
2020-02-24 13:56:13 +00:00
VLeft (V (AlreadyInstalled treq)) ->
runLogger $ $(logWarn)
(T.pack (show treq) <> [s| already installed|])
VLeft e -> die (color Red $ show e)
InstallCabal (InstallCabalOptions {..}) ->
void
$ (runInstTool $ do
v <- maybe
( getRecommended availableDownloads Cabal
?? TagNotFound Recommended Cabal
)
pure
cabalVer
liftE $ installTool (ToolRequest Cabal v)
Nothing
(OwnSpec availableDownloads)
)
>>= \case
2020-02-24 14:09:38 +00:00
VRight _ -> runLogger $ $(logInfo) ([s|Cabal installation successful|])
2020-02-24 13:56:13 +00:00
VLeft (V (AlreadyInstalled treq)) ->
runLogger $ $(logWarn)
(T.pack (show treq) <> [s| already installed|])
VLeft e -> die (color Red $ show e)
2020-02-22 18:21:10 +00:00
pure ()