Refactor excepts
This commit is contained in:
@@ -141,6 +141,7 @@ instance Pretty AlreadyInstalled where
|
||||
|
||||
-- | The Directory is supposed to be empty, but wasn't.
|
||||
data DirNotEmpty = DirNotEmpty {path :: FilePath}
|
||||
deriving Show
|
||||
|
||||
instance Pretty DirNotEmpty where
|
||||
pPrint (DirNotEmpty path) = do
|
||||
@@ -344,6 +345,17 @@ instance Pretty DownloadFailed where
|
||||
|
||||
deriving instance Show DownloadFailed
|
||||
|
||||
data InstallSetError = forall xs1 xs2 . (Show (V xs1), Pretty (V xs1), Show (V xs2), Pretty (V xs2)) => InstallSetError (V xs1) (V xs2)
|
||||
|
||||
instance Pretty InstallSetError where
|
||||
pPrint (InstallSetError reason1 reason2) =
|
||||
text "Both installation and setting the tool failed. Install error was:"
|
||||
<+> pPrint reason1
|
||||
<+> text "\nSet error was:"
|
||||
<+> pPrint reason2
|
||||
|
||||
deriving instance Show InstallSetError
|
||||
|
||||
|
||||
-- | A build failed.
|
||||
data BuildFailed = forall es . (ToVariantMaybe BuildFailed es, PopVariant BuildFailed es, Pretty (V es), Show (V es)) => BuildFailed FilePath (V es)
|
||||
|
||||
@@ -4,6 +4,7 @@
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
|
||||
{-|
|
||||
Module : GHCup.Prelude
|
||||
@@ -27,6 +28,7 @@ module GHCup.Prelude
|
||||
)
|
||||
where
|
||||
|
||||
import GHCup.Errors
|
||||
import GHCup.Prelude.Internal
|
||||
import GHCup.Types.Optics (HasLog)
|
||||
import GHCup.Prelude.Logger (logWarn)
|
||||
@@ -52,3 +54,29 @@ catchWarn :: forall es m env . ( Pretty (V es)
|
||||
, Monad m) => Excepts es m () -> Excepts '[] m ()
|
||||
catchWarn = catchAllE @_ @es (\v -> lift $ logWarn (T.pack . prettyShow $ v))
|
||||
|
||||
|
||||
runBothE' :: forall e m a b .
|
||||
( Monad m
|
||||
, Show (V e)
|
||||
, Pretty (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' a1 a2 = do
|
||||
r1 <- lift $ runE @e a1
|
||||
r2 <- lift $ runE @e a2
|
||||
case (r1, r2) of
|
||||
(VLeft e1, VLeft e2) -> throwE (InstallSetError e1 e2)
|
||||
(VLeft e , _ ) -> throwSomeE e
|
||||
(_ , VLeft e ) -> throwSomeE e
|
||||
(VRight _, VRight _) -> pure ()
|
||||
|
||||
|
||||
-- | Throw some exception
|
||||
throwSomeE :: forall es' es a m. (Monad m, LiftVariant es' es) => V es' -> Excepts es m a
|
||||
{-# INLINABLE throwSomeE #-}
|
||||
throwSomeE = Excepts . pure . VLeft . liftVariant
|
||||
|
||||
Reference in New Issue
Block a user