{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RankNTypes #-}
{-# OPTIONS_GHC -Wno-unused-record-wildcards #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module GHCup.Brick.Actions where
import GHCup
import GHCup.CabalConfig
import GHCup.Download
import GHCup.Errors
import GHCup.Types.Optics ( getDirs, getPlatformReq, HasLog )
import GHCup.Types hiding ( LeanAppState(..) )
import GHCup.Utils
import GHCup.Prelude ( decUTF8Safe, runBothE' )
import GHCup.Prelude.Logger
import GHCup.Prelude.Process
import GHCup.Prompts
import GHCup.Brick.Common (BrickData(..), BrickSettings(..), Name(..), Mode(..))
import qualified GHCup.Brick.Common as Common
import GHCup.Brick.BrickState
import GHCup.Brick.Widgets.SectionList
import qualified GHCup.Brick.Widgets.Menus.Context as ContextMenu
import GHCup.Brick.Widgets.Navigation (BrickInternalState)
import qualified GHCup.Brick.Widgets.Menus.AdvanceInstall as AdvanceInstall
import qualified GHCup.Brick.Widgets.Menus.CompileGHC as CompileGHC
import GHCup.Brick.Widgets.Menu (MenuKeyBindings(..))
import qualified Brick
import qualified Brick.Widgets.List as L
import qualified Brick.Focus as F
import Control.Applicative
import Control.Exception.Safe
import Control.Monad (when, forM, forM_)
#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail ( MonadFail )
#endif
import Control.Monad.Reader
import Control.Monad.Trans.Except
import Control.Monad.Trans.Resource
import Data.Bool
import Data.Functor
import Data.Function ( (&), on)
import Data.List
import Data.Maybe
import Data.IORef (IORef, readIORef, newIORef, modifyIORef)
import Data.Versions hiding (Lens')
import Data.Variant.Excepts
import Prelude hiding ( appendFile )
import System.Exit
import System.IO.Unsafe
import System.Process ( system )
import Text.PrettyPrint.HughesPJClass ( prettyShow )
import URI.ByteString
import qualified Data.Text as T
import qualified Data.Text.Lazy.Builder as B
import qualified Data.Text.Lazy as L
import qualified Graphics.Vty as Vty
import qualified Data.Vector as V
import System.Environment (getExecutablePath)
#if !IS_WINDOWS
import GHCup.Prelude.File
import qualified System.Posix.Process as SPP
#endif
import System.FilePath
import Optics.State (use)
import Optics.State.Operators ( (.=))
import Optics.Operators ((.~),(%~))
import Optics.Getter (view)
import Optics.Optic ((%))
import Optics ((^.), to)
import qualified GHCup.Brick.Widgets.Menus.CompileHLS as CompileHLS
import Control.Concurrent (threadDelay)
import qualified GHCup.GHC as GHC
import qualified GHCup.Utils.Parsers as Utils
import qualified GHCup.HLS as HLS
updateList :: BrickData -> BrickState -> BrickState
updateList :: BrickData -> BrickState -> BrickState
updateList BrickData
appD BrickState
bst =
let newInternalState :: GenericSectionList Name Vector ListResult
newInternalState = BrickData
-> BrickSettings
-> Maybe (GenericSectionList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
constructList BrickData
appD (BrickState
bst BrickState
-> Optic' A_Lens '[] BrickState BrickSettings -> BrickSettings
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] BrickState BrickSettings
appSettings) (GenericSectionList Name Vector ListResult
-> Maybe (GenericSectionList Name Vector ListResult)
forall a. a -> Maybe a
Just (BrickState
bst BrickState
-> Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
appState))
in BrickState
bst
BrickState -> (BrickState -> BrickState) -> BrickState
forall a b. a -> (a -> b) -> b
& Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
appState Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
-> BrickState
-> BrickState
forall k (is :: [*]) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ GenericSectionList Name Vector ListResult
newInternalState
BrickState -> (BrickState -> BrickState) -> BrickState
forall a b. a -> (a -> b) -> b
& Lens' BrickState BrickData
appData Lens' BrickState BrickData -> BrickData -> BrickState -> BrickState
forall k (is :: [*]) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ BrickData
appD
BrickState -> (BrickState -> BrickState) -> BrickState
forall a b. a -> (a -> b) -> b
& Lens' BrickState Mode
mode Lens' BrickState Mode -> Mode -> BrickState -> BrickState
forall k (is :: [*]) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Mode
Navigation
constructList :: BrickData
-> BrickSettings
-> Maybe BrickInternalState
-> BrickInternalState
constructList :: BrickData
-> BrickSettings
-> Maybe (GenericSectionList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
constructList BrickData
appD BrickSettings
settings =
(ListResult -> Bool)
-> [ListResult]
-> Maybe (GenericSectionList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
replaceLR (Bool -> ListResult -> Bool
filterVisible (BrickSettings -> Bool
_showAllVersions BrickSettings
settings))
(BrickData -> [ListResult]
_lr BrickData
appD)
selectBy :: Tool -> (ListResult -> Bool) -> BrickInternalState -> BrickInternalState
selectBy :: Tool
-> (ListResult -> Bool)
-> GenericSectionList Name Vector ListResult
-> GenericSectionList Name Vector ListResult
selectBy Tool
tool ListResult -> Bool
predicate GenericSectionList Name Vector ListResult
internal_state =
let new_focus :: FocusRing Name
new_focus = Name -> FocusRing Name -> FocusRing Name
forall n. Eq n => n -> FocusRing n -> FocusRing n
F.focusSetCurrent (Tool -> Name
Singular Tool
tool) (Optic'
A_Lens
'[]
(GenericSectionList Name Vector ListResult)
(FocusRing Name)
-> GenericSectionList Name Vector ListResult -> FocusRing Name
forall k (is :: [*]) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic'
A_Lens
'[]
(GenericSectionList Name Vector ListResult)
(FocusRing Name)
forall n (t :: * -> *) e.
Lens' (GenericSectionList n t e) (FocusRing n)
sectionListFocusRingL GenericSectionList Name Vector ListResult
internal_state)
tool_lens :: Lens' (GenericSectionList Name t e) (GenericList Name t e)
tool_lens = Name -> Lens' (GenericSectionList Name t e) (GenericList Name t e)
forall n (t :: * -> *) e.
Eq n =>
n -> Lens' (GenericSectionList n t e) (GenericList n t e)
sectionL (Tool -> Name
Singular Tool
tool)
in GenericSectionList Name Vector ListResult
internal_state
GenericSectionList Name Vector ListResult
-> (GenericSectionList Name Vector ListResult
-> GenericSectionList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
forall a b. a -> (a -> b) -> b
& Optic'
A_Lens
'[]
(GenericSectionList Name Vector ListResult)
(FocusRing Name)
forall n (t :: * -> *) e.
Lens' (GenericSectionList n t e) (FocusRing n)
sectionListFocusRingL Optic'
A_Lens
'[]
(GenericSectionList Name Vector ListResult)
(FocusRing Name)
-> FocusRing Name
-> GenericSectionList Name Vector ListResult
-> GenericSectionList Name Vector ListResult
forall k (is :: [*]) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ FocusRing Name
new_focus
GenericSectionList Name Vector ListResult
-> (GenericSectionList Name Vector ListResult
-> GenericSectionList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
forall a b. a -> (a -> b) -> b
& Lens'
(GenericSectionList Name Vector ListResult)
(GenericList Name Vector ListResult)
forall {t :: * -> *} {e}.
Lens' (GenericSectionList Name t e) (GenericList Name t e)
tool_lens Lens'
(GenericSectionList Name Vector ListResult)
(GenericList Name Vector ListResult)
-> (GenericList Name Vector ListResult
-> GenericList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
-> GenericSectionList Name Vector ListResult
forall k (is :: [*]) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
%~ Int
-> GenericList Name Vector ListResult
-> GenericList Name Vector ListResult
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
Int -> GenericList n t e -> GenericList n t e
L.listMoveTo Int
0
GenericSectionList Name Vector ListResult
-> (GenericSectionList Name Vector ListResult
-> GenericSectionList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
forall a b. a -> (a -> b) -> b
& Lens'
(GenericSectionList Name Vector ListResult)
(GenericList Name Vector ListResult)
forall {t :: * -> *} {e}.
Lens' (GenericSectionList Name t e) (GenericList Name t e)
tool_lens Lens'
(GenericSectionList Name Vector ListResult)
(GenericList Name Vector ListResult)
-> (GenericList Name Vector ListResult
-> GenericList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
-> GenericSectionList Name Vector ListResult
forall k (is :: [*]) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
%~ (ListResult -> Bool)
-> GenericList Name Vector ListResult
-> GenericList Name Vector ListResult
forall (t :: * -> *) e n.
(Foldable t, Splittable t) =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
L.listFindBy ListResult -> Bool
predicate
selectLatest :: BrickInternalState -> BrickInternalState
selectLatest :: GenericSectionList Name Vector ListResult
-> GenericSectionList Name Vector ListResult
selectLatest = Tool
-> (ListResult -> Bool)
-> GenericSectionList Name Vector ListResult
-> GenericSectionList Name Vector ListResult
selectBy Tool
GHC (Tag -> [Tag] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Tag
Latest ([Tag] -> Bool) -> (ListResult -> [Tag]) -> ListResult -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListResult -> [Tag]
lTag)
replaceLR :: (ListResult -> Bool)
-> [ListResult]
-> Maybe BrickInternalState
-> BrickInternalState
replaceLR :: (ListResult -> Bool)
-> [ListResult]
-> Maybe (GenericSectionList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
replaceLR ListResult -> Bool
filterF [ListResult]
list_result Maybe (GenericSectionList Name Vector ListResult)
s =
let oldElem :: Maybe (Int, ListResult)
oldElem = Maybe (GenericSectionList Name Vector ListResult)
s Maybe (GenericSectionList Name Vector ListResult)
-> (GenericSectionList Name Vector ListResult
-> Maybe (Int, ListResult))
-> Maybe (Int, ListResult)
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= GenericSectionList Name Vector ListResult
-> Maybe (Int, ListResult)
forall n (t :: * -> *) e.
(Eq n, Splittable t, Traversable t, Semigroup (t e)) =>
GenericSectionList n t e -> Maybe (Int, e)
sectionListSelectedElement
newVec :: [(Name, Vector ListResult)]
newVec = [(Tool -> Name
Singular (Tool -> Name) -> Tool -> Name
forall a b. (a -> b) -> a -> b
$ ListResult -> Tool
lTool ([ListResult] -> ListResult
forall a. HasCallStack => [a] -> a
head [ListResult]
g), [ListResult] -> Vector ListResult
forall a. [a] -> Vector a
V.fromList [ListResult]
g) | [ListResult]
g <- (ListResult -> ListResult -> Bool)
-> [ListResult] -> [[ListResult]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (Tool -> Tool -> Bool
forall a. Eq a => a -> a -> Bool
(==) (Tool -> Tool -> Bool)
-> (ListResult -> Tool) -> ListResult -> ListResult -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` ListResult -> Tool
lTool ) ((ListResult -> Bool) -> [ListResult] -> [ListResult]
forall a. (a -> Bool) -> [a] -> [a]
filter ListResult -> Bool
filterF [ListResult]
list_result)]
newSectionList :: GenericSectionList Name Vector ListResult
newSectionList = Name
-> [(Name, Vector ListResult)]
-> Int
-> GenericSectionList Name Vector ListResult
forall (t :: * -> *) n e.
Foldable t =>
n -> [(n, t e)] -> Int -> GenericSectionList n t e
sectionList Name
AllTools [(Name, Vector ListResult)]
newVec Int
1
in case Maybe (Int, ListResult)
oldElem of
Just (Int
_, ListResult
el) -> Tool
-> (ListResult -> Bool)
-> GenericSectionList Name Vector ListResult
-> GenericSectionList Name Vector ListResult
selectBy (ListResult -> Tool
lTool ListResult
el) (ListResult -> ListResult -> Bool
toolEqual ListResult
el) GenericSectionList Name Vector ListResult
newSectionList
Maybe (Int, ListResult)
Nothing -> GenericSectionList Name Vector ListResult
-> GenericSectionList Name Vector ListResult
selectLatest GenericSectionList Name Vector ListResult
newSectionList
where
toolEqual :: ListResult -> ListResult -> Bool
toolEqual ListResult
e1 ListResult
e2 =
ListResult -> Tool
lTool ListResult
e1 Tool -> Tool -> Bool
forall a. Eq a => a -> a -> Bool
== ListResult -> Tool
lTool ListResult
e2 Bool -> Bool -> Bool
&& ListResult -> Version
lVer ListResult
e1 Version -> Version -> Bool
forall a. Eq a => a -> a -> Bool
== ListResult -> Version
lVer ListResult
e2 Bool -> Bool -> Bool
&& ListResult -> Maybe Text
lCross ListResult
e1 Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== ListResult -> Maybe Text
lCross ListResult
e2
filterVisible :: Bool -> ListResult -> Bool
filterVisible :: Bool -> ListResult -> Bool
filterVisible Bool
v ListResult
e | ListResult -> Bool
lInstalled ListResult
e = Bool
True
| Bool
v
, Tag
Nightly Tag -> [Tag] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` ListResult -> [Tag]
lTag ListResult
e = Bool
True
| Bool -> Bool
not Bool
v
, Tag
Old Tag -> [Tag] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` ListResult -> [Tag]
lTag ListResult
e
, Tag
Nightly Tag -> [Tag] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` ListResult -> [Tag]
lTag ListResult
e = Bool
True
| Bool
otherwise = (Tag
Old Tag -> [Tag] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` ListResult -> [Tag]
lTag ListResult
e) Bool -> Bool -> Bool
&&
(Tag
Nightly Tag -> [Tag] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` ListResult -> [Tag]
lTag ListResult
e)
withIOAction :: (Ord n, Eq n)
=> ( (Int, ListResult) -> ReaderT AppState IO (Either String a))
-> Brick.EventM n BrickState ()
withIOAction :: forall n a.
(Ord n, Eq n) =>
((Int, ListResult) -> ReaderT AppState IO (Either String a))
-> EventM n BrickState ()
withIOAction (Int, ListResult) -> ReaderT AppState IO (Either String a)
action = do
BrickState
as <- EventM n BrickState BrickState
forall s (m :: * -> *). MonadState s m => m s
Brick.get
case GenericSectionList Name Vector ListResult
-> Maybe (Int, ListResult)
forall n (t :: * -> *) e.
(Eq n, Splittable t, Traversable t, Semigroup (t e)) =>
GenericSectionList n t e -> Maybe (Int, e)
sectionListSelectedElement (Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
-> BrickState -> GenericSectionList Name Vector ListResult
forall k (is :: [*]) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
appState BrickState
as) of
Maybe (Int, ListResult)
Nothing -> () -> EventM n BrickState ()
forall a. a -> EventM n BrickState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just (Int
curr_ix, ListResult
e) -> do
IO BrickState -> EventM n BrickState ()
forall n s. Ord n => IO s -> EventM n s ()
Brick.suspendAndResume (IO BrickState -> EventM n BrickState ())
-> IO BrickState -> EventM n BrickState ()
forall a b. (a -> b) -> a -> b
$ do
AppState
settings <- IORef AppState -> IO AppState
forall a. IORef a -> IO a
readIORef IORef AppState
settings'
(ReaderT AppState IO () -> AppState -> IO ())
-> AppState -> ReaderT AppState IO () -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT AppState IO () -> AppState -> IO ()
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT AppState
settings (ReaderT AppState IO () -> IO ())
-> ReaderT AppState IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ (Int, ListResult) -> ReaderT AppState IO (Either String a)
action (Int
curr_ix, ListResult
e) ReaderT AppState IO (Either String a)
-> (Either String a -> ReaderT AppState IO ())
-> ReaderT AppState IO ()
forall a b.
ReaderT AppState IO a
-> (a -> ReaderT AppState IO b) -> ReaderT AppState IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left String
err -> IO () -> ReaderT AppState IO ()
forall a. IO a -> ReaderT AppState IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ReaderT AppState IO ())
-> IO () -> ReaderT AppState IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
putStrLn (String
"Error: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
err)
Right a
_ -> IO () -> ReaderT AppState IO ()
forall a. IO a -> ReaderT AppState IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ReaderT AppState IO ())
-> IO () -> ReaderT AppState IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
putStrLn String
"Success"
Maybe GHCupInfo -> IO (Either String BrickData)
getAppData Maybe GHCupInfo
forall a. Maybe a
Nothing IO (Either String BrickData)
-> (Either String BrickData -> IO BrickState) -> IO BrickState
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Right BrickData
data' -> do
String -> IO ()
putStrLn String
"Press enter to continue"
String
_ <- IO String
getLine
BrickState -> IO BrickState
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BrickData -> BrickState -> BrickState
updateList BrickData
data' BrickState
as)
Left String
err -> IOError -> IO BrickState
forall (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
throwIO (IOError -> IO BrickState) -> IOError -> IO BrickState
forall a b. (a -> b) -> a -> b
$ String -> IOError
userError String
err
installWithOptions :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> AdvanceInstall.InstallOptions
-> (Int, ListResult)
-> m (Either String ())
installWithOptions :: forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m,
MonadMask m, MonadUnliftIO m, Alternative m) =>
InstallOptions -> (Int, ListResult) -> m (Either String ())
installWithOptions InstallOptions
opts (Int
_, ListResult {Bool
[Tag]
Maybe Text
Maybe Day
Version
Tool
lTag :: ListResult -> [Tag]
lTool :: ListResult -> Tool
lVer :: ListResult -> Version
lCross :: ListResult -> Maybe Text
lInstalled :: ListResult -> Bool
lTool :: Tool
lVer :: Version
lCross :: Maybe Text
lTag :: [Tag]
lInstalled :: Bool
lSet :: Bool
lStray :: Bool
lNoBindist :: Bool
hlsPowered :: Bool
lReleaseDay :: Maybe Day
hlsPowered :: ListResult -> Bool
lNoBindist :: ListResult -> Bool
lReleaseDay :: ListResult -> Maybe Day
lSet :: ListResult -> Bool
lStray :: ListResult -> Bool
..}) = do
AppState { ghcupInfo :: AppState -> GHCupInfo
ghcupInfo = GHCupInfo { _ghcupDownloads :: GHCupInfo -> GHCupDownloads
_ghcupDownloads = GHCupDownloads
dls }} <- m AppState
forall r (m :: * -> *). MonadReader r m => m r
ask
let
misolated :: Maybe String
misolated = InstallOptions
opts InstallOptions
-> Optic' A_Lens '[] InstallOptions (Maybe String) -> Maybe String
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] InstallOptions (Maybe String)
AdvanceInstall.isolateDirL
shouldIsolate :: InstallDir
shouldIsolate = InstallDir -> (String -> InstallDir) -> Maybe String -> InstallDir
forall b a. b -> (a -> b) -> Maybe a -> b
maybe InstallDir
GHCupInternal String -> InstallDir
IsolateDir (InstallOptions
opts InstallOptions
-> Optic' A_Lens '[] InstallOptions (Maybe String) -> Maybe String
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] InstallOptions (Maybe String)
AdvanceInstall.isolateDirL)
shouldForce :: Bool
shouldForce = InstallOptions
opts InstallOptions -> Optic' A_Lens '[] InstallOptions Bool -> Bool
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] InstallOptions Bool
AdvanceInstall.forceInstallL
shouldSet :: Bool
shouldSet = InstallOptions
opts InstallOptions -> Optic' A_Lens '[] InstallOptions Bool -> Bool
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] InstallOptions Bool
AdvanceInstall.instSetL
extraArgs :: [Text]
extraArgs = InstallOptions
opts InstallOptions -> Optic' A_Lens '[] InstallOptions [Text] -> [Text]
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] InstallOptions [Text]
AdvanceInstall.addConfArgsL
installTargets :: Text
installTargets = InstallOptions
opts InstallOptions -> Optic' A_Lens '[] InstallOptions Text -> Text
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] InstallOptions Text
AdvanceInstall.installTargetsL
v :: GHCTargetVersion
v = GHCTargetVersion -> Maybe GHCTargetVersion -> GHCTargetVersion
forall a. a -> Maybe a -> a
fromMaybe (Maybe Text -> Version -> GHCTargetVersion
GHCTargetVersion Maybe Text
lCross Version
lVer) (InstallOptions
opts InstallOptions
-> Optic' A_Lens '[] InstallOptions (Maybe GHCTargetVersion)
-> Maybe GHCTargetVersion
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] InstallOptions (Maybe GHCTargetVersion)
AdvanceInstall.instVersionL)
toolV :: Version
toolV = GHCTargetVersion -> Version
_tvVersion GHCTargetVersion
v
let run :: Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
a)
run =
ResourceT
m
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
a)
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
a)
forall (m :: * -> *) a. MonadUnliftIO m => ResourceT m a -> m a
runResourceT
(ResourceT
m
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
a)
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
a))
-> (Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
-> ResourceT
m
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
a))
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (es :: [*]) a (m :: * -> *).
Excepts es m a -> m (VEither es a)
runE
@'[ AlreadyInstalled
, ArchiveResult
, UnknownArchive
, FileDoesNotExistError
, CopyError
, NoDownload
, NotInstalled
, BuildFailed
, TagNotFound
, DigestError
, ContentLengthError
, GPGError
, DownloadFailed
, DirNotEmpty
, NoUpdate
, TarDirDoesNotExist
, FileAlreadyExistsError
, ProcessError
, ToolShadowed
, UninstallFailed
, MergeFileTreeError
, NoCompatiblePlatform
, GHCup.Errors.ParseError
, UnsupportedSetupCombo
, DistroNotFound
, NoCompatibleArch
, InstallSetError
, URIParseError
]
withNoVerify :: (MonadReader AppState m) => m a -> m a
withNoVerify :: forall (m :: * -> *) a. MonadReader AppState m => m a -> m a
withNoVerify = (AppState -> AppState) -> m a -> m a
forall a. (AppState -> AppState) -> m a -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\AppState
s -> AppState
s { settings = (settings s) { noVerify = True}})
Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(Maybe VersionInfo, Dirs, Maybe String))
forall {a}.
Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
a)
run (do
Maybe String
ce <- IO (Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe String)
forall a.
IO a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe String))
-> IO (Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe String)
forall a b. (a -> b) -> a -> b
$ (Either SomeException String -> Maybe String)
-> IO (Either SomeException String) -> IO (Maybe String)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((SomeException -> Maybe String)
-> (String -> Maybe String)
-> Either SomeException String
-> Maybe String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe String -> SomeException -> Maybe String
forall a b. a -> b -> a
const Maybe String
forall a. Maybe a
Nothing) String -> Maybe String
forall a. a -> Maybe a
Just) (IO (Either SomeException String) -> IO (Maybe String))
-> IO (Either SomeException String) -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) e a.
(HasCallStack, MonadCatch m, Exception e) =>
m a -> m (Either e a)
try @_ @SomeException (IO String -> IO (Either SomeException String))
-> IO String -> IO (Either SomeException String)
forall a b. (a -> b) -> a -> b
$ IO String
getExecutablePath IO String -> (String -> IO String) -> IO String
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> IO String
canonicalizePath
Dirs
dirs <- ResourceT m Dirs
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
Dirs
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ResourceT m Dirs
forall env (m :: * -> *).
(MonadReader env m, LabelOptic' "dirs" A_Lens env Dirs) =>
m Dirs
getDirs
case Tool
lTool of
Tool
GHC -> do
let vi :: Maybe VersionInfo
vi = GHCTargetVersion -> Tool -> GHCupDownloads -> Maybe VersionInfo
getVersionInfo GHCTargetVersion
v Tool
GHC GHCupDownloads
dls
Maybe Text
-> (Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPreInstall (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> (Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> do
ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn Text
msg
ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn
Text
"...waiting for 5 seconds, you can still abort..."
IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a.
IO a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
5000000
case InstallOptions
opts InstallOptions
-> Optic' A_Lens '[] InstallOptions (Maybe URI) -> Maybe URI
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] InstallOptions (Maybe URI)
AdvanceInstall.instBindistL of
Maybe URI
Nothing -> do
Excepts
'[InstallSetError, AlreadyInstalled, BuildFailed, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, DirNotEmpty,
ArchiveResult, ProcessError, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[InstallSetError, AlreadyInstalled, BuildFailed, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, DirNotEmpty,
ArchiveResult, ProcessError, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[InstallSetError, AlreadyInstalled, BuildFailed, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, DirNotEmpty,
ArchiveResult, ProcessError, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$
Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, NoCompatiblePlatform,
ParseError, UnsupportedSetupCombo, DistroNotFound,
NoCompatibleArch, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, NoCompatiblePlatform,
ParseError, UnsupportedSetupCombo, DistroNotFound,
NoCompatibleArch, URIParseError]
(ResourceT m)
()
-> Excepts
'[InstallSetError, AlreadyInstalled, BuildFailed, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, DirNotEmpty,
ArchiveResult, ProcessError, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT m)
()
forall (e :: [*]) (m :: * -> *) a b.
(Monad m, Show (V e), Pretty (V e), HFErrorProject (V e),
PopVariant InstallSetError e, LiftVariant' e (InstallSetError : e),
e :<< (InstallSetError : e)) =>
Excepts e m a
-> Excepts e m b -> Excepts (InstallSetError : e) m ()
runBothE'
(GHCTargetVersion
-> InstallDir
-> Bool
-> [Text]
-> Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, NoCompatiblePlatform,
ParseError, UnsupportedSetupCombo, DistroNotFound,
NoCompatibleArch, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) env.
(MonadFail m, MonadMask m, MonadCatch m, MonadReader env m,
HasPlatformReq env, HasGHCupInfo env, HasDirs env, HasSettings env,
HasLog env, MonadResource m, MonadIO m, MonadUnliftIO m,
Alternative m) =>
GHCTargetVersion
-> InstallDir
-> Bool
-> [Text]
-> Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, NoCompatiblePlatform,
ParseError, UnsupportedSetupCombo, DistroNotFound,
NoCompatibleArch, URIParseError]
m
()
installGHCBin GHCTargetVersion
v InstallDir
shouldIsolate Bool
shouldForce [Text]
extraArgs Text
installTargets)
(Bool
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, NoCompatiblePlatform,
ParseError, UnsupportedSetupCombo, DistroNotFound,
NoCompatibleArch, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, NoCompatiblePlatform,
ParseError, UnsupportedSetupCombo, DistroNotFound,
NoCompatibleArch, URIParseError]
(ResourceT m)
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
shouldSet Bool -> Bool -> Bool
&& Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
misolated) (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, NoCompatiblePlatform,
ParseError, UnsupportedSetupCombo, DistroNotFound,
NoCompatibleArch, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, NoCompatiblePlatform,
ParseError, UnsupportedSetupCombo, DistroNotFound,
NoCompatibleArch, URIParseError]
(ResourceT m)
())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, NoCompatiblePlatform,
ParseError, UnsupportedSetupCombo, DistroNotFound,
NoCompatibleArch, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
-> Excepts '[NotInstalled] (ResourceT m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
-> Excepts '[NotInstalled] (ResourceT m) ())
-> Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
-> Excepts '[NotInstalled] (ResourceT m) ()
forall a b. (a -> b) -> a -> b
$ GHCTargetVersion
-> SetGHC
-> Maybe String
-> Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
forall env (m :: * -> *).
(MonadReader env m, HasDirs env, HasLog env, MonadThrow m,
MonadFail m, MonadIO m, MonadCatch m, MonadMask m,
MonadUnliftIO m) =>
GHCTargetVersion
-> SetGHC
-> Maybe String
-> Excepts '[NotInstalled] m GHCTargetVersion
setGHC GHCTargetVersion
v SetGHC
SetGHCOnly Maybe String
forall a. Maybe a
Nothing))
(Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
forall a.
a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe VersionInfo
vi, Dirs
dirs, Maybe String
ce)
Just URI
uri -> do
Excepts
'[InstallSetError, AlreadyInstalled, BuildFailed, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, DirNotEmpty,
ArchiveResult, ProcessError, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[InstallSetError, AlreadyInstalled, BuildFailed, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, DirNotEmpty,
ArchiveResult, ProcessError, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[InstallSetError, AlreadyInstalled, BuildFailed, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, DirNotEmpty,
ArchiveResult, ProcessError, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$
Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[InstallSetError, AlreadyInstalled, BuildFailed, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, DirNotEmpty,
ArchiveResult, ProcessError, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
forall (e :: [*]) (m :: * -> *) a b.
(Monad m, Show (V e), Pretty (V e), HFErrorProject (V e),
PopVariant InstallSetError e, LiftVariant' e (InstallSetError : e),
e :<< (InstallSetError : e)) =>
Excepts e m a
-> Excepts e m b -> Excepts (InstallSetError : e) m ()
runBothE'
(Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a. MonadReader AppState m => m a -> m a
withNoVerify (Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ DownloadInfo
-> GHCTargetVersion
-> InstallDir
-> Bool
-> [Text]
-> Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) env.
(MonadFail m, MonadMask m, MonadCatch m, MonadReader env m,
HasDirs env, HasSettings env, HasPlatformReq env, HasLog env,
MonadResource m, MonadIO m, MonadUnliftIO m) =>
DownloadInfo
-> GHCTargetVersion
-> InstallDir
-> Bool
-> [Text]
-> Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
m
()
installGHCBindist
(Text
-> Maybe TarDir
-> Text
-> Maybe Integer
-> Maybe String
-> Maybe [Tag]
-> DownloadInfo
DownloadInfo ((ByteString -> Text
decUTF8Safe (ByteString -> Text) -> (URI -> ByteString) -> URI -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URI -> ByteString
forall a. URIRef a -> ByteString
serializeURIRef') URI
uri) (TarDir -> Maybe TarDir
forall a. a -> Maybe a
Just (TarDir -> Maybe TarDir) -> TarDir -> Maybe TarDir
forall a b. (a -> b) -> a -> b
$ String -> TarDir
RegexDir String
"ghc-.*") Text
"" Maybe Integer
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing Maybe [Tag]
forall a. Maybe a
Nothing)
GHCTargetVersion
v
InstallDir
shouldIsolate
Bool
shouldForce
[Text]
extraArgs
Text
installTargets
)
(Bool
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
shouldSet Bool -> Bool -> Bool
&& Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
misolated) (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, DirNotEmpty, ArchiveResult, ProcessError,
UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
-> Excepts '[NotInstalled] (ResourceT m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
-> Excepts '[NotInstalled] (ResourceT m) ())
-> Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
-> Excepts '[NotInstalled] (ResourceT m) ()
forall a b. (a -> b) -> a -> b
$ GHCTargetVersion
-> SetGHC
-> Maybe String
-> Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
forall env (m :: * -> *).
(MonadReader env m, HasDirs env, HasLog env, MonadThrow m,
MonadFail m, MonadIO m, MonadCatch m, MonadMask m,
MonadUnliftIO m) =>
GHCTargetVersion
-> SetGHC
-> Maybe String
-> Excepts '[NotInstalled] m GHCTargetVersion
setGHC GHCTargetVersion
v SetGHC
SetGHCOnly Maybe String
forall a. Maybe a
Nothing))
(Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
forall a.
a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe VersionInfo
vi, Dirs
dirs, Maybe String
ce)
Tool
Cabal -> do
let vi :: Maybe VersionInfo
vi = GHCTargetVersion -> Tool -> GHCupDownloads -> Maybe VersionInfo
getVersionInfo GHCTargetVersion
v Tool
Cabal GHCupDownloads
dls
Maybe Text
-> (Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPreInstall (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> (Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> do
ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn Text
msg
ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn
Text
"...waiting for 5 seconds, you can still abort..."
IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a.
IO a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
5000000
case InstallOptions
opts InstallOptions
-> Optic' A_Lens '[] InstallOptions (Maybe URI) -> Maybe URI
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] InstallOptions (Maybe URI)
AdvanceInstall.instBindistL of
Maybe URI
Nothing -> do
Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$
Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
forall (e :: [*]) (m :: * -> *) a b.
(Monad m, Show (V e), Pretty (V e), HFErrorProject (V e),
PopVariant InstallSetError e, LiftVariant' e (InstallSetError : e),
e :<< (InstallSetError : e)) =>
Excepts e m a
-> Excepts e m b -> Excepts (InstallSetError : e) m ()
runBothE'
(Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (m :: * -> *) env.
(MonadMask m, MonadCatch m, MonadReader env m, HasPlatformReq env,
HasGHCupInfo env, HasDirs env, HasSettings env, HasLog env,
MonadResource m, MonadIO m, MonadUnliftIO m, MonadFail m) =>
Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
m
()
installCabalBin Version
toolV InstallDir
shouldIsolate Bool
shouldForce)
(Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
shouldSet Bool -> Bool -> Bool
&& Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
misolated) (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall a b. (a -> b) -> a -> b
$ Version -> Excepts '[NotInstalled] (ResourceT m) ()
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, HasLog env,
MonadFail m, MonadIO m, MonadUnliftIO m) =>
Version -> Excepts '[NotInstalled] m ()
setCabal Version
toolV))
(Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
forall a.
a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe VersionInfo
vi, Dirs
dirs, Maybe String
ce)
Just URI
uri -> do
Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$
Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
forall (e :: [*]) (m :: * -> *) a b.
(Monad m, Show (V e), Pretty (V e), HFErrorProject (V e),
PopVariant InstallSetError e, LiftVariant' e (InstallSetError : e),
e :<< (InstallSetError : e)) =>
Excepts e m a
-> Excepts e m b -> Excepts (InstallSetError : e) m ()
runBothE'
(Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a. MonadReader AppState m => m a -> m a
withNoVerify (Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ DownloadInfo
-> Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (m :: * -> *) env.
(MonadMask m, MonadCatch m, MonadReader env m, HasPlatformReq env,
HasDirs env, HasSettings env, HasLog env, MonadResource m,
MonadIO m, MonadUnliftIO m, MonadFail m) =>
DownloadInfo
-> Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
m
()
installCabalBindist (Text
-> Maybe TarDir
-> Text
-> Maybe Integer
-> Maybe String
-> Maybe [Tag]
-> DownloadInfo
DownloadInfo ((ByteString -> Text
decUTF8Safe (ByteString -> Text) -> (URI -> ByteString) -> URI -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URI -> ByteString
forall a. URIRef a -> ByteString
serializeURIRef') URI
uri) Maybe TarDir
forall a. Maybe a
Nothing Text
"" Maybe Integer
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing Maybe [Tag]
forall a. Maybe a
Nothing) Version
toolV InstallDir
shouldIsolate Bool
shouldForce)
(Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
shouldSet Bool -> Bool -> Bool
&& Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
misolated) (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall a b. (a -> b) -> a -> b
$ Version -> Excepts '[NotInstalled] (ResourceT m) ()
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, HasLog env,
MonadFail m, MonadIO m, MonadUnliftIO m) =>
Version -> Excepts '[NotInstalled] m ()
setCabal Version
toolV))
(Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
forall a.
a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe VersionInfo
vi, Dirs
dirs, Maybe String
ce)
Tool
GHCup -> do
let vi :: Maybe VersionInfo
vi = (GHCTargetVersion, VersionInfo) -> VersionInfo
forall a b. (a, b) -> b
snd ((GHCTargetVersion, VersionInfo) -> VersionInfo)
-> Maybe (GHCTargetVersion, VersionInfo) -> Maybe VersionInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GHCupDownloads -> Tool -> Maybe (GHCTargetVersion, VersionInfo)
getLatest GHCupDownloads
dls Tool
GHCup
Maybe Text
-> (Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPreInstall (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> (Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> do
ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn Text
msg
ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn
Text
"...waiting for 5 seconds, you can still abort..."
IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a.
IO a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
5000000
Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String))
-> Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
forall a b. (a -> b) -> a -> b
$ Maybe String
-> Bool
-> Bool
-> Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
(ResourceT m)
Version
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, HasPlatformReq env,
HasGHCupInfo env, HasSettings env, MonadCatch m, HasLog env,
MonadThrow m, MonadFail m, MonadResource m, MonadIO m,
MonadUnliftIO m) =>
Maybe String
-> Bool
-> Bool
-> Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
m
Version
upgradeGHCup Maybe String
forall a. Maybe a
Nothing Bool
False Bool
False Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
(ResourceT m)
Version
-> (Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> (Maybe VersionInfo
vi, Dirs
dirs, Maybe String
ce)
Tool
HLS -> do
let vi :: Maybe VersionInfo
vi = GHCTargetVersion -> Tool -> GHCupDownloads -> Maybe VersionInfo
getVersionInfo GHCTargetVersion
v Tool
HLS GHCupDownloads
dls
Maybe Text
-> (Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPreInstall (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> (Text
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> do
ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn Text
msg
ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn
Text
"...waiting for 5 seconds, you can still abort..."
IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a.
IO a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> IO ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
5000000
case InstallOptions
opts InstallOptions
-> Optic' A_Lens '[] InstallOptions (Maybe URI) -> Maybe URI
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] InstallOptions (Maybe URI)
AdvanceInstall.instBindistL of
Maybe URI
Nothing -> do
Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, ProcessError, DirNotEmpty, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, ProcessError, DirNotEmpty, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, ProcessError, DirNotEmpty, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$
Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, ProcessError, DirNotEmpty, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (e :: [*]) (m :: * -> *) a b.
(Monad m, Show (V e), Pretty (V e), HFErrorProject (V e),
PopVariant InstallSetError e, LiftVariant' e (InstallSetError : e),
e :<< (InstallSetError : e)) =>
Excepts e m a
-> Excepts e m b -> Excepts (InstallSetError : e) m ()
runBothE'
(Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
forall (m :: * -> *) env.
(MonadMask m, MonadCatch m, MonadReader env m, HasPlatformReq env,
HasGHCupInfo env, HasDirs env, HasSettings env, HasLog env,
MonadResource m, MonadIO m, MonadUnliftIO m, MonadFail m) =>
Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
m
()
installHLSBin Version
toolV InstallDir
shouldIsolate Bool
shouldForce)
(Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
shouldSet Bool -> Bool -> Bool
&& Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
misolated) (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall a b. (a -> b) -> a -> b
$ Version
-> SetHLS
-> Maybe String
-> Excepts '[NotInstalled] (ResourceT m) ()
forall env (m :: * -> *).
(MonadReader env m, HasDirs env, HasLog env, MonadIO m,
MonadMask m, MonadFail m, MonadUnliftIO m) =>
Version -> SetHLS -> Maybe String -> Excepts '[NotInstalled] m ()
setHLS Version
toolV SetHLS
SetHLSOnly Maybe String
forall a. Maybe a
Nothing))
(Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
forall a.
a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe VersionInfo
vi, Dirs
dirs, Maybe String
ce)
Just URI
uri -> do
Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, ProcessError, DirNotEmpty, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, ProcessError, DirNotEmpty, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, ProcessError, DirNotEmpty, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$
Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, ProcessError, DirNotEmpty, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (e :: [*]) (m :: * -> *) a b.
(Monad m, Show (V e), Pretty (V e), HFErrorProject (V e),
PopVariant InstallSetError e, LiftVariant' e (InstallSetError : e),
e :<< (InstallSetError : e)) =>
Excepts e m a
-> Excepts e m b -> Excepts (InstallSetError : e) m ()
runBothE'
(Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a. MonadReader AppState m => m a -> m a
withNoVerify (Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ DownloadInfo
-> Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
forall (m :: * -> *) env.
(MonadMask m, MonadCatch m, MonadReader env m, HasPlatformReq env,
HasDirs env, HasSettings env, HasLog env, MonadResource m,
MonadIO m, MonadUnliftIO m, MonadFail m) =>
DownloadInfo
-> Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
m
()
installHLSBindist
(Text
-> Maybe TarDir
-> Text
-> Maybe Integer
-> Maybe String
-> Maybe [Tag]
-> DownloadInfo
DownloadInfo ((ByteString -> Text
decUTF8Safe (ByteString -> Text) -> (URI -> ByteString) -> URI -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URI -> ByteString
forall a. URIRef a -> ByteString
serializeURIRef') URI
uri) (if Bool
isWindows then Maybe TarDir
forall a. Maybe a
Nothing else TarDir -> Maybe TarDir
forall a. a -> Maybe a
Just (String -> TarDir
RegexDir String
"haskell-language-server-*")) Text
"" Maybe Integer
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing Maybe [Tag]
forall a. Maybe a
Nothing)
Version
toolV
InstallDir
shouldIsolate
Bool
shouldForce)
(Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
shouldSet Bool -> Bool -> Bool
&& Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
misolated) (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
ProcessError, DirNotEmpty, UninstallFailed, MergeFileTreeError,
URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall a b. (a -> b) -> a -> b
$ Version
-> SetHLS
-> Maybe String
-> Excepts '[NotInstalled] (ResourceT m) ()
forall env (m :: * -> *).
(MonadReader env m, HasDirs env, HasLog env, MonadIO m,
MonadMask m, MonadFail m, MonadUnliftIO m) =>
Version -> SetHLS -> Maybe String -> Excepts '[NotInstalled] m ()
setHLS Version
toolV SetHLS
SetHLSOnly Maybe String
forall a. Maybe a
Nothing))
(Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
forall a.
a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe VersionInfo
vi, Dirs
dirs, Maybe String
ce)
Tool
Stack -> do
let vi :: Maybe VersionInfo
vi = GHCTargetVersion -> Tool -> GHCupDownloads -> Maybe VersionInfo
getVersionInfo GHCTargetVersion
v Tool
Stack GHCupDownloads
dls
case InstallOptions
opts InstallOptions
-> Optic' A_Lens '[] InstallOptions (Maybe URI) -> Maybe URI
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] InstallOptions (Maybe URI)
AdvanceInstall.instBindistL of
Maybe URI
Nothing -> do
Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$
Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
forall (e :: [*]) (m :: * -> *) a b.
(Monad m, Show (V e), Pretty (V e), HFErrorProject (V e),
PopVariant InstallSetError e, LiftVariant' e (InstallSetError : e),
e :<< (InstallSetError : e)) =>
Excepts e m a
-> Excepts e m b -> Excepts (InstallSetError : e) m ()
runBothE'
(Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (m :: * -> *) env.
(MonadMask m, MonadCatch m, MonadReader env m, HasDirs env,
HasSettings env, HasPlatformReq env, HasGHCupInfo env, HasLog env,
MonadResource m, MonadIO m, MonadUnliftIO m, MonadFail m) =>
Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
m
()
installStackBin Version
toolV InstallDir
shouldIsolate Bool
shouldForce)
(Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
shouldSet Bool -> Bool -> Bool
&& Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
misolated) (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall a b. (a -> b) -> a -> b
$ Version -> Excepts '[NotInstalled] (ResourceT m) ()
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, HasLog env,
MonadThrow m, MonadFail m, MonadIO m, MonadUnliftIO m) =>
Version -> Excepts '[NotInstalled] m ()
setStack Version
toolV))
(Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
forall a.
a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe VersionInfo
vi, Dirs
dirs, Maybe String
ce)
Just URI
uri -> do
Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
())
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$
Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[InstallSetError, AlreadyInstalled, CopyError, DigestError,
ContentLengthError, GPGError, DownloadFailed, NoDownload,
NotInstalled, UnknownArchive, TarDirDoesNotExist, ArchiveResult,
FileAlreadyExistsError, URIParseError]
(ResourceT m)
()
forall (e :: [*]) (m :: * -> *) a b.
(Monad m, Show (V e), Pretty (V e), HFErrorProject (V e),
PopVariant InstallSetError e, LiftVariant' e (InstallSetError : e),
e :<< (InstallSetError : e)) =>
Excepts e m a
-> Excepts e m b -> Excepts (InstallSetError : e) m ()
runBothE'
(Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a. MonadReader AppState m => m a -> m a
withNoVerify (Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ DownloadInfo
-> Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (m :: * -> *) env.
(MonadMask m, MonadCatch m, MonadReader env m, HasPlatformReq env,
HasDirs env, HasSettings env, HasLog env, MonadResource m,
MonadIO m, MonadUnliftIO m, MonadFail m) =>
DownloadInfo
-> Version
-> InstallDir
-> Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
m
()
installStackBindist (Text
-> Maybe TarDir
-> Text
-> Maybe Integer
-> Maybe String
-> Maybe [Tag]
-> DownloadInfo
DownloadInfo ((ByteString -> Text
decUTF8Safe (ByteString -> Text) -> (URI -> ByteString) -> URI -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URI -> ByteString
forall a. URIRef a -> ByteString
serializeURIRef') URI
uri) Maybe TarDir
forall a. Maybe a
Nothing Text
"" Maybe Integer
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing Maybe [Tag]
forall a. Maybe a
Nothing) Version
toolV InstallDir
shouldIsolate Bool
shouldForce)
(Bool
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
shouldSet Bool -> Bool -> Bool
&& Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
misolated) (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, CopyError, DigestError, ContentLengthError,
GPGError, DownloadFailed, NoDownload, NotInstalled, UnknownArchive,
TarDirDoesNotExist, ArchiveResult, FileAlreadyExistsError,
URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall a b. (a -> b) -> a -> b
$ Version -> Excepts '[NotInstalled] (ResourceT m) ()
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, HasLog env,
MonadThrow m, MonadFail m, MonadIO m, MonadUnliftIO m) =>
Version -> Excepts '[NotInstalled] m ()
setStack Version
toolV))
(Maybe VersionInfo, Dirs, Maybe String)
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Dirs, Maybe String)
forall a.
a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe VersionInfo
vi, Dirs
dirs, Maybe String
ce)
)
m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(Maybe VersionInfo, Dirs, Maybe String))
-> (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
(Maybe VersionInfo, Dirs, Maybe String)
-> m (Either String ()))
-> m (Either String ())
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
VRight (Maybe VersionInfo
vi, Dirs{String
GHCupPath
baseDir :: GHCupPath
binDir :: String
cacheDir :: GHCupPath
logsDir :: GHCupPath
confDir :: GHCupPath
dbDir :: GHCupPath
recycleDir :: GHCupPath
tmpDir :: GHCupPath
msys2Dir :: String
baseDir :: Dirs -> GHCupPath
binDir :: Dirs -> String
cacheDir :: Dirs -> GHCupPath
confDir :: Dirs -> GHCupPath
dbDir :: Dirs -> GHCupPath
logsDir :: Dirs -> GHCupPath
msys2Dir :: Dirs -> String
recycleDir :: Dirs -> GHCupPath
tmpDir :: Dirs -> GHCupPath
..}, Just String
ce) -> do
Maybe Text -> (Text -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPostInstall (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text -> m ()) -> m ()) -> (Text -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo Text
msg
case Tool
lTool of
Tool
GHCup -> do
#if !IS_WINDOWS
Maybe String
up <- IO (Maybe String) -> m (Maybe String)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe String) -> m (Maybe String))
-> IO (Maybe String) -> m (Maybe String)
forall a b. (a -> b) -> a -> b
$ (Either SomeException String -> Maybe String)
-> IO (Either SomeException String) -> IO (Maybe String)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((SomeException -> Maybe String)
-> (String -> Maybe String)
-> Either SomeException String
-> Maybe String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe String -> SomeException -> Maybe String
forall a b. a -> b -> a
const Maybe String
forall a. Maybe a
Nothing) String -> Maybe String
forall a. a -> Maybe a
Just)
(IO (Either SomeException String) -> IO (Maybe String))
-> IO (Either SomeException String) -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) e a.
(HasCallStack, MonadCatch m, Exception e) =>
m a -> m (Either e a)
try @_ @SomeException (IO String -> IO (Either SomeException String))
-> IO String -> IO (Either SomeException String)
forall a b. (a -> b) -> a -> b
$ String -> IO String
canonicalizePath (String
binDir String -> String -> String
</> String
"ghcup" String -> String -> String
<.> String
exeExt)
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((String -> String
normalise (String -> String) -> Maybe String -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
up) Maybe String -> Maybe String -> Bool
forall a. Eq a => a -> a -> Bool
== String -> Maybe String
forall a. a -> Maybe a
Just (String -> String
normalise String
ce)) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> Bool -> [String] -> Maybe [(String, String)] -> IO ()
forall a.
String -> Bool -> [String] -> Maybe [(String, String)] -> IO a
SPP.executeFile String
ce Bool
False [String
"tui"] Maybe [(String, String)]
forall a. Maybe a
Nothing
#else
logInfo "Please restart 'ghcup' for the changes to take effect"
#endif
Tool
_ -> () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
VRight (Maybe VersionInfo
vi, Dirs
_, Maybe String
_) -> do
Maybe Text -> (Text -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPostInstall (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text -> m ()) -> m ()) -> (Text -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo Text
msg
Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo Text
"Please restart 'ghcup' for the changes to take effect"
Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
VLeft (V (AlreadyInstalled Tool
_ Version
_)) -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
VLeft (V NoUpdate
NoUpdate) -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
VLeft V '[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
e -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$ V '[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
-> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError V '[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, InstallSetError, URIParseError]
e String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\n"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"Also check the logs in ~/.ghcup/logs"
install' :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> (Int, ListResult) -> m (Either String ())
install' :: forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m,
MonadMask m, MonadUnliftIO m, Alternative m) =>
(Int, ListResult) -> m (Either String ())
install' = InstallOptions -> (Int, ListResult) -> m (Either String ())
forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m,
MonadMask m, MonadUnliftIO m, Alternative m) =>
InstallOptions -> (Int, ListResult) -> m (Either String ())
installWithOptions (Maybe URI
-> Bool
-> Maybe GHCTargetVersion
-> Maybe String
-> Bool
-> [Text]
-> Text
-> InstallOptions
AdvanceInstall.InstallOptions Maybe URI
forall a. Maybe a
Nothing Bool
False Maybe GHCTargetVersion
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing Bool
False [] Text
"install")
set' :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> (Int, ListResult)
-> m (Either String ())
set' :: forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m,
MonadMask m, MonadUnliftIO m, Alternative m) =>
(Int, ListResult) -> m (Either String ())
set' input :: (Int, ListResult)
input@(Int
_, ListResult {Bool
[Tag]
Maybe Text
Maybe Day
Version
Tool
lTag :: ListResult -> [Tag]
lTool :: ListResult -> Tool
lVer :: ListResult -> Version
lCross :: ListResult -> Maybe Text
lInstalled :: ListResult -> Bool
hlsPowered :: ListResult -> Bool
lNoBindist :: ListResult -> Bool
lReleaseDay :: ListResult -> Maybe Day
lSet :: ListResult -> Bool
lStray :: ListResult -> Bool
lTool :: Tool
lVer :: Version
lCross :: Maybe Text
lTag :: [Tag]
lInstalled :: Bool
lSet :: Bool
lStray :: Bool
lNoBindist :: Bool
hlsPowered :: Bool
lReleaseDay :: Maybe Day
..}) = do
AppState
settings <- IO AppState -> m AppState
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AppState -> m AppState) -> IO AppState -> m AppState
forall a b. (a -> b) -> a -> b
$ IORef AppState -> IO AppState
forall a. IORef a -> IO a
readIORef IORef AppState
settings'
let run :: Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
a
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
run =
(ReaderT
AppState
m
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
-> AppState
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a))
-> AppState
-> ReaderT
AppState
m
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT
AppState
m
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
-> AppState
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT AppState
settings
(ReaderT
AppState
m
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a))
-> (Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
a
-> ReaderT
AppState
m
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a))
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
a
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ResourceT
(ReaderT AppState m)
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
-> ReaderT
AppState
m
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
forall (m :: * -> *) a. MonadUnliftIO m => ResourceT m a -> m a
runResourceT
(ResourceT
(ReaderT AppState m)
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
-> ReaderT
AppState
m
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a))
-> (Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
a
-> ResourceT
(ReaderT AppState m)
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a))
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
a
-> ReaderT
AppState
m
(VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (es :: [*]) a (m :: * -> *).
Excepts es m a -> m (VEither es a)
runE
@'[ AlreadyInstalled
, ArchiveResult
, UnknownArchive
, FileDoesNotExistError
, CopyError
, NoDownload
, NotInstalled
, BuildFailed
, TagNotFound
, DigestError
, ContentLengthError
, GPGError
, DownloadFailed
, DirNotEmpty
, NoUpdate
, TarDirDoesNotExist
, FileAlreadyExistsError
, ProcessError
, ToolShadowed
, UninstallFailed
, MergeFileTreeError
, NoCompatiblePlatform
, GHCup.Errors.ParseError
, UnsupportedSetupCombo
, DistroNotFound
, NoCompatibleArch
, URIParseError
]
Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
())
forall {a}.
Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
a
-> m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
a)
run (do
case Tool
lTool of
Tool
GHC -> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
())
-> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
forall a b. (a -> b) -> a -> b
$ GHCTargetVersion
-> SetGHC
-> Maybe String
-> Excepts
'[NotInstalled] (ResourceT (ReaderT AppState m)) GHCTargetVersion
forall env (m :: * -> *).
(MonadReader env m, HasDirs env, HasLog env, MonadThrow m,
MonadFail m, MonadIO m, MonadCatch m, MonadMask m,
MonadUnliftIO m) =>
GHCTargetVersion
-> SetGHC
-> Maybe String
-> Excepts '[NotInstalled] m GHCTargetVersion
setGHC (Maybe Text -> Version -> GHCTargetVersion
GHCTargetVersion Maybe Text
lCross Version
lVer) SetGHC
SetGHCOnly Maybe String
forall a. Maybe a
Nothing Excepts
'[NotInstalled] (ResourceT (ReaderT AppState m)) GHCTargetVersion
-> ()
-> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> ()
Tool
Cabal -> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
())
-> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
forall a b. (a -> b) -> a -> b
$ Version
-> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, HasLog env,
MonadFail m, MonadIO m, MonadUnliftIO m) =>
Version -> Excepts '[NotInstalled] m ()
setCabal Version
lVer Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> ()
-> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> ()
Tool
HLS -> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
())
-> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
forall a b. (a -> b) -> a -> b
$ Version
-> SetHLS
-> Maybe String
-> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
forall env (m :: * -> *).
(MonadReader env m, HasDirs env, HasLog env, MonadIO m,
MonadMask m, MonadFail m, MonadUnliftIO m) =>
Version -> SetHLS -> Maybe String -> Excepts '[NotInstalled] m ()
setHLS Version
lVer SetHLS
SetHLSOnly Maybe String
forall a. Maybe a
Nothing Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> ()
-> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> ()
Tool
Stack -> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
())
-> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
forall a b. (a -> b) -> a -> b
$ Version
-> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, HasLog env,
MonadThrow m, MonadFail m, MonadIO m, MonadUnliftIO m) =>
Version -> Excepts '[NotInstalled] m ()
setStack Version
lVer Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
-> ()
-> Excepts '[NotInstalled] (ResourceT (ReaderT AppState m)) ()
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> ()
Tool
GHCup -> do
PromptResponse
promptAnswer <- Text
-> PromptResponse
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
PromptResponse
forall env (m :: * -> *).
(HasLog env, MonadReader env m, MonadIO m) =>
Text -> PromptResponse -> m PromptResponse
getUserPromptResponse
Text
"Switching GHCup versions is not supported.\nDo you want to install the latest version? [Y/n]: "
PromptResponse
PromptYes
case PromptResponse
promptAnswer of
PromptResponse
PromptYes -> do
Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
Version
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
Version
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
())
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
Version
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
forall a b. (a -> b) -> a -> b
$ Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
(ResourceT (ReaderT AppState m))
Version
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
Version
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
(ResourceT (ReaderT AppState m))
Version
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
Version)
-> Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
(ResourceT (ReaderT AppState m))
Version
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
Version
forall a b. (a -> b) -> a -> b
$ Maybe String
-> Bool
-> Bool
-> Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
(ResourceT (ReaderT AppState m))
Version
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, HasPlatformReq env,
HasGHCupInfo env, HasSettings env, MonadCatch m, HasLog env,
MonadThrow m, MonadFail m, MonadResource m, MonadIO m,
MonadUnliftIO m) =>
Maybe String
-> Bool
-> Bool
-> Excepts
'[CopyError, DigestError, ContentLengthError, GPGError, GPGError,
DownloadFailed, NoDownload, NoUpdate, ToolShadowed, URIParseError]
m
Version
upgradeGHCup Maybe String
forall a. Maybe a
Nothing Bool
False Bool
False
PromptResponse
PromptNo -> ()
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
()
forall a.
a
-> Excepts
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
(ResourceT (ReaderT AppState m))
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
)
m (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
())
-> (VEither
'[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
()
-> m (Either String ()))
-> m (Either String ())
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
VRight ()
_ -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
VLeft V '[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
e -> case V '[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
e of
(V (NotInstalled Tool
tool GHCTargetVersion
_)) -> do
PromptResponse
promptAnswer <- Text -> PromptResponse -> m PromptResponse
forall env (m :: * -> *).
(HasLog env, MonadReader env m, MonadIO m) =>
Text -> PromptResponse -> m PromptResponse
getUserPromptResponse Text
userPrompt PromptResponse
PromptYes
case PromptResponse
promptAnswer of
PromptResponse
PromptYes -> do
Either String ()
res <- (Int, ListResult) -> m (Either String ())
forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m,
MonadMask m, MonadUnliftIO m, Alternative m) =>
(Int, ListResult) -> m (Either String ())
install' (Int, ListResult)
input
case Either String ()
res of
(Left String
err) -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left String
err
(Right ()
_) -> do
Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo Text
"Setting now..."
(Int, ListResult) -> m (Either String ())
forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m,
MonadMask m, MonadUnliftIO m, Alternative m) =>
(Int, ListResult) -> m (Either String ())
set' (Int, ListResult)
input
PromptResponse
PromptNo -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (V '[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
-> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError V '[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
e)
where
userPrompt :: Text
userPrompt = LazyText -> Text
L.toStrict (LazyText -> Text) -> (String -> LazyText) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> LazyText
B.toLazyText (Builder -> LazyText) -> (String -> Builder) -> String -> LazyText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
B.fromString (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
String
"This Version of "
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Tool -> String
forall a. Show a => a -> String
show Tool
tool
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" you are trying to set is not installed.\n"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"Would you like to install it first? [Y/n]: "
V '[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
_ -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (V '[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
-> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError V '[AlreadyInstalled, ArchiveResult, UnknownArchive,
FileDoesNotExistError, CopyError, NoDownload, NotInstalled,
BuildFailed, TagNotFound, DigestError, ContentLengthError,
GPGError, DownloadFailed, DirNotEmpty, NoUpdate,
TarDirDoesNotExist, FileAlreadyExistsError, ProcessError,
ToolShadowed, UninstallFailed, MergeFileTreeError,
NoCompatiblePlatform, ParseError, UnsupportedSetupCombo,
DistroNotFound, NoCompatibleArch, URIParseError]
e)
logGHCPostRm :: (MonadReader env m, HasLog env, MonadIO m) => GHCTargetVersion -> m ()
logGHCPostRm :: forall env (m :: * -> *).
(MonadReader env m, HasLog env, MonadIO m) =>
GHCTargetVersion -> m ()
logGHCPostRm GHCTargetVersion
ghcVer = do
String
cabalStore <- IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ (IOError -> IO String) -> IO String -> IO String
forall (m :: * -> *) a.
(HasCallStack, MonadCatch m) =>
(IOError -> m a) -> m a -> m a
handleIO (\IOError
_ -> if Bool
isWindows then String -> IO String
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"C:\\cabal\\store" else String -> IO String
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"~/.cabal/store or ~/.local/state/cabal/store")
IO String
getStoreDir
let storeGhcDir :: String
storeGhcDir = String
cabalStore String -> String -> String
</> (String
"ghc-" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack (Version -> Text
prettyVer (Version -> Text) -> Version -> Text
forall a b. (a -> b) -> a -> b
$ GHCTargetVersion -> Version
_tvVersion GHCTargetVersion
ghcVer))
Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"After removing GHC you might also want to clean up your cabal store at: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
storeGhcDir
del' :: (MonadReader AppState m, MonadIO m, MonadFail m, MonadMask m, MonadUnliftIO m)
=> (Int, ListResult)
-> m (Either String ())
del' :: forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadFail m, MonadMask m,
MonadUnliftIO m) =>
(Int, ListResult) -> m (Either String ())
del' (Int
_, ListResult {Bool
[Tag]
Maybe Text
Maybe Day
Version
Tool
lTag :: ListResult -> [Tag]
lTool :: ListResult -> Tool
lVer :: ListResult -> Version
lCross :: ListResult -> Maybe Text
lInstalled :: ListResult -> Bool
hlsPowered :: ListResult -> Bool
lNoBindist :: ListResult -> Bool
lReleaseDay :: ListResult -> Maybe Day
lSet :: ListResult -> Bool
lStray :: ListResult -> Bool
lTool :: Tool
lVer :: Version
lCross :: Maybe Text
lTag :: [Tag]
lInstalled :: Bool
lSet :: Bool
lStray :: Bool
lNoBindist :: Bool
hlsPowered :: Bool
lReleaseDay :: Maybe Day
..}) = do
AppState { ghcupInfo :: AppState -> GHCupInfo
ghcupInfo = GHCupInfo { _ghcupDownloads :: GHCupInfo -> GHCupDownloads
_ghcupDownloads = GHCupDownloads
dls }} <- m AppState
forall r (m :: * -> *). MonadReader r m => m r
ask
let run :: Excepts '[NotInstalled, UninstallFailed] m a
-> m (VEither '[NotInstalled, UninstallFailed] a)
run = forall (es :: [*]) a (m :: * -> *).
Excepts es m a -> m (VEither es a)
runE @'[NotInstalled, UninstallFailed]
Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
-> m (VEither '[NotInstalled, UninstallFailed] (Maybe VersionInfo))
forall {m :: * -> *} {a}.
Excepts '[NotInstalled, UninstallFailed] m a
-> m (VEither '[NotInstalled, UninstallFailed] a)
run (do
let vi :: Maybe VersionInfo
vi = GHCTargetVersion -> Tool -> GHCupDownloads -> Maybe VersionInfo
getVersionInfo GHCTargetVersion
crossVer Tool
lTool GHCupDownloads
dls
case Tool
lTool of
Tool
GHC -> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo))
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
forall a b. (a -> b) -> a -> b
$ GHCTargetVersion -> Excepts '[NotInstalled, UninstallFailed] m ()
forall env (m :: * -> *).
(MonadReader env m, HasDirs env, MonadThrow m, HasLog env,
MonadIO m, MonadFail m, MonadCatch m, MonadMask m,
MonadUnliftIO m) =>
GHCTargetVersion -> Excepts '[NotInstalled, UninstallFailed] m ()
rmGHCVer GHCTargetVersion
crossVer Excepts '[NotInstalled, UninstallFailed] m ()
-> Maybe VersionInfo
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe VersionInfo
vi
Tool
Cabal -> Excepts '[NotInstalled] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo))
-> Excepts '[NotInstalled] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
forall a b. (a -> b) -> a -> b
$ Version -> Excepts '[NotInstalled] m ()
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, MonadThrow m,
HasLog env, MonadIO m, MonadFail m, MonadCatch m,
MonadUnliftIO m) =>
Version -> Excepts '[NotInstalled] m ()
rmCabalVer Version
lVer Excepts '[NotInstalled] m ()
-> Maybe VersionInfo
-> Excepts '[NotInstalled] m (Maybe VersionInfo)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe VersionInfo
vi
Tool
HLS -> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo))
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
forall a b. (a -> b) -> a -> b
$ Version -> Excepts '[NotInstalled, UninstallFailed] m ()
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, MonadThrow m,
HasLog env, MonadIO m, MonadFail m, MonadCatch m,
MonadUnliftIO m) =>
Version -> Excepts '[NotInstalled, UninstallFailed] m ()
rmHLSVer Version
lVer Excepts '[NotInstalled, UninstallFailed] m ()
-> Maybe VersionInfo
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe VersionInfo
vi
Tool
Stack -> Excepts '[NotInstalled] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo))
-> Excepts '[NotInstalled] m (Maybe VersionInfo)
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
forall a b. (a -> b) -> a -> b
$ Version -> Excepts '[NotInstalled] m ()
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, MonadThrow m,
HasLog env, MonadIO m, MonadFail m, MonadCatch m,
MonadUnliftIO m) =>
Version -> Excepts '[NotInstalled] m ()
rmStackVer Version
lVer Excepts '[NotInstalled] m ()
-> Maybe VersionInfo
-> Excepts '[NotInstalled] m (Maybe VersionInfo)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe VersionInfo
vi
Tool
GHCup -> Maybe VersionInfo
-> Excepts '[NotInstalled, UninstallFailed] m (Maybe VersionInfo)
forall a. a -> Excepts '[NotInstalled, UninstallFailed] m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe VersionInfo
forall a. Maybe a
Nothing
)
m (VEither '[NotInstalled, UninstallFailed] (Maybe VersionInfo))
-> (VEither '[NotInstalled, UninstallFailed] (Maybe VersionInfo)
-> m (Either String ()))
-> m (Either String ())
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
VRight Maybe VersionInfo
vi -> do
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Tool
lTool Tool -> Tool -> Bool
forall a. Eq a => a -> a -> Bool
== Tool
GHC) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ GHCTargetVersion -> m ()
forall env (m :: * -> *).
(MonadReader env m, HasLog env, MonadIO m) =>
GHCTargetVersion -> m ()
logGHCPostRm GHCTargetVersion
crossVer
Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"Successfuly removed " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Tool -> String
forall a. Pretty a => a -> String
prettyShow Tool
lTool) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (if Tool
lTool Tool -> Tool -> Bool
forall a. Eq a => a -> a -> Bool
== Tool
GHC then GHCTargetVersion -> Text
tVerToText GHCTargetVersion
crossVer else Version -> Text
prettyVer Version
lVer)
Maybe Text -> (Text -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPostRemove (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text -> m ()) -> m ()) -> (Text -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Text
msg ->
Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo Text
msg
Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
VLeft V '[NotInstalled, UninstallFailed]
e -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (V '[NotInstalled, UninstallFailed] -> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError V '[NotInstalled, UninstallFailed]
e)
where
crossVer :: GHCTargetVersion
crossVer = Maybe Text -> Version -> GHCTargetVersion
GHCTargetVersion Maybe Text
lCross Version
lVer
changelog' :: (MonadReader AppState m, MonadIO m)
=> (Int, ListResult)
-> m (Either String ())
changelog' :: forall (m :: * -> *).
(MonadReader AppState m, MonadIO m) =>
(Int, ListResult) -> m (Either String ())
changelog' (Int
_, ListResult {Bool
[Tag]
Maybe Text
Maybe Day
Version
Tool
lTag :: ListResult -> [Tag]
lTool :: ListResult -> Tool
lVer :: ListResult -> Version
lCross :: ListResult -> Maybe Text
lInstalled :: ListResult -> Bool
hlsPowered :: ListResult -> Bool
lNoBindist :: ListResult -> Bool
lReleaseDay :: ListResult -> Maybe Day
lSet :: ListResult -> Bool
lStray :: ListResult -> Bool
lTool :: Tool
lVer :: Version
lCross :: Maybe Text
lTag :: [Tag]
lInstalled :: Bool
lSet :: Bool
lStray :: Bool
lNoBindist :: Bool
hlsPowered :: Bool
lReleaseDay :: Maybe Day
..}) = do
AppState { PlatformRequest
pfreq :: PlatformRequest
pfreq :: AppState -> PlatformRequest
pfreq, ghcupInfo :: AppState -> GHCupInfo
ghcupInfo = GHCupInfo { _ghcupDownloads :: GHCupInfo -> GHCupDownloads
_ghcupDownloads = GHCupDownloads
dls }} <- m AppState
forall r (m :: * -> *). MonadReader r m => m r
ask
case GHCupDownloads -> Tool -> ToolVersion -> Maybe URI
getChangeLog GHCupDownloads
dls Tool
lTool (Version -> ToolVersion
ToolVersion Version
lVer) of
Maybe URI
Nothing -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$
String
"Could not find ChangeLog for " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Tool -> String
forall a. Pretty a => a -> String
prettyShow Tool
lTool String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
", version " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack (Version -> Text
prettyVer Version
lVer)
Just URI
uri -> do
case PlatformRequest -> Platform
_rPlatform PlatformRequest
pfreq of
Platform
Darwin -> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> m (Either ProcessError ())
forall (m :: * -> *).
MonadIO m =>
String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> m (Either ProcessError ())
exec String
"open" [Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
decUTF8Safe (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ URI -> ByteString
forall a. URIRef a -> ByteString
serializeURIRef' URI
uri] Maybe String
forall a. Maybe a
Nothing Maybe [(String, String)]
forall a. Maybe a
Nothing
Linux LinuxDistro
_ -> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> m (Either ProcessError ())
forall (m :: * -> *).
MonadIO m =>
String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> m (Either ProcessError ())
exec String
"xdg-open" [Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
decUTF8Safe (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ URI -> ByteString
forall a. URIRef a -> ByteString
serializeURIRef' URI
uri] Maybe String
forall a. Maybe a
Nothing Maybe [(String, String)]
forall a. Maybe a
Nothing
Platform
FreeBSD -> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> m (Either ProcessError ())
forall (m :: * -> *).
MonadIO m =>
String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> m (Either ProcessError ())
exec String
"xdg-open" [Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
decUTF8Safe (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ URI -> ByteString
forall a. URIRef a -> ByteString
serializeURIRef' URI
uri] Maybe String
forall a. Maybe a
Nothing Maybe [(String, String)]
forall a. Maybe a
Nothing
Platform
OpenBSD -> String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> m (Either ProcessError ())
forall (m :: * -> *).
MonadIO m =>
String
-> [String]
-> Maybe String
-> Maybe [(String, String)]
-> m (Either ProcessError ())
exec String
"xdg-open" [Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
decUTF8Safe (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ URI -> ByteString
forall a. URIRef a -> ByteString
serializeURIRef' URI
uri] Maybe String
forall a. Maybe a
Nothing Maybe [(String, String)]
forall a. Maybe a
Nothing
Platform
Windows -> do
let args :: String
args = String
"start \"\" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
decUTF8Safe (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ URI -> ByteString
forall a. URIRef a -> ByteString
serializeURIRef' URI
uri)
ExitCode
c <- IO ExitCode -> m ExitCode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ExitCode -> m ExitCode) -> IO ExitCode -> m ExitCode
forall a b. (a -> b) -> a -> b
$ String -> IO ExitCode
system (String -> IO ExitCode) -> String -> IO ExitCode
forall a b. (a -> b) -> a -> b
$ String
args
case ExitCode
c of
(ExitFailure Int
xi) -> Either ProcessError () -> m (Either ProcessError ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ProcessError () -> m (Either ProcessError ()))
-> Either ProcessError () -> m (Either ProcessError ())
forall a b. (a -> b) -> a -> b
$ ProcessError -> Either ProcessError ()
forall a b. a -> Either a b
Left (ProcessError -> Either ProcessError ())
-> ProcessError -> Either ProcessError ()
forall a b. (a -> b) -> a -> b
$ Int -> String -> [String] -> ProcessError
NonZeroExit Int
xi String
"cmd.exe" [String
args]
ExitCode
ExitSuccess -> Either ProcessError () -> m (Either ProcessError ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ProcessError () -> m (Either ProcessError ()))
-> Either ProcessError () -> m (Either ProcessError ())
forall a b. (a -> b) -> a -> b
$ () -> Either ProcessError ()
forall a b. b -> Either a b
Right ()
m (Either ProcessError ())
-> (Either ProcessError () -> m (Either String ()))
-> m (Either String ())
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Right ()
_ -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
Left ProcessError
e -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$ ProcessError -> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError ProcessError
e
compileGHC :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> CompileGHC.CompileGHCOptions -> (Int, ListResult) -> m (Either String ())
compileGHC :: forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m,
MonadMask m, MonadUnliftIO m, Alternative m) =>
CompileGHCOptions -> (Int, ListResult) -> m (Either String ())
compileGHC CompileGHCOptions
compopts (Int
_, lr :: ListResult
lr@ListResult{lTool :: ListResult -> Tool
lTool = Tool
GHC, Bool
[Tag]
Maybe Text
Maybe Day
Version
lTag :: ListResult -> [Tag]
lVer :: ListResult -> Version
lCross :: ListResult -> Maybe Text
lInstalled :: ListResult -> Bool
hlsPowered :: ListResult -> Bool
lNoBindist :: ListResult -> Bool
lReleaseDay :: ListResult -> Maybe Day
lSet :: ListResult -> Bool
lStray :: ListResult -> Bool
lVer :: Version
lCross :: Maybe Text
lTag :: [Tag]
lInstalled :: Bool
lSet :: Bool
lStray :: Bool
lNoBindist :: Bool
hlsPowered :: Bool
lReleaseDay :: Maybe Day
..}) = do
AppState
appstate <- m AppState
forall r (m :: * -> *). MonadReader r m => m r
ask
let run :: Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
a
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
a)
run =
ResourceT
m
(VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
a)
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
a)
forall (m :: * -> *) a. MonadUnliftIO m => ResourceT m a -> m a
runResourceT
(ResourceT
m
(VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
a)
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
a))
-> (Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
a
-> ResourceT
m
(VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
a))
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
a
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (es :: [*]) a (m :: * -> *).
Excepts es m a -> m (VEither es a)
runE @'[ AlreadyInstalled
, BuildFailed
, DigestError
, ContentLengthError
, GPGError
, DownloadFailed
, GHCupSetError
, NoDownload
, NotFoundInPATH
, PatchFailed
, UnknownArchive
, TarDirDoesNotExist
, NotInstalled
, DirNotEmpty
, ArchiveResult
, FileDoesNotExistError
, HadrianNotFound
, InvalidBuildConfig
, ProcessError
, CopyError
, BuildFailed
, UninstallFailed
, MergeFileTreeError
, URIParseError
]
VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(Maybe VersionInfo, GHCTargetVersion)
compileResult <- Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, GHCTargetVersion)
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(Maybe VersionInfo, GHCTargetVersion))
forall {a}.
Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
a
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
a)
run (do
AppState { ghcupInfo :: AppState -> GHCupInfo
ghcupInfo = GHCupInfo { _ghcupDownloads :: GHCupInfo -> GHCupDownloads
_ghcupDownloads = GHCupDownloads
dls }} <- Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
AppState
forall r (m :: * -> *). MonadReader r m => m r
ask
GHCVer
ghcVer <- case CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions (Maybe String)
-> Maybe String
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions (Maybe String)
CompileGHC.gitRef of
Just String
ref -> GHCVer
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
GHCVer
forall a.
a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GitBranch -> GHCVer
GHC.GitDist (String -> Maybe String -> GitBranch
GitBranch String
ref Maybe String
forall a. Maybe a
Nothing))
Maybe String
Nothing -> do
let vi :: Maybe VersionInfo
vi = GHCTargetVersion -> Tool -> GHCupDownloads -> Maybe VersionInfo
getVersionInfo (Version -> GHCTargetVersion
mkTVer Version
lVer) Tool
GHC GHCupDownloads
dls
Maybe Text
-> (Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPreInstall (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> (Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> do
ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn Text
msg
ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn
Text
"...waiting for 5 seconds, you can still abort..."
IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a.
IO a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
5000000
Maybe Text
-> (Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPreCompile (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> (Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> do
Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo Text
msg
Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo
Text
"...waiting for 5 seconds, you can still abort..."
IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a.
IO a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
5000000
GHCVer
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
GHCVer
forall a.
a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Version -> GHCVer
GHC.SourceDist Version
lVer)
GHCTargetVersion
targetVer <- Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
GHCTargetVersion
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
GHCTargetVersion
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
GHCTargetVersion
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
GHCTargetVersion)
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
GHCTargetVersion
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
GHCTargetVersion
forall a b. (a -> b) -> a -> b
$ GHCVer
-> Maybe Text
-> Maybe [VersionPattern]
-> Either Version String
-> Maybe (Either Version String)
-> Maybe Int
-> Maybe String
-> Maybe (Either String [URI])
-> [Text]
-> Maybe String
-> Maybe BuildSystem
-> InstallDir
-> Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
GHCTargetVersion
forall (m :: * -> *) env.
(MonadMask m, MonadReader env m, HasDirs env, HasPlatformReq env,
HasGHCupInfo env, HasSettings env, MonadThrow m, MonadResource m,
HasLog env, MonadIO m, MonadUnliftIO m, MonadFail m) =>
GHCVer
-> Maybe Text
-> Maybe [VersionPattern]
-> Either Version String
-> Maybe (Either Version String)
-> Maybe Int
-> Maybe String
-> Maybe (Either String [URI])
-> [Text]
-> Maybe String
-> Maybe BuildSystem
-> InstallDir
-> Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
m
GHCTargetVersion
GHCup.compileGHC
GHCVer
ghcVer
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions (Maybe Text) -> Maybe Text
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions (Maybe Text)
CompileGHC.crossTarget)
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions (Maybe [VersionPattern])
-> Maybe [VersionPattern]
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions (Maybe [VersionPattern])
CompileGHC.overwriteVer)
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions (Either Version String)
-> Either Version String
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions (Either Version String)
CompileGHC.bootstrapGhc)
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic'
A_Lens '[] CompileGHCOptions (Maybe (Either Version String))
-> Maybe (Either Version String)
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions (Maybe (Either Version String))
CompileGHC.hadrianGhc)
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions (Maybe Int) -> Maybe Int
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions (Maybe Int)
CompileGHC.jobs)
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions (Maybe String)
-> Maybe String
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions (Maybe String)
CompileGHC.buildConfig)
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic'
A_Lens '[] CompileGHCOptions (Maybe (Either String [URI]))
-> Maybe (Either String [URI])
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions (Maybe (Either String [URI]))
CompileGHC.patches)
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions [Text] -> [Text]
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions [Text]
CompileGHC.addConfArgs)
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions (Maybe String)
-> Maybe String
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions (Maybe String)
CompileGHC.buildFlavour)
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions (Maybe BuildSystem)
-> Maybe BuildSystem
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions (Maybe BuildSystem)
CompileGHC.buildSystem)
(InstallDir -> (String -> InstallDir) -> Maybe String -> InstallDir
forall b a. b -> (a -> b) -> Maybe a -> b
maybe InstallDir
GHCupInternal String -> InstallDir
IsolateDir (Maybe String -> InstallDir) -> Maybe String -> InstallDir
forall a b. (a -> b) -> a -> b
$ CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions (Maybe String)
-> Maybe String
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions (Maybe String)
CompileGHC.isolateDir)
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions Text -> Text
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions Text
CompileGHC.installTargets)
AppState { ghcupInfo :: AppState -> GHCupInfo
ghcupInfo = GHCupInfo { _ghcupDownloads :: GHCupInfo -> GHCupDownloads
_ghcupDownloads = GHCupDownloads
dls2 }} <- Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
AppState
forall r (m :: * -> *). MonadReader r m => m r
ask
let vi2 :: Maybe VersionInfo
vi2 = GHCTargetVersion -> Tool -> GHCupDownloads -> Maybe VersionInfo
getVersionInfo GHCTargetVersion
targetVer Tool
GHC GHCupDownloads
dls2
Bool
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when
(CompileGHCOptions
compopts CompileGHCOptions
-> Optic' A_Lens '[] CompileGHCOptions Bool -> Bool
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileGHCOptions Bool
CompileGHC.setCompile)
(Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> (Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
-> Excepts '[NotInstalled] (ResourceT m) ())
-> Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
-> Excepts '[NotInstalled] (ResourceT m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ GHCTargetVersion
-> SetGHC
-> Maybe String
-> Excepts '[NotInstalled] (ResourceT m) GHCTargetVersion
forall env (m :: * -> *).
(MonadReader env m, HasDirs env, HasLog env, MonadThrow m,
MonadFail m, MonadIO m, MonadCatch m, MonadMask m,
MonadUnliftIO m) =>
GHCTargetVersion
-> SetGHC
-> Maybe String
-> Excepts '[NotInstalled] m GHCTargetVersion
GHCup.setGHC GHCTargetVersion
targetVer SetGHC
SetGHCOnly Maybe String
forall a. Maybe a
Nothing)
(Maybe VersionInfo, GHCTargetVersion)
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, GHCTargetVersion)
forall a.
a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe VersionInfo
vi2, GHCTargetVersion
targetVer)
)
case VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
(Maybe VersionInfo, GHCTargetVersion)
compileResult of
VRight (Maybe VersionInfo
vi, GHCTargetVersion
tv) -> do
Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo Text
"GHC successfully compiled and installed"
Maybe Text -> (Text -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPostInstall (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text -> m ()) -> m ()) -> (Text -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo Text
msg
IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
putStr (Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ GHCTargetVersion -> Text
tVerToText GHCTargetVersion
tv)
Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
VLeft (V (AlreadyInstalled Tool
_ Version
v)) -> do
Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$
String
"GHC ver " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack (Version -> Text
prettyVer Version
v) String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" already installed, remove it first to reinstall"
VLeft (V (DirNotEmpty String
fp)) -> do
Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$
String
"Install directory " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
fp String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" is not empty."
VLeft err :: V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
err@(V (BuildFailed String
tmpdir V es
_)) -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$
case Settings -> KeepDirs
keepDirs (AppState
appstate AppState -> (AppState -> Settings) -> Settings
forall a b. a -> (a -> b) -> b
& AppState -> Settings
settings) of
KeepDirs
Never -> V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
-> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
err
KeepDirs
_ -> V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
-> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
err String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\n"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"Check the logs at " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> (GHCupPath -> String
fromGHCupPath (GHCupPath -> String) -> GHCupPath -> String
forall a b. (a -> b) -> a -> b
$ AppState
appstate AppState -> (AppState -> Dirs) -> Dirs
forall a b. a -> (a -> b) -> b
& AppState -> Dirs
dirs Dirs -> (Dirs -> GHCupPath) -> GHCupPath
forall a b. a -> (a -> b) -> b
& Dirs -> GHCupPath
logsDir)
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" and the build directory "
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
tmpdir String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" for more clues." String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\n"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"Make sure to clean up " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
tmpdir String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" afterwards."
VLeft V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
e -> do
Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$ V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
-> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
NotInstalled, DirNotEmpty, ArchiveResult, FileDoesNotExistError,
HadrianNotFound, InvalidBuildConfig, ProcessError, CopyError,
BuildFailed, UninstallFailed, MergeFileTreeError, URIParseError]
e
compileGHC CompileGHCOptions
_ (Int
_, ListResult{lTool :: ListResult -> Tool
lTool = Tool
_}) = Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> Either String ()
forall a b. b -> Either a b
Right ())
compileHLS :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> CompileHLS.CompileHLSOptions -> (Int, ListResult) -> m (Either String ())
compileHLS :: forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m,
MonadMask m, MonadUnliftIO m, Alternative m) =>
CompileHLSOptions -> (Int, ListResult) -> m (Either String ())
compileHLS CompileHLSOptions
compopts (Int
_, lr :: ListResult
lr@ListResult{lTool :: ListResult -> Tool
lTool = Tool
HLS, Bool
[Tag]
Maybe Text
Maybe Day
Version
lTag :: ListResult -> [Tag]
lVer :: ListResult -> Version
lCross :: ListResult -> Maybe Text
lInstalled :: ListResult -> Bool
hlsPowered :: ListResult -> Bool
lNoBindist :: ListResult -> Bool
lReleaseDay :: ListResult -> Maybe Day
lSet :: ListResult -> Bool
lStray :: ListResult -> Bool
lVer :: Version
lCross :: Maybe Text
lTag :: [Tag]
lInstalled :: Bool
lSet :: Bool
lStray :: Bool
lNoBindist :: Bool
hlsPowered :: Bool
lReleaseDay :: Maybe Day
..}) = do
AppState
appstate <- m AppState
forall r (m :: * -> *). MonadReader r m => m r
ask
let run :: Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
a
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
a)
run =
ResourceT
m
(VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
a)
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
a)
forall (m :: * -> *) a. MonadUnliftIO m => ResourceT m a -> m a
runResourceT
(ResourceT
m
(VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
a)
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
a))
-> (Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
a
-> ResourceT
m
(VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
a))
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
a
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (es :: [*]) a (m :: * -> *).
Excepts es m a -> m (VEither es a)
runE @'[ AlreadyInstalled
, BuildFailed
, DigestError
, ContentLengthError
, GPGError
, DownloadFailed
, GHCupSetError
, NoDownload
, NotFoundInPATH
, PatchFailed
, UnknownArchive
, TarDirDoesNotExist
, TagNotFound
, DayNotFound
, NextVerNotFound
, NoToolVersionSet
, NotInstalled
, DirNotEmpty
, ArchiveResult
, UninstallFailed
, MergeFileTreeError
, URIParseError
]
VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(Maybe VersionInfo, Version)
compileResult <- Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Version)
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(Maybe VersionInfo, Version))
forall {a}.
Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
a
-> m (VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
a)
run (do
AppState { ghcupInfo :: AppState -> GHCupInfo
ghcupInfo = GHCupInfo { _ghcupDownloads :: GHCupInfo -> GHCupDownloads
_ghcupDownloads = GHCupDownloads
dls }} <- Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
AppState
forall r (m :: * -> *). MonadReader r m => m r
ask
HLSVer
hlsVer <- case CompileHLSOptions
compopts CompileHLSOptions
-> Optic' A_Lens '[] CompileHLSOptions (Maybe String)
-> Maybe String
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileHLSOptions (Maybe String)
CompileHLS.gitRef of
Just String
ref -> HLSVer
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
HLSVer
forall a.
a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GitBranch -> HLSVer
HLS.GitDist (String -> Maybe String -> GitBranch
GitBranch String
ref Maybe String
forall a. Maybe a
Nothing))
Maybe String
Nothing -> do
let vi :: Maybe VersionInfo
vi = GHCTargetVersion -> Tool -> GHCupDownloads -> Maybe VersionInfo
getVersionInfo (Version -> GHCTargetVersion
mkTVer Version
lVer) Tool
HLS GHCupDownloads
dls
Maybe Text
-> (Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPreInstall (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> (Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> do
ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn Text
msg
ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> ResourceT m ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Text -> ResourceT m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn
Text
"...waiting for 5 seconds, you can still abort..."
IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a.
IO a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
5000000
Maybe Text
-> (Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPreCompile (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> (Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> do
Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo Text
msg
Text
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo
Text
"...waiting for 5 seconds, you can still abort..."
IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a.
IO a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> IO ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
5000000
HLSVer
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
HLSVer
forall a.
a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Version -> HLSVer
HLS.SourceDist Version
lVer)
[Version]
ghcs <-
Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
[Version]
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
[Version]
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
[Version]
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
[Version])
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
[Version]
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
[Version]
forall a b. (a -> b) -> a -> b
$ [ToolVersion]
-> (ToolVersion
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
Version)
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
[Version]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (CompileHLSOptions
compopts CompileHLSOptions
-> Optic' A_Lens '[] CompileHLSOptions [ToolVersion]
-> [ToolVersion]
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileHLSOptions [ToolVersion]
CompileHLS.targetGHCs)
(\ToolVersion
ghc -> ((GHCTargetVersion, Maybe VersionInfo) -> Version)
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
(GHCTargetVersion, Maybe VersionInfo)
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
Version
forall a b.
(a -> b)
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
a
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (GHCTargetVersion -> Version
_tvVersion (GHCTargetVersion -> Version)
-> ((GHCTargetVersion, Maybe VersionInfo) -> GHCTargetVersion)
-> (GHCTargetVersion, Maybe VersionInfo)
-> Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GHCTargetVersion, Maybe VersionInfo) -> GHCTargetVersion
forall a b. (a, b) -> a
fst) (Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
(GHCTargetVersion, Maybe VersionInfo)
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
Version)
-> (Tool
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
(GHCTargetVersion, Maybe VersionInfo))
-> Tool
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe ToolVersion
-> GuessMode
-> Tool
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
(GHCTargetVersion, Maybe VersionInfo)
forall env (m :: * -> *).
(HasLog env, MonadFail m, MonadReader env m, HasGHCupInfo env,
HasDirs env, MonadThrow m, MonadIO m, MonadCatch m) =>
Maybe ToolVersion
-> GuessMode
-> Tool
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
m
(GHCTargetVersion, Maybe VersionInfo)
Utils.fromVersion (ToolVersion -> Maybe ToolVersion
forall a. a -> Maybe a
Just ToolVersion
ghc) GuessMode
GStrict (Tool
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
Version)
-> Tool
-> Excepts
'[TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet]
(ResourceT m)
Version
forall a b. (a -> b) -> a -> b
$ Tool
GHC)
Version
targetVer <- Excepts
'[NoDownload, GPGError, DownloadFailed, DigestError,
ContentLengthError, UnknownArchive, TarDirDoesNotExist,
ArchiveResult, BuildFailed, NotInstalled, URIParseError]
(ResourceT m)
Version
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
Version
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[NoDownload, GPGError, DownloadFailed, DigestError,
ContentLengthError, UnknownArchive, TarDirDoesNotExist,
ArchiveResult, BuildFailed, NotInstalled, URIParseError]
(ResourceT m)
Version
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
Version)
-> Excepts
'[NoDownload, GPGError, DownloadFailed, DigestError,
ContentLengthError, UnknownArchive, TarDirDoesNotExist,
ArchiveResult, BuildFailed, NotInstalled, URIParseError]
(ResourceT m)
Version
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
Version
forall a b. (a -> b) -> a -> b
$ HLSVer
-> [Version]
-> Maybe Int
-> Maybe [VersionPattern]
-> InstallDir
-> Maybe (Either String URI)
-> Maybe URI
-> Bool
-> Maybe (Either String [URI])
-> [Text]
-> Excepts
'[NoDownload, GPGError, DownloadFailed, DigestError,
ContentLengthError, UnknownArchive, TarDirDoesNotExist,
ArchiveResult, BuildFailed, NotInstalled, URIParseError]
(ResourceT m)
Version
forall (m :: * -> *) env.
(MonadMask m, MonadCatch m, MonadReader env m, HasDirs env,
HasSettings env, HasPlatformReq env, HasGHCupInfo env, HasLog env,
MonadResource m, MonadIO m, MonadUnliftIO m, MonadFail m) =>
HLSVer
-> [Version]
-> Maybe Int
-> Maybe [VersionPattern]
-> InstallDir
-> Maybe (Either String URI)
-> Maybe URI
-> Bool
-> Maybe (Either String [URI])
-> [Text]
-> Excepts
'[NoDownload, GPGError, DownloadFailed, DigestError,
ContentLengthError, UnknownArchive, TarDirDoesNotExist,
ArchiveResult, BuildFailed, NotInstalled, URIParseError]
m
Version
GHCup.compileHLS
HLSVer
hlsVer
[Version]
ghcs
(CompileHLSOptions
compopts CompileHLSOptions
-> Optic' A_Lens '[] CompileHLSOptions (Maybe Int) -> Maybe Int
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileHLSOptions (Maybe Int)
CompileHLS.jobs)
(CompileHLSOptions
compopts CompileHLSOptions
-> Optic' A_Lens '[] CompileHLSOptions (Maybe [VersionPattern])
-> Maybe [VersionPattern]
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileHLSOptions (Maybe [VersionPattern])
CompileHLS.overwriteVer)
(InstallDir -> (String -> InstallDir) -> Maybe String -> InstallDir
forall b a. b -> (a -> b) -> Maybe a -> b
maybe InstallDir
GHCupInternal String -> InstallDir
IsolateDir (Maybe String -> InstallDir) -> Maybe String -> InstallDir
forall a b. (a -> b) -> a -> b
$ CompileHLSOptions
compopts CompileHLSOptions
-> Optic' A_Lens '[] CompileHLSOptions (Maybe String)
-> Maybe String
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileHLSOptions (Maybe String)
CompileHLS.isolateDir)
(CompileHLSOptions
compopts CompileHLSOptions
-> Optic' A_Lens '[] CompileHLSOptions (Maybe (Either String URI))
-> Maybe (Either String URI)
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileHLSOptions (Maybe (Either String URI))
CompileHLS.cabalProject)
(CompileHLSOptions
compopts CompileHLSOptions
-> Optic' A_Lens '[] CompileHLSOptions (Maybe URI) -> Maybe URI
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileHLSOptions (Maybe URI)
CompileHLS.cabalProjectLocal)
(CompileHLSOptions
compopts CompileHLSOptions
-> Optic' A_Lens '[] CompileHLSOptions Bool -> Bool
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileHLSOptions Bool
CompileHLS.updateCabal)
(CompileHLSOptions
compopts CompileHLSOptions
-> Optic'
A_Lens '[] CompileHLSOptions (Maybe (Either String [URI]))
-> Maybe (Either String [URI])
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileHLSOptions (Maybe (Either String [URI]))
CompileHLS.patches)
(CompileHLSOptions
compopts CompileHLSOptions
-> Optic' A_Lens '[] CompileHLSOptions [Text] -> [Text]
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileHLSOptions [Text]
CompileHLS.cabalArgs)
AppState { ghcupInfo :: AppState -> GHCupInfo
ghcupInfo = GHCupInfo { _ghcupDownloads :: GHCupInfo -> GHCupDownloads
_ghcupDownloads = GHCupDownloads
dls2 }} <- Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
AppState
forall r (m :: * -> *). MonadReader r m => m r
ask
let vi2 :: Maybe VersionInfo
vi2 = GHCTargetVersion -> Tool -> GHCupDownloads -> Maybe VersionInfo
getVersionInfo (Version -> GHCTargetVersion
mkTVer Version
targetVer) Tool
GHC GHCupDownloads
dls2
Bool
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when
(CompileHLSOptions
compopts CompileHLSOptions
-> Optic' A_Lens '[] CompileHLSOptions Bool -> Bool
forall k s (is :: [*]) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens '[] CompileHLSOptions Bool
CompileHLS.setCompile)
(Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts '[NotInstalled] (ResourceT m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
())
-> Excepts '[NotInstalled] (ResourceT m) ()
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
()
forall a b. (a -> b) -> a -> b
$ Version
-> SetHLS
-> Maybe String
-> Excepts '[NotInstalled] (ResourceT m) ()
forall env (m :: * -> *).
(MonadReader env m, HasDirs env, HasLog env, MonadIO m,
MonadMask m, MonadFail m, MonadUnliftIO m) =>
Version -> SetHLS -> Maybe String -> Excepts '[NotInstalled] m ()
GHCup.setHLS Version
targetVer SetHLS
SetHLSOnly Maybe String
forall a. Maybe a
Nothing)
(Maybe VersionInfo, Version)
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
(Maybe VersionInfo, Version)
forall a.
a
-> Excepts
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(ResourceT m)
a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe VersionInfo
vi2, Version
targetVer)
)
case VEither
'[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
(Maybe VersionInfo, Version)
compileResult of
VRight (Maybe VersionInfo
vi, Version
tv) -> do
Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo Text
"HLS successfully compiled and installed"
Maybe Text -> (Text -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (VersionInfo -> Maybe Text
_viPostInstall (VersionInfo -> Maybe Text) -> Maybe VersionInfo -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe VersionInfo
vi) ((Text -> m ()) -> m ()) -> (Text -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Text
msg -> Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logInfo Text
msg
IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
putStr (Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Version -> Text
prettyVer Version
tv)
Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
VLeft err :: V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
err@(V (BuildFailed String
tmpdir V es
_)) -> Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$
case Settings -> KeepDirs
keepDirs (AppState
appstate AppState -> (AppState -> Settings) -> Settings
forall a b. a -> (a -> b) -> b
& AppState -> Settings
settings) of
KeepDirs
Never -> V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
-> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
err
KeepDirs
_ -> V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
-> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
err String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\n"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"Check the logs at " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> (GHCupPath -> String
fromGHCupPath (GHCupPath -> String) -> GHCupPath -> String
forall a b. (a -> b) -> a -> b
$ AppState
appstate AppState -> (AppState -> Dirs) -> Dirs
forall a b. a -> (a -> b) -> b
& AppState -> Dirs
dirs Dirs -> (Dirs -> GHCupPath) -> GHCupPath
forall a b. a -> (a -> b) -> b
& Dirs -> GHCupPath
logsDir)
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" and the build directory "
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
tmpdir String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" for more clues." String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\n"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"Make sure to clean up " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
tmpdir String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" afterwards."
VLeft V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
e -> do
Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> m (Either String ()))
-> Either String () -> m (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left (String -> Either String ()) -> String -> Either String ()
forall a b. (a -> b) -> a -> b
$ V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
-> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError V '[AlreadyInstalled, BuildFailed, DigestError, ContentLengthError,
GPGError, DownloadFailed, GHCupSetError, NoDownload,
NotFoundInPATH, PatchFailed, UnknownArchive, TarDirDoesNotExist,
TagNotFound, DayNotFound, NextVerNotFound, NoToolVersionSet,
NotInstalled, DirNotEmpty, ArchiveResult, UninstallFailed,
MergeFileTreeError, URIParseError]
e
compileHLS CompileHLSOptions
_ (Int
_, ListResult{lTool :: ListResult -> Tool
lTool = Tool
_}) = Either String () -> m (Either String ())
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> Either String ()
forall a b. b -> Either a b
Right ())
settings' :: IORef AppState
{-# NOINLINE settings' #-}
settings' :: IORef AppState
settings' = IO (IORef AppState) -> IORef AppState
forall a. IO a -> a
unsafePerformIO (IO (IORef AppState) -> IORef AppState)
-> IO (IORef AppState) -> IORef AppState
forall a b. (a -> b) -> a -> b
$ do
Dirs
dirs <- IO Dirs
getAllDirs
let loggerConfig :: LoggerConfig
loggerConfig = LoggerConfig { lcPrintDebug :: Bool
lcPrintDebug = Bool
False
, consoleOutter :: Text -> IO ()
consoleOutter = \Text
_ -> () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
, fileOutter :: Text -> IO ()
fileOutter = \Text
_ -> () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
, fancyColors :: Bool
fancyColors = Bool
True
}
AppState -> IO (IORef AppState)
forall a. a -> IO (IORef a)
newIORef (AppState -> IO (IORef AppState))
-> AppState -> IO (IORef AppState)
forall a b. (a -> b) -> a -> b
$ Settings
-> Dirs
-> KeyBindings
-> GHCupInfo
-> PlatformRequest
-> LoggerConfig
-> AppState
AppState Settings
defaultSettings
Dirs
dirs
KeyBindings
defaultKeyBindings
(ToolRequirements -> GHCupDownloads -> Maybe URI -> GHCupInfo
GHCupInfo ToolRequirements
forall a. Monoid a => a
mempty GHCupDownloads
forall a. Monoid a => a
mempty Maybe URI
forall a. Maybe a
Nothing)
(Architecture -> Platform -> Maybe Versioning -> PlatformRequest
PlatformRequest Architecture
A_64 Platform
Darwin Maybe Versioning
forall a. Maybe a
Nothing)
LoggerConfig
loggerConfig
getGHCupInfo :: IO (Either String GHCupInfo)
getGHCupInfo :: IO (Either String GHCupInfo)
getGHCupInfo = do
AppState
settings <- IORef AppState -> IO AppState
forall a. IORef a -> IO a
readIORef IORef AppState
settings'
VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo
r <-
(ReaderT
AppState
IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo)
-> AppState
-> IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo))
-> AppState
-> ReaderT
AppState
IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo)
-> IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo)
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT
AppState
IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo)
-> AppState
-> IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT AppState
settings
(ReaderT
AppState
IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo)
-> IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo))
-> (Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
GHCupInfo
-> ReaderT
AppState
IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo))
-> Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
GHCupInfo
-> IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (es :: [*]) a (m :: * -> *).
Excepts es m a -> m (VEither es a)
runE @'[DigestError, ContentLengthError, GPGError, JSONError , DownloadFailed , FileDoesNotExistError, StackPlatformDetectError]
(Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
GHCupInfo
-> IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo))
-> Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
GHCupInfo
-> IO
(VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo)
forall a b. (a -> b) -> a -> b
$ do
PlatformRequest
pfreq <- ReaderT AppState IO PlatformRequest
-> Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
PlatformRequest
forall (m :: * -> *) a.
Monad m =>
m a
-> Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
m
a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ReaderT AppState IO PlatformRequest
forall env (m :: * -> *).
(MonadReader env m,
LabelOptic' "pfreq" A_Lens env PlatformRequest) =>
m PlatformRequest
getPlatformReq
Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
GHCupInfo
-> Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
GHCupInfo
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE (Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
GHCupInfo
-> Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
GHCupInfo)
-> Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
GHCupInfo
-> Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
GHCupInfo
forall a b. (a -> b) -> a -> b
$ PlatformRequest
-> Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
(ReaderT AppState IO)
GHCupInfo
forall env (m :: * -> *).
(FromJSONKey Tool, FromJSONKey Version, FromJSON VersionInfo,
MonadReader env m, HasSettings env, HasDirs env, MonadIO m,
MonadCatch m, HasLog env, MonadThrow m, MonadFail m,
MonadMask m) =>
PlatformRequest
-> Excepts
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
m
GHCupInfo
getDownloadsF PlatformRequest
pfreq
case VEither
'[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
GHCupInfo
r of
VRight GHCupInfo
a -> Either String GHCupInfo -> IO (Either String GHCupInfo)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String GHCupInfo -> IO (Either String GHCupInfo))
-> Either String GHCupInfo -> IO (Either String GHCupInfo)
forall a b. (a -> b) -> a -> b
$ GHCupInfo -> Either String GHCupInfo
forall a b. b -> Either a b
Right GHCupInfo
a
VLeft V '[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
e -> Either String GHCupInfo -> IO (Either String GHCupInfo)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String GHCupInfo -> IO (Either String GHCupInfo))
-> Either String GHCupInfo -> IO (Either String GHCupInfo)
forall a b. (a -> b) -> a -> b
$ String -> Either String GHCupInfo
forall a b. a -> Either a b
Left (V '[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
-> String
forall e. (Pretty e, HFErrorProject e) => e -> String
prettyHFError V '[DigestError, ContentLengthError, GPGError, JSONError,
DownloadFailed, FileDoesNotExistError, StackPlatformDetectError]
e)
getAppData :: Maybe GHCupInfo
-> IO (Either String BrickData)
getAppData :: Maybe GHCupInfo -> IO (Either String BrickData)
getAppData Maybe GHCupInfo
mgi = ExceptT String IO BrickData -> IO (Either String BrickData)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT String IO BrickData -> IO (Either String BrickData))
-> ExceptT String IO BrickData -> IO (Either String BrickData)
forall a b. (a -> b) -> a -> b
$ do
GHCupInfo
r <- IO (Either String GHCupInfo) -> ExceptT String IO GHCupInfo
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (IO (Either String GHCupInfo) -> ExceptT String IO GHCupInfo)
-> IO (Either String GHCupInfo) -> ExceptT String IO GHCupInfo
forall a b. (a -> b) -> a -> b
$ IO (Either String GHCupInfo)
-> (GHCupInfo -> IO (Either String GHCupInfo))
-> Maybe GHCupInfo
-> IO (Either String GHCupInfo)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO (Either String GHCupInfo)
getGHCupInfo (Either String GHCupInfo -> IO (Either String GHCupInfo)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String GHCupInfo -> IO (Either String GHCupInfo))
-> (GHCupInfo -> Either String GHCupInfo)
-> GHCupInfo
-> IO (Either String GHCupInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GHCupInfo -> Either String GHCupInfo
forall a b. b -> Either a b
Right) Maybe GHCupInfo
mgi
IO () -> ExceptT String IO ()
forall a. IO a -> ExceptT String IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT String IO ()) -> IO () -> ExceptT String IO ()
forall a b. (a -> b) -> a -> b
$ IORef AppState -> (AppState -> AppState) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef IORef AppState
settings' (\AppState
s -> AppState
s { ghcupInfo = r })
AppState
settings <- IO AppState -> ExceptT String IO AppState
forall a. IO a -> ExceptT String IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AppState -> ExceptT String IO AppState)
-> IO AppState -> ExceptT String IO AppState
forall a b. (a -> b) -> a -> b
$ IORef AppState -> IO AppState
forall a. IORef a -> IO a
readIORef IORef AppState
settings'
(ReaderT AppState (ExceptT String IO) BrickData
-> AppState -> ExceptT String IO BrickData)
-> AppState
-> ReaderT AppState (ExceptT String IO) BrickData
-> ExceptT String IO BrickData
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT AppState (ExceptT String IO) BrickData
-> AppState -> ExceptT String IO BrickData
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT AppState
settings (ReaderT AppState (ExceptT String IO) BrickData
-> ExceptT String IO BrickData)
-> ReaderT AppState (ExceptT String IO) BrickData
-> ExceptT String IO BrickData
forall a b. (a -> b) -> a -> b
$ do
[ListResult]
lV <- Maybe Tool
-> [ListCriteria]
-> Bool
-> Bool
-> (Maybe Day, Maybe Day)
-> ReaderT AppState (ExceptT String IO) [ListResult]
forall (m :: * -> *) env.
(MonadCatch m, HasLog env, MonadThrow m, HasLog env, MonadIO m,
MonadReader env m, HasDirs env, HasPlatformReq env,
HasGHCupInfo env) =>
Maybe Tool
-> [ListCriteria]
-> Bool
-> Bool
-> (Maybe Day, Maybe Day)
-> m [ListResult]
listVersions Maybe Tool
forall a. Maybe a
Nothing [] Bool
False Bool
True (Maybe Day
forall a. Maybe a
Nothing, Maybe Day
forall a. Maybe a
Nothing)
BrickData -> ReaderT AppState (ExceptT String IO) BrickData
forall a. a -> ReaderT AppState (ExceptT String IO) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BrickData -> ReaderT AppState (ExceptT String IO) BrickData)
-> BrickData -> ReaderT AppState (ExceptT String IO) BrickData
forall a b. (a -> b) -> a -> b
$ [ListResult] -> BrickData
BrickData ([ListResult] -> [ListResult]
forall a. [a] -> [a]
reverse [ListResult]
lV)
keyHandlers :: KeyBindings
-> [ ( KeyCombination
, BrickSettings -> String
, Brick.EventM Name BrickState ()
)
]
keyHandlers :: KeyBindings
-> [(KeyCombination, BrickSettings -> String,
EventM Name BrickState ())]
keyHandlers KeyBindings {KeyCombination
bUp :: KeyCombination
bDown :: KeyCombination
bQuit :: KeyCombination
bInstall :: KeyCombination
bUninstall :: KeyCombination
bSet :: KeyCombination
bChangelog :: KeyCombination
bShowAllVersions :: KeyCombination
bChangelog :: KeyBindings -> KeyCombination
bDown :: KeyBindings -> KeyCombination
bInstall :: KeyBindings -> KeyCombination
bQuit :: KeyBindings -> KeyCombination
bSet :: KeyBindings -> KeyCombination
bShowAllVersions :: KeyBindings -> KeyCombination
bUninstall :: KeyBindings -> KeyCombination
bUp :: KeyBindings -> KeyCombination
..} =
[ (KeyCombination
bQuit, String -> BrickSettings -> String
forall a b. a -> b -> a
const String
"Quit" , EventM Name BrickState ()
forall n s. EventM n s ()
Brick.halt)
, (KeyCombination
bInstall, String -> BrickSettings -> String
forall a b. a -> b -> a
const String
"Install" , ((Int, ListResult) -> ReaderT AppState IO (Either String ()))
-> EventM Name BrickState ()
forall n a.
(Ord n, Eq n) =>
((Int, ListResult) -> ReaderT AppState IO (Either String a))
-> EventM n BrickState ()
withIOAction (Int, ListResult) -> ReaderT AppState IO (Either String ())
forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m,
MonadMask m, MonadUnliftIO m, Alternative m) =>
(Int, ListResult) -> m (Either String ())
install')
, (KeyCombination
bUninstall, String -> BrickSettings -> String
forall a b. a -> b -> a
const String
"Uninstall", ((Int, ListResult) -> ReaderT AppState IO (Either String ()))
-> EventM Name BrickState ()
forall n a.
(Ord n, Eq n) =>
((Int, ListResult) -> ReaderT AppState IO (Either String a))
-> EventM n BrickState ()
withIOAction (Int, ListResult) -> ReaderT AppState IO (Either String ())
forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadFail m, MonadMask m,
MonadUnliftIO m) =>
(Int, ListResult) -> m (Either String ())
del')
, (KeyCombination
bSet, String -> BrickSettings -> String
forall a b. a -> b -> a
const String
"Set" , ((Int, ListResult) -> ReaderT AppState IO (Either String ()))
-> EventM Name BrickState ()
forall n a.
(Ord n, Eq n) =>
((Int, ListResult) -> ReaderT AppState IO (Either String a))
-> EventM n BrickState ()
withIOAction (Int, ListResult) -> ReaderT AppState IO (Either String ())
forall (m :: * -> *).
(MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m,
MonadMask m, MonadUnliftIO m, Alternative m) =>
(Int, ListResult) -> m (Either String ())
set')
, (KeyCombination
bChangelog, String -> BrickSettings -> String
forall a b. a -> b -> a
const String
"ChangeLog", ((Int, ListResult) -> ReaderT AppState IO (Either String ()))
-> EventM Name BrickState ()
forall n a.
(Ord n, Eq n) =>
((Int, ListResult) -> ReaderT AppState IO (Either String a))
-> EventM n BrickState ()
withIOAction (Int, ListResult) -> ReaderT AppState IO (Either String ())
forall (m :: * -> *).
(MonadReader AppState m, MonadIO m) =>
(Int, ListResult) -> m (Either String ())
changelog')
, ( KeyCombination
bShowAllVersions
, \BrickSettings {Bool
_showAllVersions :: BrickSettings -> Bool
_showAllVersions :: Bool
..} ->
if Bool
_showAllVersions then String
"Don't show all versions" else String
"Show all versions"
, (BrickSettings -> Bool) -> EventM Name BrickState ()
forall {m :: * -> *}.
MonadState BrickState m =>
(BrickSettings -> Bool) -> m ()
hideShowHandler' (Bool -> Bool
not (Bool -> Bool) -> (BrickSettings -> Bool) -> BrickSettings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BrickSettings -> Bool
_showAllVersions)
)
, (KeyCombination
bUp, String -> BrickSettings -> String
forall a b. a -> b -> a
const String
"Up", Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
-> EventM Name (GenericSectionList Name Vector ListResult) ()
-> EventM Name BrickState ()
forall {m :: * -> *} {n :: * -> *} {s} {t} {k} {c} {is :: [*]}.
(Zoom m n s t, Is k A_Lens, Functor (Zoomed m c)) =>
Optic k is t t s s -> m c -> n c
Common.zoom Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
appState EventM Name (GenericSectionList Name Vector ListResult) ()
forall (t :: * -> *) n e.
(Splittable t, Ord n, Foldable t) =>
EventM n (GenericSectionList n t e) ()
moveUp)
, (KeyCombination
bDown, String -> BrickSettings -> String
forall a b. a -> b -> a
const String
"Down", Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
-> EventM Name (GenericSectionList Name Vector ListResult) ()
-> EventM Name BrickState ()
forall {m :: * -> *} {n :: * -> *} {s} {t} {k} {c} {is :: [*]}.
(Zoom m n s t, Is k A_Lens, Functor (Zoomed m c)) =>
Optic k is t t s s -> m c -> n c
Common.zoom Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
appState EventM Name (GenericSectionList Name Vector ListResult) ()
forall (t :: * -> *) n e.
(Splittable t, Ord n, Foldable t) =>
EventM n (GenericSectionList n t e) ()
moveDown)
, (Key -> [Modifier] -> KeyCombination
KeyCombination (Char -> Key
Vty.KChar Char
'h') [], String -> BrickSettings -> String
forall a b. a -> b -> a
const String
"help", Lens' BrickState Mode
mode Lens' BrickState Mode -> Mode -> EventM Name BrickState ()
forall k s (m :: * -> *) (is :: [*]) a b.
(Is k A_Setter, MonadState s m) =>
Optic k is s s a b -> b -> m ()
.= Mode
KeyInfo)
, (Key -> [Modifier] -> KeyCombination
KeyCombination Key
Vty.KEnter [], String -> BrickSettings -> String
forall a b. a -> b -> a
const String
"advance options", EventM Name BrickState ()
createMenuforTool )
]
where
createMenuforTool :: EventM Name BrickState ()
createMenuforTool = do
Maybe (Int, ListResult)
e <- Optic' A_Getter '[] BrickState (Maybe (Int, ListResult))
-> EventM Name BrickState (Maybe (Int, ListResult))
forall k s (m :: * -> *) (is :: [*]) a.
(Is k A_Getter, MonadState s m) =>
Optic' k is s a -> m a
use (Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
appState Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
-> Optic
A_Getter
'[]
(GenericSectionList Name Vector ListResult)
(GenericSectionList Name Vector ListResult)
(Maybe (Int, ListResult))
(Maybe (Int, ListResult))
-> Optic' A_Getter '[] BrickState (Maybe (Int, ListResult))
forall k l m (is :: [*]) (js :: [*]) (ks :: [*]) s t u v a b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% (GenericSectionList Name Vector ListResult
-> Maybe (Int, ListResult))
-> Optic
A_Getter
'[]
(GenericSectionList Name Vector ListResult)
(GenericSectionList Name Vector ListResult)
(Maybe (Int, ListResult))
(Maybe (Int, ListResult))
forall s a. (s -> a) -> Getter s a
to GenericSectionList Name Vector ListResult
-> Maybe (Int, ListResult)
forall n (t :: * -> *) e.
(Eq n, Splittable t, Traversable t, Semigroup (t e)) =>
GenericSectionList n t e -> Maybe (Int, e)
sectionListSelectedElement)
case Maybe (Int, ListResult)
e of
Maybe (Int, ListResult)
Nothing -> () -> EventM Name BrickState ()
forall a. a -> EventM Name BrickState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just (Int
_, ListResult
r) -> do
Lens' BrickState ContextMenu
contextMenu Lens' BrickState ContextMenu
-> ContextMenu -> EventM Name BrickState ()
forall k s (m :: * -> *) (is :: [*]) a b.
(Is k A_Setter, MonadState s m) =>
Optic k is s s a b -> b -> m ()
.= ListResult -> MenuKeyBindings -> ContextMenu
ContextMenu.create ListResult
r
(MenuKeyBindings { mKbUp :: KeyCombination
mKbUp = KeyCombination
bUp, mKbDown :: KeyCombination
mKbDown = KeyCombination
bDown, mKbQuit :: KeyCombination
mKbQuit = KeyCombination
bQuit})
Lens' BrickState Mode
mode Lens' BrickState Mode -> Mode -> EventM Name BrickState ()
forall k s (m :: * -> *) (is :: [*]) a b.
(Is k A_Setter, MonadState s m) =>
Optic k is s s a b -> b -> m ()
.= Mode
ContextPanel
() -> EventM Name BrickState ()
forall a. a -> EventM Name BrickState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
hideShowHandler' :: (BrickSettings -> Bool) -> m ()
hideShowHandler' BrickSettings -> Bool
f = do
BrickSettings
app_settings <- Optic' A_Lens '[] BrickState BrickSettings -> m BrickSettings
forall k s (m :: * -> *) (is :: [*]) a.
(Is k A_Getter, MonadState s m) =>
Optic' k is s a -> m a
use Optic' A_Lens '[] BrickState BrickSettings
appSettings
let
vers :: Bool
vers = BrickSettings -> Bool
f BrickSettings
app_settings
newAppSettings :: BrickSettings
newAppSettings = BrickSettings
app_settings BrickSettings -> (BrickSettings -> BrickSettings) -> BrickSettings
forall a b. a -> (a -> b) -> b
& Iso' BrickSettings Bool
Common.showAllVersions Iso' BrickSettings Bool -> Bool -> BrickSettings -> BrickSettings
forall k (is :: [*]) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Bool
vers
BrickData
ad <- Lens' BrickState BrickData -> m BrickData
forall k s (m :: * -> *) (is :: [*]) a.
(Is k A_Getter, MonadState s m) =>
Optic' k is s a -> m a
use Lens' BrickState BrickData
appData
GenericSectionList Name Vector ListResult
current_app_state <- Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
-> m (GenericSectionList Name Vector ListResult)
forall k s (m :: * -> *) (is :: [*]) a.
(Is k A_Getter, MonadState s m) =>
Optic' k is s a -> m a
use Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
appState
Optic' A_Lens '[] BrickState BrickSettings
appSettings Optic' A_Lens '[] BrickState BrickSettings -> BrickSettings -> m ()
forall k s (m :: * -> *) (is :: [*]) a b.
(Is k A_Setter, MonadState s m) =>
Optic k is s s a b -> b -> m ()
.= BrickSettings
newAppSettings
Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
appState Optic'
A_Lens '[] BrickState (GenericSectionList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult -> m ()
forall k s (m :: * -> *) (is :: [*]) a b.
(Is k A_Setter, MonadState s m) =>
Optic k is s s a b -> b -> m ()
.= BrickData
-> BrickSettings
-> Maybe (GenericSectionList Name Vector ListResult)
-> GenericSectionList Name Vector ListResult
constructList BrickData
ad BrickSettings
newAppSettings (GenericSectionList Name Vector ListResult
-> Maybe (GenericSectionList Name Vector ListResult)
forall a. a -> Maybe a
Just GenericSectionList Name Vector ListResult
current_app_state)