2022-05-21 20:54:18 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
|
|
{-# LANGUAGE TypeFamilies #-}
|
2022-05-23 21:32:58 +00:00
|
|
|
{-# LANGUAGE TypeOperators #-}
|
2022-05-21 20:54:18 +00:00
|
|
|
|
|
|
|
{-|
|
|
|
|
Module : GHCup.Prelude
|
|
|
|
Description : MegaParsec utilities
|
|
|
|
Copyright : (c) Julian Ospald, 2020
|
|
|
|
License : LGPL-3.0
|
|
|
|
Maintainer : hasufell@hasufell.de
|
|
|
|
Stability : experimental
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
GHCup specific prelude. Lots of Excepts functionality.
|
|
|
|
-}
|
|
|
|
module GHCup.Prelude
|
|
|
|
(module GHCup.Prelude,
|
|
|
|
module GHCup.Prelude.Internal,
|
|
|
|
#if defined(IS_WINDOWS)
|
|
|
|
module GHCup.Prelude.Windows
|
|
|
|
#else
|
|
|
|
module GHCup.Prelude.Posix
|
|
|
|
#endif
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
2022-05-23 21:32:58 +00:00
|
|
|
import GHCup.Errors
|
2022-05-21 20:54:18 +00:00
|
|
|
import GHCup.Prelude.Internal
|
|
|
|
import GHCup.Types.Optics (HasLog)
|
|
|
|
import GHCup.Prelude.Logger (logWarn)
|
|
|
|
#if defined(IS_WINDOWS)
|
|
|
|
import GHCup.Prelude.Windows
|
|
|
|
#else
|
|
|
|
import GHCup.Prelude.Posix
|
|
|
|
#endif
|
|
|
|
|
|
|
|
import Control.Monad.IO.Class
|
|
|
|
import Control.Monad.Reader
|
|
|
|
import Haskus.Utils.Variant.Excepts
|
2022-12-19 16:10:19 +00:00
|
|
|
import Text.PrettyPrint.HughesPJClass ( Pretty )
|
2022-05-21 20:54:18 +00:00
|
|
|
import qualified Data.Text as T
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
-- for some obscure reason... this won't type-check if we move it to a different module
|
|
|
|
catchWarn :: forall es m env . ( Pretty (V es)
|
2022-12-19 16:10:19 +00:00
|
|
|
, HFErrorProject (V es)
|
2022-05-21 20:54:18 +00:00
|
|
|
, MonadReader env m
|
|
|
|
, HasLog env
|
|
|
|
, MonadIO m
|
|
|
|
, Monad m) => Excepts es m () -> Excepts '[] m ()
|
2022-12-19 16:10:19 +00:00
|
|
|
catchWarn = catchAllE @_ @es (\v -> lift $ logWarn (T.pack . prettyHFError $ v))
|
2022-05-21 20:54:18 +00:00
|
|
|
|
2022-05-23 21:32:58 +00:00
|
|
|
|
|
|
|
runBothE' :: forall e m a b .
|
|
|
|
( Monad m
|
|
|
|
, Show (V e)
|
|
|
|
, Pretty (V e)
|
2022-12-19 16:10:19 +00:00
|
|
|
, HFErrorProject (V e)
|
2022-05-23 21:32:58 +00:00
|
|
|
, 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
|