-
Notifications
You must be signed in to change notification settings - Fork 90
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
Showing
6 changed files
with
199 additions
and
0 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,124 @@ | ||
{-# LANGUAGE CPP #-} | ||
{-# LANGUAGE DataKinds #-} | ||
{-# LANGUAGE TypeApplications #-} | ||
{-# LANGUAGE FlexibleContexts #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
{-# LANGUAGE TemplateHaskell #-} | ||
{-# LANGUAGE QuasiQuotes #-} | ||
{-# LANGUAGE DuplicateRecordFields #-} | ||
{-# LANGUAGE RankNTypes #-} | ||
|
||
module GHCup.OptParse.HealthCheck where | ||
|
||
|
||
import GHCup | ||
import GHCup.Errors | ||
import GHCup.Types | ||
import GHCup.Prelude.Logger | ||
import GHCup.Prelude.String.QQ | ||
|
||
#if !MIN_VERSION_base(4,13,0) | ||
import Control.Monad.Fail ( MonadFail ) | ||
#endif | ||
import Control.Monad.Reader | ||
import Control.Monad.Trans.Resource | ||
import Data.Functor | ||
import Haskus.Utils.Variant.Excepts | ||
import Options.Applicative hiding ( style ) | ||
import Prelude hiding ( appendFile ) | ||
import System.Exit | ||
|
||
import qualified Data.Text as T | ||
import Control.Exception.Safe (MonadMask) | ||
|
||
|
||
|
||
|
||
|
||
--------------- | ||
--[ Options ]-- | ||
--------------- | ||
|
||
|
||
data HealtCheckOptions = HealtCheckOptions | ||
{ hcOffline :: Bool | ||
} deriving (Eq, Show) | ||
|
||
|
||
|
||
--------------- | ||
--[ Parsers ]-- | ||
--------------- | ||
|
||
|
||
hcP :: Parser HealtCheckOptions | ||
hcP = | ||
HealtCheckOptions | ||
<$> | ||
switch | ||
(short 'o' <> long "offline" <> help "Only do checks that don't require internet") | ||
|
||
|
||
|
||
-------------- | ||
--[ Footer ]-- | ||
-------------- | ||
|
||
|
||
hcFooter :: String | ||
hcFooter = [s|Discussion: | ||
Performs various health checks. Good for attaching to bug reports.|] | ||
|
||
|
||
|
||
|
||
--------------------------- | ||
--[ Effect interpreters ]-- | ||
--------------------------- | ||
|
||
|
||
type HCEffects = '[ DigestError | ||
, ContentLengthError | ||
, GPGError | ||
, DownloadFailed | ||
, NoDownload | ||
] | ||
|
||
|
||
|
||
runHC :: MonadUnliftIO m | ||
=> (ReaderT AppState m (VEither HCEffects a) -> m (VEither HCEffects a)) | ||
-> Excepts HCEffects (ResourceT (ReaderT AppState m)) a | ||
-> m (VEither HCEffects a) | ||
runHC runAppState = | ||
runAppState | ||
. runResourceT | ||
. runE | ||
@HCEffects | ||
|
||
|
||
|
||
------------------ | ||
--[ Entrypoint ]-- | ||
------------------ | ||
|
||
|
||
|
||
hc :: ( Monad m | ||
, MonadMask m | ||
, MonadUnliftIO m | ||
, MonadFail m | ||
) | ||
=> HealtCheckOptions | ||
-> (forall a. ReaderT AppState m (VEither HCEffects a) -> m (VEither HCEffects a)) | ||
-> (ReaderT LeanAppState m () -> m ()) | ||
-> m ExitCode | ||
hc HealtCheckOptions{..} runAppState runLogger = runHC runAppState (do | ||
runHealthCheck hcOffline | ||
) >>= \case | ||
VRight _ -> do | ||
pure ExitSuccess | ||
VLeft e -> do | ||
runLogger $ logError $ T.pack $ prettyHFError e | ||
pure $ ExitFailure 27 | ||
|
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,63 @@ | ||
{-# LANGUAGE CPP #-} | ||
{-# LANGUAGE DataKinds #-} | ||
{-# LANGUAGE FlexibleContexts #-} | ||
{-# LANGUAGE FlexibleInstances #-} | ||
{-# LANGUAGE MultiParamTypeClasses #-} | ||
|
||
{-| | ||
Module : GHCup.HealthCheck | ||
Description : HealthCheck for GHCup | ||
License : LGPL-3.0 | ||
Stability : experimental | ||
Portability : portable | ||
-} | ||
module GHCup.HealthCheck where | ||
|
||
import GHCup.Download | ||
import GHCup.Errors | ||
import GHCup.Types | ||
import GHCup.Types.JSON ( ) | ||
import GHCup.Types.Optics | ||
import GHCup.Utils | ||
import GHCup.Prelude.Logger | ||
import GHCup.Version | ||
|
||
import Conduit (sourceToList) | ||
import Control.Applicative | ||
import Control.Exception.Safe | ||
import Control.Monad | ||
#if !MIN_VERSION_base(4,13,0) | ||
import Control.Monad.Fail ( MonadFail ) | ||
#endif | ||
import Control.Monad.Reader | ||
import Control.Monad.Trans.Resource | ||
hiding ( throwM ) | ||
import Data.ByteString ( ByteString ) | ||
import Data.Either | ||
import Data.List | ||
import Data.Maybe | ||
import Data.Versions hiding ( patch ) | ||
import GHC.IO.Exception | ||
import Haskus.Utils.Variant.Excepts | ||
import Optics | ||
|
||
runHealthCheck :: ( MonadReader env m | ||
, HasDirs env | ||
, HasLog env | ||
, MonadIO m | ||
, MonadMask m | ||
, MonadFail m | ||
, MonadUnliftIO m | ||
) | ||
=> Bool | ||
-> Excepts | ||
'[ DigestError | ||
, ContentLengthError | ||
, GPGError | ||
, DownloadFailed | ||
, NoDownload | ||
] | ||
m () | ||
runHealthCheck offline = do | ||
pure () | ||
|