Compare commits
21 Commits
| Author | SHA1 | Date | |
|---|---|---|---|
|
30d9eb5634
|
|||
|
9fe7af3335
|
|||
|
bedfb3d114
|
|||
|
c19dd5ee8b
|
|||
|
6ae3bfe395
|
|||
|
4f82e80dad
|
|||
|
8e8198546f
|
|||
|
9497e310ca
|
|||
|
02135bdbae
|
|||
|
041a341879
|
|||
|
15dd810d67
|
|||
|
7982f3aec0
|
|||
|
2fb07201c7
|
|||
|
b5ca01dc4f
|
|||
|
fa523d590e
|
|||
|
523f2f57e1
|
|||
|
d662682fb5
|
|||
|
ff2b06a5e8
|
|||
|
aece305003
|
|||
|
ef8da9bcec
|
|||
|
3cd55beab1
|
@@ -86,7 +86,7 @@ variables:
|
|||||||
|
|
||||||
.freebsd12:
|
.freebsd12:
|
||||||
tags:
|
tags:
|
||||||
- x86_64-freebsd
|
- x86_64-freebsd12
|
||||||
variables:
|
variables:
|
||||||
OS: "FREEBSD"
|
OS: "FREEBSD"
|
||||||
ARCH: "64"
|
ARCH: "64"
|
||||||
|
|||||||
@@ -11,21 +11,23 @@
|
|||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import GHCup.Types
|
import GHCup.Types
|
||||||
import GHCup.Types.Optics
|
|
||||||
import GHCup.Errors
|
import GHCup.Errors
|
||||||
import GHCup.Platform
|
import GHCup.Platform
|
||||||
import GHCup.Utils.Dirs
|
import GHCup.Utils.Dirs
|
||||||
|
import GHCup.Utils.Logger
|
||||||
import GHCup.Types.JSON ( )
|
import GHCup.Types.JSON ( )
|
||||||
|
|
||||||
import Control.Monad.Trans.Reader ( runReaderT )
|
import Control.Monad.Trans.Reader ( runReaderT )
|
||||||
import Control.Monad.IO.Class
|
import Control.Monad.IO.Class
|
||||||
import Data.Char ( toLower )
|
import Data.Char ( toLower )
|
||||||
|
import Data.Maybe
|
||||||
#if !MIN_VERSION_base(4,13,0)
|
#if !MIN_VERSION_base(4,13,0)
|
||||||
import Data.Semigroup ( (<>) )
|
import Data.Semigroup ( (<>) )
|
||||||
#endif
|
#endif
|
||||||
import Options.Applicative hiding ( style )
|
import Options.Applicative hiding ( style )
|
||||||
import Haskus.Utils.Variant.Excepts
|
import Haskus.Utils.Variant.Excepts
|
||||||
import System.Console.Pretty
|
import System.Console.Pretty
|
||||||
|
import System.Environment
|
||||||
import System.Exit
|
import System.Exit
|
||||||
import System.IO ( stderr )
|
import System.IO ( stderr )
|
||||||
import Text.Regex.Posix
|
import Text.Regex.Posix
|
||||||
@@ -114,12 +116,14 @@ com = subparser
|
|||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
let loggerConfig = LoggerConfig { lcPrintDebug = True
|
no_color <- isJust <$> lookupEnv "NO_COLOR"
|
||||||
, colorOutter = T.hPutStr stderr
|
let loggerConfig = LoggerConfig { lcPrintDebug = True
|
||||||
, rawOutter = \_ -> pure ()
|
, consoleOutter = T.hPutStr stderr
|
||||||
|
, fileOutter = \_ -> pure ()
|
||||||
|
, fancyColors = not no_color
|
||||||
}
|
}
|
||||||
dirs <- liftIO getAllDirs
|
dirs <- liftIO getAllDirs
|
||||||
let leanAppstate = LeanAppState (Settings True False Never Curl True GHCupURL False GPGNone) dirs defaultKeyBindings loggerConfig
|
let leanAppstate = LeanAppState (Settings True False Never Curl True GHCupURL False GPGNone False) dirs defaultKeyBindings loggerConfig
|
||||||
|
|
||||||
pfreq <- (
|
pfreq <- (
|
||||||
flip runReaderT leanAppstate . runE @'[NoCompatiblePlatform, NoCompatibleArch, DistroNotFound] $ platformRequest
|
flip runReaderT leanAppstate . runE @'[NoCompatiblePlatform, NoCompatibleArch, DistroNotFound] $ platformRequest
|
||||||
@@ -129,7 +133,7 @@ main = do
|
|||||||
flip runReaderT leanAppstate $ logError $ T.pack $ prettyShow e
|
flip runReaderT leanAppstate $ logError $ T.pack $ prettyShow e
|
||||||
liftIO $ exitWith (ExitFailure 2)
|
liftIO $ exitWith (ExitFailure 2)
|
||||||
|
|
||||||
let appstate = AppState (Settings True False Never Curl True GHCupURL False GPGNone) dirs defaultKeyBindings (GHCupInfo mempty mempty mempty) pfreq loggerConfig
|
let appstate = AppState (Settings True False Never Curl True GHCupURL False GPGNone False) dirs defaultKeyBindings (GHCupInfo mempty mempty mempty) pfreq loggerConfig
|
||||||
|
|
||||||
_ <- customExecParser (prefs showHelpOnError) (info (opts <**> helper) idm)
|
_ <- customExecParser (prefs showHelpOnError) (info (opts <**> helper) idm)
|
||||||
>>= \Options {..} -> case optCommand of
|
>>= \Options {..} -> case optCommand of
|
||||||
|
|||||||
@@ -15,6 +15,7 @@ import GHCup.Errors
|
|||||||
import GHCup.Types
|
import GHCup.Types
|
||||||
import GHCup.Types.Optics
|
import GHCup.Types.Optics
|
||||||
import GHCup.Utils
|
import GHCup.Utils
|
||||||
|
import GHCup.Utils.Logger
|
||||||
import GHCup.Utils.Version.QQ
|
import GHCup.Utils.Version.QQ
|
||||||
|
|
||||||
import Codec.Archive
|
import Codec.Archive
|
||||||
|
|||||||
@@ -13,9 +13,9 @@ module BrickMain where
|
|||||||
import GHCup
|
import GHCup
|
||||||
import GHCup.Download
|
import GHCup.Download
|
||||||
import GHCup.Errors
|
import GHCup.Errors
|
||||||
import GHCup.Types.Optics hiding ( getGHCupInfo )
|
|
||||||
import GHCup.Types hiding ( LeanAppState(..) )
|
import GHCup.Types hiding ( LeanAppState(..) )
|
||||||
import GHCup.Utils
|
import GHCup.Utils
|
||||||
|
import GHCup.Utils.Logger
|
||||||
import GHCup.Utils.Prelude ( decUTF8Safe )
|
import GHCup.Utils.Prelude ( decUTF8Safe )
|
||||||
import GHCup.Utils.File
|
import GHCup.Utils.File
|
||||||
|
|
||||||
@@ -43,7 +43,6 @@ import Data.Vector ( Vector
|
|||||||
import Data.Versions hiding ( str )
|
import Data.Versions hiding ( str )
|
||||||
import Haskus.Utils.Variant.Excepts
|
import Haskus.Utils.Variant.Excepts
|
||||||
import Prelude hiding ( appendFile )
|
import Prelude hiding ( appendFile )
|
||||||
import System.Environment
|
|
||||||
import System.Exit
|
import System.Exit
|
||||||
import System.IO.Unsafe
|
import System.IO.Unsafe
|
||||||
import Text.PrettyPrint.HughesPJClass ( prettyShow )
|
import Text.PrettyPrint.HughesPJClass ( prettyShow )
|
||||||
@@ -537,9 +536,10 @@ settings' :: IORef AppState
|
|||||||
{-# NOINLINE settings' #-}
|
{-# NOINLINE settings' #-}
|
||||||
settings' = unsafePerformIO $ do
|
settings' = unsafePerformIO $ do
|
||||||
dirs <- getAllDirs
|
dirs <- getAllDirs
|
||||||
let loggerConfig = LoggerConfig { lcPrintDebug = False
|
let loggerConfig = LoggerConfig { lcPrintDebug = False
|
||||||
, colorOutter = \_ -> pure ()
|
, consoleOutter = \_ -> pure ()
|
||||||
, rawOutter = \_ -> pure ()
|
, fileOutter = \_ -> pure ()
|
||||||
|
, fancyColors = True
|
||||||
}
|
}
|
||||||
newIORef $ AppState (Settings { cache = True
|
newIORef $ AppState (Settings { cache = True
|
||||||
, noVerify = False
|
, noVerify = False
|
||||||
@@ -549,6 +549,7 @@ settings' = unsafePerformIO $ do
|
|||||||
, urlSource = GHCupURL
|
, urlSource = GHCupURL
|
||||||
, noNetwork = False
|
, noNetwork = False
|
||||||
, gpgSetting = GPGNone
|
, gpgSetting = GPGNone
|
||||||
|
, noColor = False
|
||||||
, ..
|
, ..
|
||||||
})
|
})
|
||||||
dirs
|
dirs
|
||||||
@@ -564,13 +565,11 @@ brickMain :: AppState
|
|||||||
brickMain s = do
|
brickMain s = do
|
||||||
writeIORef settings' s
|
writeIORef settings' s
|
||||||
|
|
||||||
no_color <- isJust <$> lookupEnv "NO_COLOR"
|
|
||||||
|
|
||||||
eAppData <- getAppData (Just $ ghcupInfo s)
|
eAppData <- getAppData (Just $ ghcupInfo s)
|
||||||
case eAppData of
|
case eAppData of
|
||||||
Right ad ->
|
Right ad ->
|
||||||
defaultMain
|
defaultMain
|
||||||
(app (defaultAttributes no_color) (dimAttributes no_color))
|
(app (defaultAttributes (noColor $ settings s)) (dimAttributes (noColor $ settings s)))
|
||||||
(BrickState ad
|
(BrickState ad
|
||||||
defaultAppSettings
|
defaultAppSettings
|
||||||
(constructList ad defaultAppSettings Nothing)
|
(constructList ad defaultAppSettings Nothing)
|
||||||
|
|||||||
@@ -49,7 +49,6 @@ import Data.Char
|
|||||||
import Data.Either
|
import Data.Either
|
||||||
import Data.Functor
|
import Data.Functor
|
||||||
import Data.List ( intercalate, nub, sort, sortBy )
|
import Data.List ( intercalate, nub, sort, sortBy )
|
||||||
import Data.List.NonEmpty (NonEmpty ((:|)))
|
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Text ( Text )
|
import Data.Text ( Text )
|
||||||
import Data.Versions hiding ( str )
|
import Data.Versions hiding ( str )
|
||||||
@@ -118,6 +117,7 @@ data Command
|
|||||||
| Interactive
|
| Interactive
|
||||||
#endif
|
#endif
|
||||||
| Prefetch PrefetchCommand
|
| Prefetch PrefetchCommand
|
||||||
|
| GC GCOptions
|
||||||
|
|
||||||
data ToolVersion = ToolVersion GHCTargetVersion -- target is ignored for cabal
|
data ToolVersion = ToolVersion GHCTargetVersion -- target is ignored for cabal
|
||||||
| ToolTag Tag
|
| ToolTag Tag
|
||||||
@@ -146,6 +146,15 @@ data InstallOptions = InstallOptions
|
|||||||
, forceInstall :: Bool
|
, forceInstall :: Bool
|
||||||
}
|
}
|
||||||
|
|
||||||
|
data GCOptions = GCOptions
|
||||||
|
{ gcOldGHC :: Bool
|
||||||
|
, gcProfilingLibs :: Bool
|
||||||
|
, gcShareDir :: Bool
|
||||||
|
, gcHLSNoGHC :: Bool
|
||||||
|
, gcCache :: Bool
|
||||||
|
, gcTmp :: Bool
|
||||||
|
}
|
||||||
|
|
||||||
data SetCommand = SetGHC SetOptions
|
data SetCommand = SetGHC SetOptions
|
||||||
| SetCabal SetOptions
|
| SetCabal SetOptions
|
||||||
| SetHLS SetOptions
|
| SetHLS SetOptions
|
||||||
@@ -439,6 +448,16 @@ com =
|
|||||||
(progDesc "Prefetch assets"
|
(progDesc "Prefetch assets"
|
||||||
<> footerDoc ( Just $ text prefetchFooter ))
|
<> footerDoc ( Just $ text prefetchFooter ))
|
||||||
)
|
)
|
||||||
|
<> command
|
||||||
|
"gc"
|
||||||
|
(info
|
||||||
|
( (GC
|
||||||
|
<$> gcP
|
||||||
|
) <**> helper
|
||||||
|
)
|
||||||
|
(progDesc "Garbage collection"
|
||||||
|
<> footerDoc ( Just $ text gcFooter ))
|
||||||
|
)
|
||||||
<> commandGroup "Main commands:"
|
<> commandGroup "Main commands:"
|
||||||
)
|
)
|
||||||
<|> subparser
|
<|> subparser
|
||||||
@@ -485,6 +504,7 @@ com =
|
|||||||
(info (pure Nuke <**> helper)
|
(info (pure Nuke <**> helper)
|
||||||
(progDesc "Completely remove ghcup from your system"))
|
(progDesc "Completely remove ghcup from your system"))
|
||||||
<> commandGroup "Nuclear Commands:"
|
<> commandGroup "Nuclear Commands:"
|
||||||
|
<> hidden
|
||||||
)
|
)
|
||||||
|
|
||||||
where
|
where
|
||||||
@@ -543,6 +563,10 @@ Examples:
|
|||||||
ghcup prefetch ghc 8.10.5
|
ghcup prefetch ghc 8.10.5
|
||||||
ghcup --offline install ghc 8.10.5|]
|
ghcup --offline install ghc 8.10.5|]
|
||||||
|
|
||||||
|
gcFooter :: String
|
||||||
|
gcFooter = [s|Discussion:
|
||||||
|
Performs garbage collection. If no switches are specified, does nothing.|]
|
||||||
|
|
||||||
configFooter :: String
|
configFooter :: String
|
||||||
configFooter = [s|Examples:
|
configFooter = [s|Examples:
|
||||||
|
|
||||||
@@ -824,7 +848,7 @@ listOpts =
|
|||||||
<$> optional
|
<$> optional
|
||||||
(option
|
(option
|
||||||
(eitherReader toolParser)
|
(eitherReader toolParser)
|
||||||
(short 't' <> long "tool" <> metavar "<ghc|cabal>" <> help
|
(short 't' <> long "tool" <> metavar "<ghc|cabal|hls|stack>" <> help
|
||||||
"Tool to list versions for. Default is all"
|
"Tool to list versions for. Default is all"
|
||||||
)
|
)
|
||||||
)
|
)
|
||||||
@@ -833,8 +857,8 @@ listOpts =
|
|||||||
(eitherReader criteriaParser)
|
(eitherReader criteriaParser)
|
||||||
( short 'c'
|
( short 'c'
|
||||||
<> long "show-criteria"
|
<> long "show-criteria"
|
||||||
<> metavar "<installed|set>"
|
<> metavar "<installed|set|available>"
|
||||||
<> help "Show only installed or set tool versions"
|
<> help "Show only installed/set/available tool versions"
|
||||||
)
|
)
|
||||||
)
|
)
|
||||||
<*> switch
|
<*> switch
|
||||||
@@ -1123,6 +1147,28 @@ prefetchP = subparser
|
|||||||
)
|
)
|
||||||
)
|
)
|
||||||
|
|
||||||
|
gcP :: Parser GCOptions
|
||||||
|
gcP =
|
||||||
|
GCOptions
|
||||||
|
<$>
|
||||||
|
switch
|
||||||
|
(short 'o' <> long "ghc-old" <> help "Remove GHC versions marked as 'old'")
|
||||||
|
<*>
|
||||||
|
switch
|
||||||
|
(short 'p' <> long "profiling-libs" <> help "Remove profiling libs of GHC versions")
|
||||||
|
<*>
|
||||||
|
switch
|
||||||
|
(short 's' <> long "share-dir" <> help "Remove GHC share directories (documentation)")
|
||||||
|
<*>
|
||||||
|
switch
|
||||||
|
(short 'h' <> long "hls-no-ghc" <> help "Remove HLS versions that don't have a corresponding installed GHC version")
|
||||||
|
<*>
|
||||||
|
switch
|
||||||
|
(short 'c' <> long "cache" <> help "GC the GHCup cache")
|
||||||
|
<*>
|
||||||
|
switch
|
||||||
|
(short 't' <> long "tmpdirs" <> help "Remove tmpdir leftovers")
|
||||||
|
|
||||||
|
|
||||||
ghcCompileOpts :: Parser GHCCompileOptions
|
ghcCompileOpts :: Parser GHCCompileOptions
|
||||||
ghcCompileOpts =
|
ghcCompileOpts =
|
||||||
@@ -1338,12 +1384,13 @@ tagCompleter :: Tool -> [String] -> Completer
|
|||||||
tagCompleter tool add = listIOCompleter $ do
|
tagCompleter tool add = listIOCompleter $ do
|
||||||
dirs' <- liftIO getAllDirs
|
dirs' <- liftIO getAllDirs
|
||||||
let loggerConfig = LoggerConfig
|
let loggerConfig = LoggerConfig
|
||||||
{ lcPrintDebug = False
|
{ lcPrintDebug = False
|
||||||
, colorOutter = mempty
|
, consoleOutter = mempty
|
||||||
, rawOutter = mempty
|
, fileOutter = mempty
|
||||||
|
, fancyColors = False
|
||||||
}
|
}
|
||||||
let appState = LeanAppState
|
let appState = LeanAppState
|
||||||
(Settings True False Never Curl False GHCupURL True GPGNone)
|
(Settings True False Never Curl False GHCupURL True GPGNone False)
|
||||||
dirs'
|
dirs'
|
||||||
defaultKeyBindings
|
defaultKeyBindings
|
||||||
loggerConfig
|
loggerConfig
|
||||||
@@ -1364,11 +1411,12 @@ versionCompleter :: Maybe ListCriteria -> Tool -> Completer
|
|||||||
versionCompleter criteria tool = listIOCompleter $ do
|
versionCompleter criteria tool = listIOCompleter $ do
|
||||||
dirs' <- liftIO getAllDirs
|
dirs' <- liftIO getAllDirs
|
||||||
let loggerConfig = LoggerConfig
|
let loggerConfig = LoggerConfig
|
||||||
{ lcPrintDebug = False
|
{ lcPrintDebug = False
|
||||||
, colorOutter = mempty
|
, consoleOutter = mempty
|
||||||
, rawOutter = mempty
|
, fileOutter = mempty
|
||||||
|
, fancyColors = False
|
||||||
}
|
}
|
||||||
let settings = Settings True False Never Curl False GHCupURL True GPGNone
|
let settings = Settings True False Never Curl False GHCupURL True GPGNone False
|
||||||
let leanAppState = LeanAppState
|
let leanAppState = LeanAppState
|
||||||
settings
|
settings
|
||||||
dirs'
|
dirs'
|
||||||
@@ -1427,6 +1475,8 @@ toolVersionEither s' =
|
|||||||
toolParser :: String -> Either String Tool
|
toolParser :: String -> Either String Tool
|
||||||
toolParser s' | t == T.pack "ghc" = Right GHC
|
toolParser s' | t == T.pack "ghc" = Right GHC
|
||||||
| t == T.pack "cabal" = Right Cabal
|
| t == T.pack "cabal" = Right Cabal
|
||||||
|
| t == T.pack "hls" = Right HLS
|
||||||
|
| t == T.pack "stack" = Right Stack
|
||||||
| otherwise = Left ("Unknown tool: " <> s')
|
| otherwise = Left ("Unknown tool: " <> s')
|
||||||
where t = T.toLower (T.pack s')
|
where t = T.toLower (T.pack s')
|
||||||
|
|
||||||
@@ -1434,6 +1484,7 @@ toolParser s' | t == T.pack "ghc" = Right GHC
|
|||||||
criteriaParser :: String -> Either String ListCriteria
|
criteriaParser :: String -> Either String ListCriteria
|
||||||
criteriaParser s' | t == T.pack "installed" = Right ListInstalled
|
criteriaParser s' | t == T.pack "installed" = Right ListInstalled
|
||||||
| t == T.pack "set" = Right ListSet
|
| t == T.pack "set" = Right ListSet
|
||||||
|
| t == T.pack "available" = Right ListAvailable
|
||||||
| otherwise = Left ("Unknown criteria: " <> s')
|
| otherwise = Left ("Unknown criteria: " <> s')
|
||||||
where t = T.toLower (T.pack s')
|
where t = T.toLower (T.pack s')
|
||||||
|
|
||||||
@@ -1527,6 +1578,7 @@ absolutePathParser f = case isValid f && isAbsolute f of
|
|||||||
|
|
||||||
toSettings :: Options -> IO (Settings, KeyBindings)
|
toSettings :: Options -> IO (Settings, KeyBindings)
|
||||||
toSettings options = do
|
toSettings options = do
|
||||||
|
noColor <- isJust <$> lookupEnv "NO_COLOR"
|
||||||
userConf <- runE @'[ JSONError ] ghcupConfigFile >>= \case
|
userConf <- runE @'[ JSONError ] ghcupConfigFile >>= \case
|
||||||
VRight r -> pure r
|
VRight r -> pure r
|
||||||
VLeft (V (JSONDecodeError e)) -> do
|
VLeft (V (JSONDecodeError e)) -> do
|
||||||
@@ -1534,10 +1586,10 @@ toSettings options = do
|
|||||||
pure defaultUserSettings
|
pure defaultUserSettings
|
||||||
_ -> do
|
_ -> do
|
||||||
die "Unexpected error!"
|
die "Unexpected error!"
|
||||||
pure $ mergeConf options userConf
|
pure $ mergeConf options userConf noColor
|
||||||
where
|
where
|
||||||
mergeConf :: Options -> UserSettings -> (Settings, KeyBindings)
|
mergeConf :: Options -> UserSettings -> Bool -> (Settings, KeyBindings)
|
||||||
mergeConf Options{..} UserSettings{..} =
|
mergeConf Options{..} UserSettings{..} noColor =
|
||||||
let cache = fromMaybe (fromMaybe False uCache) optCache
|
let cache = fromMaybe (fromMaybe False uCache) optCache
|
||||||
noVerify = fromMaybe (fromMaybe False uNoVerify) optNoVerify
|
noVerify = fromMaybe (fromMaybe False uNoVerify) optNoVerify
|
||||||
verbose = fromMaybe (fromMaybe False uVerbose) optVerbose
|
verbose = fromMaybe (fromMaybe False uVerbose) optVerbose
|
||||||
@@ -1583,7 +1635,7 @@ updateSettings config settings = do
|
|||||||
urlSource' = fromMaybe urlSource uUrlSource
|
urlSource' = fromMaybe urlSource uUrlSource
|
||||||
noNetwork' = fromMaybe noNetwork uNoNetwork
|
noNetwork' = fromMaybe noNetwork uNoNetwork
|
||||||
gpgSetting' = fromMaybe gpgSetting uGPGSetting
|
gpgSetting' = fromMaybe gpgSetting uGPGSetting
|
||||||
in Settings cache' noVerify' keepDirs' downloader' verbose' urlSource' noNetwork' gpgSetting'
|
in Settings cache' noVerify' keepDirs' downloader' verbose' urlSource' noNetwork' gpgSetting' noColor
|
||||||
|
|
||||||
upgradeOptsP :: Parser UpgradeOpts
|
upgradeOptsP :: Parser UpgradeOpts
|
||||||
upgradeOptsP =
|
upgradeOptsP =
|
||||||
@@ -1608,7 +1660,7 @@ describe_result = $( LitE . StringL <$>
|
|||||||
runIO (do
|
runIO (do
|
||||||
CapturedProcess{..} <- do
|
CapturedProcess{..} <- do
|
||||||
dirs <- liftIO getAllDirs
|
dirs <- liftIO getAllDirs
|
||||||
let settings = AppState (Settings True False Never Curl False GHCupURL False GPGNone)
|
let settings = AppState (Settings True False Never Curl False GHCupURL False GPGNone False)
|
||||||
dirs
|
dirs
|
||||||
defaultKeyBindings
|
defaultKeyBindings
|
||||||
flip runReaderT settings $ executeOut "git" ["describe"] Nothing
|
flip runReaderT settings $ executeOut "git" ["describe"] Nothing
|
||||||
@@ -1688,17 +1740,19 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
|
|||||||
|
|
||||||
-- logger interpreter
|
-- logger interpreter
|
||||||
logfile <- flip runReaderT dirs initGHCupFileLogging
|
logfile <- flip runReaderT dirs initGHCupFileLogging
|
||||||
|
no_color <- isJust <$> lookupEnv "NO_COLOR"
|
||||||
let loggerConfig = LoggerConfig
|
let loggerConfig = LoggerConfig
|
||||||
{ lcPrintDebug = verbose settings
|
{ lcPrintDebug = verbose settings
|
||||||
, colorOutter = T.hPutStr stderr
|
, consoleOutter = T.hPutStr stderr
|
||||||
, rawOutter =
|
, fileOutter =
|
||||||
case optCommand of
|
case optCommand of
|
||||||
Nuke -> \_ -> pure ()
|
Nuke -> \_ -> pure ()
|
||||||
_ -> T.appendFile logfile
|
_ -> T.appendFile logfile
|
||||||
|
, fancyColors = not no_color
|
||||||
}
|
}
|
||||||
let leanAppstate = LeanAppState settings dirs keybindings loggerConfig
|
let leanAppstate = LeanAppState settings dirs keybindings loggerConfig
|
||||||
let runLogger = flip runReaderT leanAppstate
|
let runLogger = flip runReaderT leanAppstate
|
||||||
let siletRunLogger = flip runReaderT (leanAppstate { loggerConfig = loggerConfig { colorOutter = \_ -> pure () } } :: LeanAppState)
|
let siletRunLogger = flip runReaderT (leanAppstate { loggerConfig = loggerConfig { consoleOutter = \_ -> pure () } } :: LeanAppState)
|
||||||
|
|
||||||
|
|
||||||
-------------------------
|
-------------------------
|
||||||
@@ -1972,6 +2026,13 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
|
|||||||
, FileDoesNotExistError
|
, FileDoesNotExistError
|
||||||
]
|
]
|
||||||
|
|
||||||
|
let runGC =
|
||||||
|
runAppState
|
||||||
|
. runResourceT
|
||||||
|
. runE
|
||||||
|
@'[ NotInstalled
|
||||||
|
]
|
||||||
|
|
||||||
|
|
||||||
-----------------------
|
-----------------------
|
||||||
-- Command functions --
|
-- Command functions --
|
||||||
@@ -2336,7 +2397,7 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
|
|||||||
List ListOptions {..} ->
|
List ListOptions {..} ->
|
||||||
runListGHC (do
|
runListGHC (do
|
||||||
l <- listVersions loTool lCriteria
|
l <- listVersions loTool lCriteria
|
||||||
liftIO $ printListResult lRawFormat l
|
liftIO $ printListResult no_color lRawFormat l
|
||||||
pure ExitSuccess
|
pure ExitSuccess
|
||||||
)
|
)
|
||||||
|
|
||||||
@@ -2691,6 +2752,20 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
|
|||||||
VLeft e -> do
|
VLeft e -> do
|
||||||
runLogger $ logError $ T.pack $ prettyShow e
|
runLogger $ logError $ T.pack $ prettyShow e
|
||||||
pure $ ExitFailure 15
|
pure $ ExitFailure 15
|
||||||
|
GC GCOptions{..} ->
|
||||||
|
runGC (do
|
||||||
|
when gcOldGHC rmOldGHC
|
||||||
|
lift $ when gcProfilingLibs rmProfilingLibs
|
||||||
|
lift $ when gcShareDir rmShareDir
|
||||||
|
lift $ when gcHLSNoGHC rmHLSNoGHC
|
||||||
|
lift $ when gcCache rmCache
|
||||||
|
lift $ when gcTmp rmTmp
|
||||||
|
) >>= \case
|
||||||
|
VRight _ -> do
|
||||||
|
pure ExitSuccess
|
||||||
|
VLeft e -> do
|
||||||
|
runLogger $ logError $ T.pack $ prettyShow e
|
||||||
|
pure $ ExitFailure 27
|
||||||
|
|
||||||
|
|
||||||
case res of
|
case res of
|
||||||
@@ -2741,13 +2816,15 @@ fromVersion' SetRecommended tool = do
|
|||||||
fromVersion' (SetToolVersion v) tool = do
|
fromVersion' (SetToolVersion v) tool = do
|
||||||
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
||||||
let vi = getVersionInfo (_tvVersion v) tool dls
|
let vi = getVersionInfo (_tvVersion v) tool dls
|
||||||
case pvp $ prettyVer (_tvVersion v) of
|
case pvp $ prettyVer (_tvVersion v) of -- need to be strict here
|
||||||
Left _ -> pure (v, vi)
|
Left _ -> pure (v, vi)
|
||||||
Right (PVP (major' :|[minor'])) ->
|
Right pvpIn ->
|
||||||
case getLatestGHCFor (fromIntegral major') (fromIntegral minor') dls of
|
lift (getLatestToolFor tool pvpIn dls) >>= \case
|
||||||
Just (v', vi') -> pure (GHCTargetVersion (_tvTarget v) v', Just vi')
|
Just (pvp_, vi') -> do
|
||||||
|
v' <- lift $ pvpToVersion pvp_
|
||||||
|
when (v' /= (_tvVersion v)) $ lift $ logWarn ("Assuming you meant version " <> prettyVer v')
|
||||||
|
pure (GHCTargetVersion (_tvTarget v) v', Just vi')
|
||||||
Nothing -> pure (v, vi)
|
Nothing -> pure (v, vi)
|
||||||
Right _ -> pure (v, vi)
|
|
||||||
fromVersion' (SetToolTag Latest) tool = do
|
fromVersion' (SetToolTag Latest) tool = do
|
||||||
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
||||||
(\(x, y) -> (mkTVer x, Just y)) <$> getLatest dls tool ?? TagNotFound Latest tool
|
(\(x, y) -> (mkTVer x, Just y)) <$> getLatest dls tool ?? TagNotFound Latest tool
|
||||||
@@ -2807,9 +2884,8 @@ fromVersion' (SetToolTag t') tool =
|
|||||||
throwE $ TagNotFound t' tool
|
throwE $ TagNotFound t' tool
|
||||||
|
|
||||||
|
|
||||||
printListResult :: Bool -> [ListResult] -> IO ()
|
printListResult :: Bool -> Bool -> [ListResult] -> IO ()
|
||||||
printListResult raw lr = do
|
printListResult no_color raw lr = do
|
||||||
no_color <- isJust <$> lookupEnv "NO_COLOR"
|
|
||||||
|
|
||||||
let
|
let
|
||||||
color | raw || no_color = flip const
|
color | raw || no_color = flip const
|
||||||
|
|||||||
@@ -8,11 +8,6 @@ package ghcup
|
|||||||
tests: True
|
tests: True
|
||||||
flags: +tui
|
flags: +tui
|
||||||
|
|
||||||
source-repository-package
|
|
||||||
type: git
|
|
||||||
location: https://github.com/bgamari/terminal-size
|
|
||||||
tag: 34ea816bd63f75f800eedac12c6908c6f3736036
|
|
||||||
|
|
||||||
source-repository-package
|
source-repository-package
|
||||||
type: git
|
type: git
|
||||||
location: https://github.com/hasufell/libarchive
|
location: https://github.com/hasufell/libarchive
|
||||||
|
|||||||
@@ -2269,7 +2269,7 @@ ghcupDownloads:
|
|||||||
dlUri: https://downloads.haskell.org/~ghcup/unofficial-bindists/cabal/3.6.0.0/cabal-install-3.6.0.0-armv7-linux.tar.xz
|
dlUri: https://downloads.haskell.org/~ghcup/unofficial-bindists/cabal/3.6.0.0/cabal-install-3.6.0.0-armv7-linux.tar.xz
|
||||||
dlHash: 11b5ca042a8bf45971224f2127a3e9d6b803f09210042ca80a254bea06f01a2e
|
dlHash: 11b5ca042a8bf45971224f2127a3e9d6b803f09210042ca80a254bea06f01a2e
|
||||||
GHCup:
|
GHCup:
|
||||||
0.1.16.2:
|
0.1.17:
|
||||||
viTags:
|
viTags:
|
||||||
- Recommended
|
- Recommended
|
||||||
- Latest
|
- Latest
|
||||||
@@ -2279,43 +2279,43 @@ ghcupDownloads:
|
|||||||
A_64:
|
A_64:
|
||||||
Linux_UnknownLinux:
|
Linux_UnknownLinux:
|
||||||
unknown_versioning: &ghcup-64
|
unknown_versioning: &ghcup-64
|
||||||
dlUri: https://downloads.haskell.org/~ghcup/0.1.16.2/x86_64-linux-ghcup-0.1.16.2
|
dlUri: https://downloads.haskell.org/~ghcup/0.1.17/x86_64-linux-ghcup-0.1.17
|
||||||
dlHash: d5e43b95ce1d42263376e414f7eb7c5dd440271c7c6cd9bad446fdeff3823893
|
dlHash: 1eaa33af4180f97edf02822d6d711ce618d9828fe9ebbf042d198fe6c1c9d153
|
||||||
Darwin:
|
Darwin:
|
||||||
unknown_versioning:
|
unknown_versioning:
|
||||||
dlUri: https://downloads.haskell.org/~ghcup/0.1.16.2/x86_64-apple-darwin-ghcup-0.1.16.2
|
dlUri: https://downloads.haskell.org/~ghcup/0.1.17/x86_64-apple-darwin-ghcup-0.1.17
|
||||||
dlHash: a334620ccce7705211b2142882dde544003e6030af4b91a44c890542a90f879f
|
dlHash: a3d4ed12f8631c0537d8d9531cc5518bc6f90edcee3326e5d4e0efb72c8dfc6f
|
||||||
FreeBSD:
|
FreeBSD:
|
||||||
unknown_versioning:
|
unknown_versioning:
|
||||||
dlUri: https://downloads.haskell.org/~ghcup/0.1.16.2/x86_64-portbld-freebsd-ghcup-0.1.16.2
|
dlUri: https://downloads.haskell.org/~ghcup/0.1.17/x86_64-portbld-freebsd-ghcup-0.1.17
|
||||||
dlHash: 92359592a5694375e53b22628920086bf4bbf0faff5be018a0ed3e745a6426a9
|
dlHash: 83012de837773f3aa26182c607c2da85ee6ff3b0092becb78907700f407a27fb
|
||||||
Windows:
|
Windows:
|
||||||
unknown_versioning:
|
unknown_versioning:
|
||||||
dlUri: https://downloads.haskell.org/~ghcup/0.1.16.2/x86_64-mingw64-ghcup-0.1.16.2.exe
|
dlUri: https://downloads.haskell.org/~ghcup/0.1.17/x86_64-mingw64-ghcup-0.1.17.exe
|
||||||
dlHash: ec78872a84213968c490675127b9aad2285980b747c68207801ae824b98c7948
|
dlHash: 40bda6050c800fa69af51d2e668426ca73b4179214bfeef329b795484991d258
|
||||||
Linux_Alpine:
|
Linux_Alpine:
|
||||||
unknown_versioning: *ghcup-64
|
unknown_versioning: *ghcup-64
|
||||||
A_32:
|
A_32:
|
||||||
Linux_UnknownLinux:
|
Linux_UnknownLinux:
|
||||||
unknown_versioning: &ghcup-32
|
unknown_versioning: &ghcup-32
|
||||||
dlUri: https://downloads.haskell.org/~ghcup/0.1.16.2/i386-linux-ghcup-0.1.16.2
|
dlUri: https://downloads.haskell.org/~ghcup/0.1.17/i386-linux-ghcup-0.1.17
|
||||||
dlHash: 01968ca6decac7b6e8ba6e2c817870d3fa47289a6507e0c1ab563f7b6eec0e38
|
dlHash: d0f887b13a2c7a11477dc54cb90b446ef0ebe1d2a6bfbf60ccd4b37fc5de70cc
|
||||||
Linux_Alpine:
|
Linux_Alpine:
|
||||||
unknown_versioning: *ghcup-32
|
unknown_versioning: *ghcup-32
|
||||||
A_ARM64:
|
A_ARM64:
|
||||||
Linux_UnknownLinux:
|
Linux_UnknownLinux:
|
||||||
unknown_versioning:
|
unknown_versioning:
|
||||||
dlUri: https://downloads.haskell.org/~ghcup/0.1.16.2/aarch64-linux-ghcup-0.1.16.2
|
dlUri: https://downloads.haskell.org/~ghcup/0.1.17/aarch64-linux-ghcup-0.1.17
|
||||||
dlHash: 0bdbfc724e0ddabb266156eea83c2c4e19c6ed79dd06db0c29b7d69df8d9fa8c
|
dlHash: be67cf8800ae305c5ba210b645f4fce8751763f3eac3db399f6efca145b7ab38
|
||||||
Darwin:
|
Darwin:
|
||||||
unknown_versioning:
|
unknown_versioning:
|
||||||
dlUri: https://downloads.haskell.org/~ghcup/0.1.16.2/aarch64-apple-darwin-ghcup-0.1.16.2
|
dlUri: https://downloads.haskell.org/~ghcup/0.1.17/aarch64-apple-darwin-ghcup-0.1.17
|
||||||
dlHash: 8854e991a2ba1350abda59dab96ce50ae7729d1ce99399d67929ef31e90f1da5
|
dlHash: b1be8c55838bd0d972e42b02b71bdf47fbbf67be1456e0de2d7d346620538539
|
||||||
A_ARM:
|
A_ARM:
|
||||||
Linux_UnknownLinux:
|
Linux_UnknownLinux:
|
||||||
unknown_versioning:
|
unknown_versioning:
|
||||||
dlUri: https://downloads.haskell.org/~ghcup/0.1.16.2/armv7-linux-ghcup-0.1.16.2
|
dlUri: https://downloads.haskell.org/~ghcup/0.1.17/armv7-linux-ghcup-0.1.17
|
||||||
dlHash: 983ebb5b584bfa600704216a63f94b40d36a02573834e90ef1042c8472d9ad57
|
dlHash: fe54ded2fafff4f8d82e511229f257f4c3b87b14c796f9b5b0ea35c359c26cb0
|
||||||
HLS:
|
HLS:
|
||||||
1.1.0:
|
1.1.0:
|
||||||
viTags:
|
viTags:
|
||||||
|
|||||||
@@ -1,5 +1,14 @@
|
|||||||
# Revision history for ghcup
|
# Revision history for ghcup
|
||||||
|
|
||||||
|
## 0.1.17.1 -- 2021-09-26
|
||||||
|
|
||||||
|
* Fix `NO_COLOR`
|
||||||
|
* Fix `ghcup list -t` for hls/stack, wrt [#244](https://gitlab.haskell.org/haskell/ghcup-hs/-/issues/244)
|
||||||
|
* Get rid of concurrent-output
|
||||||
|
* Improve cli interface with partial versions (e.g. `ghcup install ghc 8`)
|
||||||
|
* Fix HLS compilation builds
|
||||||
|
* Implement `ghcup gc` (garbage collection) command
|
||||||
|
|
||||||
## 0.1.17 -- 2021-09-20
|
## 0.1.17 -- 2021-09-20
|
||||||
|
|
||||||
* Add `--force` option to install/compile wrt [#210](https://gitlab.haskell.org/haskell/ghcup-hs/-/issues/210) by Arjun Kathuria
|
* Add `--force` option to install/compile wrt [#210](https://gitlab.haskell.org/haskell/ghcup-hs/-/issues/210) by Arjun Kathuria
|
||||||
|
|||||||
49
ghcup.cabal
49
ghcup.cabal
@@ -1,33 +1,33 @@
|
|||||||
cabal-version: 3.0
|
cabal-version: 3.0
|
||||||
name: ghcup
|
name: ghcup
|
||||||
version: 0.1.17
|
version: 0.1.17.1
|
||||||
license: LGPL-3.0-only
|
license: LGPL-3.0-only
|
||||||
license-file: LICENSE
|
license-file: LICENSE
|
||||||
copyright: Julian Ospald 2020
|
copyright: Julian Ospald 2020
|
||||||
maintainer: hasufell@posteo.de
|
maintainer: hasufell@posteo.de
|
||||||
author: Julian Ospald
|
author: Julian Ospald
|
||||||
homepage: https://gitlab.haskell.org/haskell/ghcup-hs
|
homepage: https://gitlab.haskell.org/haskell/ghcup-hs
|
||||||
bug-reports: https://gitlab.haskell.org/haskell/ghcup-hs/issues
|
bug-reports: https://gitlab.haskell.org/haskell/ghcup-hs/issues
|
||||||
synopsis: ghc toolchain installer
|
synopsis: ghc toolchain installer
|
||||||
description:
|
description:
|
||||||
A rewrite of the shell script ghcup, for providing
|
A rewrite of the shell script ghcup, for providing
|
||||||
a more stable user experience and exposing an API.
|
a more stable user experience and exposing an API.
|
||||||
|
|
||||||
category: System
|
category: System
|
||||||
build-type: Simple
|
build-type: Simple
|
||||||
extra-doc-files:
|
extra-doc-files:
|
||||||
README.md
|
|
||||||
docs/CHANGELOG.md
|
|
||||||
docs/HACKING.md
|
|
||||||
docs/RELEASING.md
|
|
||||||
data/config.yaml
|
data/config.yaml
|
||||||
data/metadata/ghcup-0.0.4.yaml
|
data/metadata/ghcup-0.0.4.yaml
|
||||||
data/metadata/ghcup-0.0.5.yaml
|
data/metadata/ghcup-0.0.5.yaml
|
||||||
data/metadata/ghcup-0.0.6.yaml
|
data/metadata/ghcup-0.0.6.yaml
|
||||||
|
docs/CHANGELOG.md
|
||||||
|
docs/HACKING.md
|
||||||
|
docs/RELEASING.md
|
||||||
|
README.md
|
||||||
|
|
||||||
extra-source-files:
|
extra-source-files:
|
||||||
data/build_mk/default
|
|
||||||
data/build_mk/cross
|
data/build_mk/cross
|
||||||
|
data/build_mk/default
|
||||||
|
|
||||||
source-repository head
|
source-repository head
|
||||||
type: git
|
type: git
|
||||||
@@ -102,7 +102,6 @@ library
|
|||||||
, Cabal
|
, Cabal
|
||||||
, case-insensitive ^>=1.2.1.0
|
, case-insensitive ^>=1.2.1.0
|
||||||
, casing ^>=0.1.4.1
|
, casing ^>=0.1.4.1
|
||||||
, concurrent-output ^>=1.10.11
|
|
||||||
, containers ^>=0.6
|
, containers ^>=0.6
|
||||||
, cryptohash-sha256 ^>=0.11.101.0
|
, cryptohash-sha256 ^>=0.11.101.0
|
||||||
, deepseq ^>=1.4.4.0
|
, deepseq ^>=1.4.4.0
|
||||||
@@ -111,6 +110,7 @@ library
|
|||||||
, filepath ^>=1.4.2.1
|
, filepath ^>=1.4.2.1
|
||||||
, haskus-utils-types ^>=1.5
|
, haskus-utils-types ^>=1.5
|
||||||
, haskus-utils-variant >=3.0 && <3.2
|
, haskus-utils-variant >=3.0 && <3.2
|
||||||
|
, HsYAML-aeson ^>=0.2.0.0
|
||||||
, libarchive ^>=3.0.0.0
|
, libarchive ^>=3.0.0.0
|
||||||
, lzma-static ^>=5.2.5.3
|
, lzma-static ^>=5.2.5.3
|
||||||
, megaparsec >=8.0.0 && <9.1
|
, megaparsec >=8.0.0 && <9.1
|
||||||
@@ -136,7 +136,6 @@ library
|
|||||||
, vector ^>=0.12
|
, vector ^>=0.12
|
||||||
, versions >=4.0.1 && <5.1
|
, versions >=4.0.1 && <5.1
|
||||||
, word8 ^>=0.1.3
|
, word8 ^>=0.1.3
|
||||||
, HsYAML-aeson ^>=0.2.0.0
|
|
||||||
, zlib ^>=0.6.2.2
|
, zlib ^>=0.6.2.2
|
||||||
|
|
||||||
if (flag(internal-downloader) && !os(windows))
|
if (flag(internal-downloader) && !os(windows))
|
||||||
@@ -158,7 +157,11 @@ library
|
|||||||
, Win32 ^>=2.10
|
, Win32 ^>=2.10
|
||||||
|
|
||||||
else
|
else
|
||||||
other-modules: GHCup.Utils.File.Posix
|
other-modules:
|
||||||
|
GHCup.Utils.File.Posix
|
||||||
|
System.Console.Terminal.Common
|
||||||
|
System.Console.Terminal.Posix
|
||||||
|
|
||||||
build-depends:
|
build-depends:
|
||||||
, bz2 >=0.5.0.5 && <1.1
|
, bz2 >=0.5.0.5 && <1.1
|
||||||
, unix ^>=2.7
|
, unix ^>=2.7
|
||||||
@@ -198,6 +201,7 @@ executable ghcup
|
|||||||
, filepath ^>=1.4.2.1
|
, filepath ^>=1.4.2.1
|
||||||
, ghcup
|
, ghcup
|
||||||
, haskus-utils-variant >=3.0 && <3.2
|
, haskus-utils-variant >=3.0 && <3.2
|
||||||
|
, HsYAML-aeson ^>=0.2.0.0
|
||||||
, libarchive ^>=3.0.0.0
|
, libarchive ^>=3.0.0.0
|
||||||
, megaparsec >=8.0.0 && <9.1
|
, megaparsec >=8.0.0 && <9.1
|
||||||
, mtl ^>=2.2
|
, mtl ^>=2.2
|
||||||
@@ -212,7 +216,6 @@ executable ghcup
|
|||||||
, uri-bytestring ^>=0.3.2.2
|
, uri-bytestring ^>=0.3.2.2
|
||||||
, utf8-string ^>=1.0
|
, utf8-string ^>=1.0
|
||||||
, versions >=4.0.1 && <5.1
|
, versions >=4.0.1 && <5.1
|
||||||
, HsYAML-aeson ^>=0.2.0.0
|
|
||||||
|
|
||||||
if flag(internal-downloader)
|
if flag(internal-downloader)
|
||||||
cpp-options: -DINTERNAL_DOWNLOADER
|
cpp-options: -DINTERNAL_DOWNLOADER
|
||||||
@@ -260,6 +263,7 @@ executable ghcup-gen
|
|||||||
, filepath ^>=1.4.2.1
|
, filepath ^>=1.4.2.1
|
||||||
, ghcup
|
, ghcup
|
||||||
, haskus-utils-variant >=3.0 && <3.2
|
, haskus-utils-variant >=3.0 && <3.2
|
||||||
|
, HsYAML-aeson ^>=0.2.0.0
|
||||||
, libarchive ^>=3.0.0.0
|
, libarchive ^>=3.0.0.0
|
||||||
, mtl ^>=2.2
|
, mtl ^>=2.2
|
||||||
, optics ^>=0.4
|
, optics ^>=0.4
|
||||||
@@ -272,7 +276,6 @@ executable ghcup-gen
|
|||||||
, text ^>=1.2.4.0
|
, text ^>=1.2.4.0
|
||||||
, transformers ^>=0.5
|
, transformers ^>=0.5
|
||||||
, versions >=4.0.1 && <5.1
|
, versions >=4.0.1 && <5.1
|
||||||
, HsYAML-aeson ^>=0.2.0.0
|
|
||||||
|
|
||||||
test-suite ghcup-test
|
test-suite ghcup-test
|
||||||
type: exitcode-stdio-1.0
|
type: exitcode-stdio-1.0
|
||||||
|
|||||||
193
lib/GHCup.hs
193
lib/GHCup.hs
@@ -34,6 +34,7 @@ import GHCup.Types.JSON ( )
|
|||||||
import GHCup.Types.Optics
|
import GHCup.Types.Optics
|
||||||
import GHCup.Utils
|
import GHCup.Utils
|
||||||
import GHCup.Utils.File
|
import GHCup.Utils.File
|
||||||
|
import GHCup.Utils.Logger
|
||||||
import GHCup.Utils.Prelude
|
import GHCup.Utils.Prelude
|
||||||
import GHCup.Utils.String.QQ
|
import GHCup.Utils.String.QQ
|
||||||
import GHCup.Utils.Version.QQ
|
import GHCup.Utils.Version.QQ
|
||||||
@@ -58,6 +59,7 @@ import Data.ByteString ( ByteString )
|
|||||||
import Data.Either
|
import Data.Either
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
import Data.List.NonEmpty ( NonEmpty((:|)) )
|
||||||
import Data.String ( fromString )
|
import Data.String ( fromString )
|
||||||
import Data.Text ( Text )
|
import Data.Text ( Text )
|
||||||
import Data.Time.Clock
|
import Data.Time.Clock
|
||||||
@@ -81,9 +83,7 @@ import System.Directory hiding ( findFiles )
|
|||||||
import System.Environment
|
import System.Environment
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.IO.Error
|
import System.IO.Error
|
||||||
#if defined(IS_WINDOWS)
|
|
||||||
import System.IO.Temp
|
import System.IO.Temp
|
||||||
#endif
|
|
||||||
import Text.PrettyPrint.HughesPJClass ( prettyShow )
|
import Text.PrettyPrint.HughesPJClass ( prettyShow )
|
||||||
import Text.Regex.Posix
|
import Text.Regex.Posix
|
||||||
|
|
||||||
@@ -510,7 +510,7 @@ installCabalUnpacked path inst mver' forceInstall = do
|
|||||||
unless forceInstall -- Overwrite it when it IS a force install
|
unless forceInstall -- Overwrite it when it IS a force install
|
||||||
(liftE $ throwIfFileAlreadyExists destPath)
|
(liftE $ throwIfFileAlreadyExists destPath)
|
||||||
|
|
||||||
handleIO (throwE . CopyError . show) $ liftIO $ copyFile
|
copyFileE
|
||||||
(path </> cabalFile <> exeExt)
|
(path </> cabalFile <> exeExt)
|
||||||
destPath
|
destPath
|
||||||
lift $ chmod_755 destPath
|
lift $ chmod_755 destPath
|
||||||
@@ -660,7 +660,7 @@ installHLSUnpacked path inst mver' forceInstall = do
|
|||||||
unless forceInstall -- if it is a force install, overwrite it.
|
unless forceInstall -- if it is a force install, overwrite it.
|
||||||
(liftE $ throwIfFileAlreadyExists destPath)
|
(liftE $ throwIfFileAlreadyExists destPath)
|
||||||
|
|
||||||
handleIO (throwE . CopyError . show) $ liftIO $ copyFile
|
copyFileE
|
||||||
srcPath
|
srcPath
|
||||||
destPath
|
destPath
|
||||||
lift $ chmod_755 destPath
|
lift $ chmod_755 destPath
|
||||||
@@ -676,7 +676,7 @@ installHLSUnpacked path inst mver' forceInstall = do
|
|||||||
unless forceInstall
|
unless forceInstall
|
||||||
(liftE $ throwIfFileAlreadyExists destWrapperPath)
|
(liftE $ throwIfFileAlreadyExists destWrapperPath)
|
||||||
|
|
||||||
handleIO (throwE . CopyError . show) $ liftIO $ copyFile
|
copyFileE
|
||||||
srcWrapperPath
|
srcWrapperPath
|
||||||
destWrapperPath
|
destWrapperPath
|
||||||
|
|
||||||
@@ -848,35 +848,37 @@ compileHLS targetHLS ghcs jobs ov isolateDir cabalProject cabalProjectLocal patc
|
|||||||
cp <- case cabalProject of
|
cp <- case cabalProject of
|
||||||
Just cp
|
Just cp
|
||||||
| isAbsolute cp -> do
|
| isAbsolute cp -> do
|
||||||
handleIO (throwE . CopyError . show) $ liftIO $ copyFile cp (workdir </> "cabal.project")
|
copyFileE cp (workdir </> "cabal.project")
|
||||||
pure "cabal.project"
|
pure "cabal.project"
|
||||||
| otherwise -> pure (takeFileName cp)
|
| otherwise -> pure (takeFileName cp)
|
||||||
Nothing -> pure "cabal.project"
|
Nothing -> pure "cabal.project"
|
||||||
forM_ cabalProjectLocal $ \cpl -> handleIO (throwE . CopyError . show) $ liftIO $ copyFile cpl (workdir </> cp <.> "local")
|
forM_ cabalProjectLocal $ \cpl -> copyFileE cpl (workdir </> cp <.> "local")
|
||||||
|
|
||||||
|
let targets = ["exe:haskell-language-server", "exe:haskell-language-server-wrapper"]
|
||||||
|
|
||||||
artifacts <- forM (sort ghcs) $ \ghc -> do
|
artifacts <- forM (sort ghcs) $ \ghc -> do
|
||||||
let ghcInstallDir = installDir </> T.unpack (prettyVer ghc)
|
let ghcInstallDir = installDir </> T.unpack (prettyVer ghc)
|
||||||
liftIO $ createDirRecursive' installDir
|
liftIO $ createDirRecursive' ghcInstallDir
|
||||||
lift $ logInfo $ "Building HLS " <> prettyVer installVer <> " for GHC version " <> prettyVer ghc
|
lift $ logInfo $ "Building HLS " <> prettyVer installVer <> " for GHC version " <> prettyVer ghc
|
||||||
liftE $ lEM @_ @'[ProcessError] $
|
liftE $ lEM @_ @'[ProcessError] $
|
||||||
execLogged "cabal" ( [ "v2-install"
|
execLogged "cabal" ( [ "v2-build"
|
||||||
, "-w"
|
, "-w"
|
||||||
, "ghc-" <> T.unpack (prettyVer ghc)
|
, "ghc-" <> T.unpack (prettyVer ghc)
|
||||||
, "--install-method=copy"
|
|
||||||
] ++
|
] ++
|
||||||
maybe [] (\j -> ["--jobs=" <> show j]) jobs ++
|
maybe [] (\j -> ["--jobs=" <> show j]) jobs ++
|
||||||
[ "--overwrite-policy=always"
|
[ "--project-file=" <> cp
|
||||||
, "--disable-profiling"
|
] ++ targets
|
||||||
, "--disable-tests"
|
|
||||||
, "--enable-split-sections"
|
|
||||||
, "--enable-executable-stripping"
|
|
||||||
, "--enable-executable-static"
|
|
||||||
, "--installdir=" <> ghcInstallDir
|
|
||||||
, "--project-file=" <> cp
|
|
||||||
, "exe:haskell-language-server"
|
|
||||||
, "exe:haskell-language-server-wrapper"]
|
|
||||||
)
|
)
|
||||||
(Just workdir) "cabal" Nothing
|
(Just workdir) "cabal" Nothing
|
||||||
|
forM_ targets $ \target -> do
|
||||||
|
let cabal = "cabal"
|
||||||
|
args = ["list-bin", target]
|
||||||
|
CapturedProcess{..} <- lift $ executeOut cabal args (Just workdir)
|
||||||
|
case _exitCode of
|
||||||
|
ExitFailure i -> throwE (NonZeroExit i cabal args)
|
||||||
|
_ -> pure ()
|
||||||
|
let cbin = stripNewlineEnd . T.unpack . decUTF8Safe' $ _stdOut
|
||||||
|
copyFileE cbin (ghcInstallDir </> takeFileName cbin)
|
||||||
pure ghcInstallDir
|
pure ghcInstallDir
|
||||||
|
|
||||||
forM_ artifacts $ \artifact -> do
|
forM_ artifacts $ \artifact -> do
|
||||||
@@ -1037,7 +1039,7 @@ installStackUnpacked path inst mver' forceInstall = do
|
|||||||
unless forceInstall
|
unless forceInstall
|
||||||
(liftE $ throwIfFileAlreadyExists destPath)
|
(liftE $ throwIfFileAlreadyExists destPath)
|
||||||
|
|
||||||
handleIO (throwE . CopyError . show) $ liftIO $ copyFile
|
copyFileE
|
||||||
(path </> stackFile <> exeExt)
|
(path </> stackFile <> exeExt)
|
||||||
destPath
|
destPath
|
||||||
lift $ chmod_755 destPath
|
lift $ chmod_755 destPath
|
||||||
@@ -1226,7 +1228,7 @@ setHLS ver = do
|
|||||||
lift $ rmLink (binDir </> f)
|
lift $ rmLink (binDir </> f)
|
||||||
|
|
||||||
-- set haskell-language-server-<ghcver> symlinks
|
-- set haskell-language-server-<ghcver> symlinks
|
||||||
bins <- lift $ hlsServerBinaries ver
|
bins <- lift $ hlsServerBinaries ver Nothing
|
||||||
when (null bins) $ throwE $ NotInstalled HLS (GHCTargetVersion Nothing ver)
|
when (null bins) $ throwE $ NotInstalled HLS (GHCTargetVersion Nothing ver)
|
||||||
|
|
||||||
forM_ bins $ \f -> do
|
forM_ bins $ \f -> do
|
||||||
@@ -1334,6 +1336,7 @@ warnAboutHlsCompatibility = do
|
|||||||
-- | Filter data type for 'listVersions'.
|
-- | Filter data type for 'listVersions'.
|
||||||
data ListCriteria = ListInstalled
|
data ListCriteria = ListInstalled
|
||||||
| ListSet
|
| ListSet
|
||||||
|
| ListAvailable
|
||||||
deriving Show
|
deriving Show
|
||||||
|
|
||||||
-- | A list result describes a single tool version
|
-- | A list result describes a single tool version
|
||||||
@@ -1571,7 +1574,7 @@ listVersions lt' criteria = do
|
|||||||
|
|
||||||
currentGHCup :: Map.Map Version VersionInfo -> Maybe ListResult
|
currentGHCup :: Map.Map Version VersionInfo -> Maybe ListResult
|
||||||
currentGHCup av =
|
currentGHCup av =
|
||||||
let currentVer = pvpToVersion ghcUpVer
|
let currentVer = fromJust $ pvpToVersion ghcUpVer
|
||||||
listVer = Map.lookup currentVer av
|
listVer = Map.lookup currentVer av
|
||||||
latestVer = fst <$> headOf (getTagged Latest) av
|
latestVer = fst <$> headOf (getTagged Latest) av
|
||||||
recommendedVer = fst <$> headOf (getTagged Latest) av
|
recommendedVer = fst <$> headOf (getTagged Latest) av
|
||||||
@@ -1676,6 +1679,7 @@ listVersions lt' criteria = do
|
|||||||
Nothing -> lr
|
Nothing -> lr
|
||||||
Just ListInstalled -> filter (\ListResult {..} -> lInstalled) lr
|
Just ListInstalled -> filter (\ListResult {..} -> lInstalled) lr
|
||||||
Just ListSet -> filter (\ListResult {..} -> lSet) lr
|
Just ListSet -> filter (\ListResult {..} -> lSet) lr
|
||||||
|
Just ListAvailable -> filter (\ListResult {..} -> not lNoBindist) lr
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
@@ -1728,7 +1732,7 @@ rmGHCVer ver = do
|
|||||||
(\(e :: ParseError) -> lift $ logWarn (T.pack $ displayException e) >> pure Nothing)
|
(\(e :: ParseError) -> lift $ logWarn (T.pack $ displayException e) >> pure Nothing)
|
||||||
$ fmap Just
|
$ fmap Just
|
||||||
$ getMajorMinorV (_tvVersion ver)
|
$ getMajorMinorV (_tvVersion ver)
|
||||||
forM_ v' $ \(mj, mi) -> lift (getGHCForMajor mj mi (_tvTarget ver))
|
forM_ v' $ \(mj, mi) -> lift (getGHCForPVP (PVP (fromIntegral mj :| [fromIntegral mi])) (_tvTarget ver))
|
||||||
>>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
|
>>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
|
||||||
|
|
||||||
Dirs {..} <- lift getDirs
|
Dirs {..} <- lift getDirs
|
||||||
@@ -2406,7 +2410,7 @@ compileGHC targetGhc ov bstrap jobs mbuildConfig patchdir aargs buildFlavour had
|
|||||||
<> ".tar"
|
<> ".tar"
|
||||||
<> takeExtension tar)
|
<> takeExtension tar)
|
||||||
let tarPath = cacheDir </> tarName
|
let tarPath = cacheDir </> tarName
|
||||||
handleIO (throwE . CopyError . show) $ liftIO $ copyFile (workdir </> tar)
|
copyFileE (workdir </> tar)
|
||||||
tarPath
|
tarPath
|
||||||
lift $ logInfo $ "Copied bindist to " <> T.pack tarPath
|
lift $ logInfo $ "Copied bindist to " <> T.pack tarPath
|
||||||
pure tarPath
|
pure tarPath
|
||||||
@@ -2536,6 +2540,7 @@ upgradeGHCup :: ( MonadMask m
|
|||||||
, MonadCatch m
|
, MonadCatch m
|
||||||
, HasLog env
|
, HasLog env
|
||||||
, MonadThrow m
|
, MonadThrow m
|
||||||
|
, MonadFail m
|
||||||
, MonadResource m
|
, MonadResource m
|
||||||
, MonadIO m
|
, MonadIO m
|
||||||
, MonadUnliftIO m
|
, MonadUnliftIO m
|
||||||
@@ -2560,7 +2565,8 @@ upgradeGHCup mtarget force' = do
|
|||||||
|
|
||||||
lift $ logInfo "Upgrading GHCup..."
|
lift $ logInfo "Upgrading GHCup..."
|
||||||
let latestVer = fromJust $ fst <$> getLatest dls GHCup
|
let latestVer = fromJust $ fst <$> getLatest dls GHCup
|
||||||
when (not force' && (latestVer <= pvpToVersion ghcUpVer)) $ throwE NoUpdate
|
(Just ghcupPVPVer) <- pure $ pvpToVersion ghcUpVer
|
||||||
|
when (not force' && (latestVer <= ghcupPVPVer)) $ throwE NoUpdate
|
||||||
dli <- liftE $ getDownloadInfo GHCup latestVer
|
dli <- liftE $ getDownloadInfo GHCup latestVer
|
||||||
tmp <- lift withGHCupTmpDir
|
tmp <- lift withGHCupTmpDir
|
||||||
let fn = "ghcup" <> exeExt
|
let fn = "ghcup" <> exeExt
|
||||||
@@ -2572,7 +2578,7 @@ upgradeGHCup mtarget force' = do
|
|||||||
lift $ logDebug $ "rm -f " <> T.pack destFile
|
lift $ logDebug $ "rm -f " <> T.pack destFile
|
||||||
lift $ hideError NoSuchThing $ recycleFile destFile
|
lift $ hideError NoSuchThing $ recycleFile destFile
|
||||||
lift $ logDebug $ "cp " <> T.pack p <> " " <> T.pack destFile
|
lift $ logDebug $ "cp " <> T.pack p <> " " <> T.pack destFile
|
||||||
handleIO (throwE . CopyError . show) $ liftIO $ copyFile p
|
copyFileE p
|
||||||
destFile
|
destFile
|
||||||
lift $ chmod_755 destFile
|
lift $ chmod_755 destFile
|
||||||
|
|
||||||
@@ -2623,7 +2629,7 @@ postGHCInstall ver@GHCTargetVersion {..} = do
|
|||||||
handle (\(e :: ParseError) -> lift $ logWarn (T.pack $ displayException e) >> pure Nothing)
|
handle (\(e :: ParseError) -> lift $ logWarn (T.pack $ displayException e) >> pure Nothing)
|
||||||
$ fmap Just
|
$ fmap Just
|
||||||
$ getMajorMinorV _tvVersion
|
$ getMajorMinorV _tvVersion
|
||||||
forM_ v' $ \(mj, mi) -> lift (getGHCForMajor mj mi _tvTarget)
|
forM_ v' $ \(mj, mi) -> lift (getGHCForPVP (PVP (fromIntegral mj :| [fromIntegral mi])) _tvTarget)
|
||||||
>>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
|
>>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
|
||||||
|
|
||||||
|
|
||||||
@@ -2697,3 +2703,134 @@ throwIfFileAlreadyExists :: ( MonadIO m ) =>
|
|||||||
throwIfFileAlreadyExists fp = whenM (checkFileAlreadyExists fp)
|
throwIfFileAlreadyExists fp = whenM (checkFileAlreadyExists fp)
|
||||||
(throwE $ FileAlreadyExistsError fp)
|
(throwE $ FileAlreadyExistsError fp)
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
--------------------------
|
||||||
|
--[ Garbage collection ]--
|
||||||
|
--------------------------
|
||||||
|
|
||||||
|
|
||||||
|
rmOldGHC :: ( MonadReader env m
|
||||||
|
, HasGHCupInfo env
|
||||||
|
, HasDirs env
|
||||||
|
, HasLog env
|
||||||
|
, MonadIO m
|
||||||
|
, MonadFail m
|
||||||
|
, MonadMask m
|
||||||
|
, MonadUnliftIO m
|
||||||
|
)
|
||||||
|
=> Excepts '[NotInstalled] m ()
|
||||||
|
rmOldGHC = do
|
||||||
|
GHCupInfo { _ghcupDownloads = dls } <- lift getGHCupInfo
|
||||||
|
let oldGHCs = mkTVer <$> toListOf (ix GHC % getTagged Old % to fst) dls
|
||||||
|
ghcs <- lift $ fmap rights getInstalledGHCs
|
||||||
|
forM_ ghcs $ \ghc -> when (ghc `elem` oldGHCs) $ rmGHCVer ghc
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
rmProfilingLibs :: ( MonadReader env m
|
||||||
|
, HasDirs env
|
||||||
|
, HasLog env
|
||||||
|
, MonadIO m
|
||||||
|
, MonadFail m
|
||||||
|
, MonadMask m
|
||||||
|
, MonadUnliftIO m
|
||||||
|
)
|
||||||
|
=> m ()
|
||||||
|
rmProfilingLibs = do
|
||||||
|
ghcs <- fmap rights getInstalledGHCs
|
||||||
|
|
||||||
|
let regexes :: [ByteString]
|
||||||
|
regexes = [[s|.*_p\.a$|], [s|.*\.p_hi$|]]
|
||||||
|
|
||||||
|
forM_ regexes $ \regex ->
|
||||||
|
forM_ ghcs $ \ghc -> do
|
||||||
|
d <- ghcupGHCDir ghc
|
||||||
|
matches <- liftIO $ handleIO (\_ -> pure []) $ findFilesDeep
|
||||||
|
d
|
||||||
|
(makeRegexOpts compExtended
|
||||||
|
execBlank
|
||||||
|
regex
|
||||||
|
)
|
||||||
|
forM_ matches $ \m -> do
|
||||||
|
let p = d </> m
|
||||||
|
logDebug $ "rm " <> T.pack p
|
||||||
|
rmFile p
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
rmShareDir :: ( MonadReader env m
|
||||||
|
, HasDirs env
|
||||||
|
, HasLog env
|
||||||
|
, MonadIO m
|
||||||
|
, MonadFail m
|
||||||
|
, MonadMask m
|
||||||
|
, MonadUnliftIO m
|
||||||
|
)
|
||||||
|
=> m ()
|
||||||
|
rmShareDir = do
|
||||||
|
ghcs <- fmap rights getInstalledGHCs
|
||||||
|
forM_ ghcs $ \ghc -> do
|
||||||
|
d <- ghcupGHCDir ghc
|
||||||
|
let p = d </> "share"
|
||||||
|
logDebug $ "rm -rf " <> T.pack p
|
||||||
|
rmPathForcibly p
|
||||||
|
|
||||||
|
|
||||||
|
rmHLSNoGHC :: ( MonadReader env m
|
||||||
|
, HasDirs env
|
||||||
|
, HasLog env
|
||||||
|
, MonadIO m
|
||||||
|
, MonadMask m
|
||||||
|
)
|
||||||
|
=> m ()
|
||||||
|
rmHLSNoGHC = do
|
||||||
|
Dirs {..} <- getDirs
|
||||||
|
ghcs <- fmap rights getInstalledGHCs
|
||||||
|
hlses <- fmap rights getInstalledHLSs
|
||||||
|
forM_ hlses $ \hls -> do
|
||||||
|
hlsGHCs <- fmap mkTVer <$> hlsGHCVersions' hls
|
||||||
|
forM_ hlsGHCs $ \ghc -> do
|
||||||
|
when (ghc `notElem` ghcs) $ do
|
||||||
|
bins <- hlsServerBinaries hls (Just $ _tvVersion ghc)
|
||||||
|
forM_ bins $ \bin -> do
|
||||||
|
let f = binDir </> bin
|
||||||
|
logDebug $ "rm " <> T.pack f
|
||||||
|
rmFile f
|
||||||
|
|
||||||
|
|
||||||
|
rmCache :: ( MonadReader env m
|
||||||
|
, HasDirs env
|
||||||
|
, HasLog env
|
||||||
|
, MonadIO m
|
||||||
|
, MonadMask m
|
||||||
|
)
|
||||||
|
=> m ()
|
||||||
|
rmCache = do
|
||||||
|
Dirs {..} <- getDirs
|
||||||
|
contents <- liftIO $ listDirectory cacheDir
|
||||||
|
forM_ contents $ \f -> do
|
||||||
|
let p = cacheDir </> f
|
||||||
|
logDebug $ "rm " <> T.pack p
|
||||||
|
rmFile p
|
||||||
|
|
||||||
|
|
||||||
|
rmTmp :: ( MonadReader env m
|
||||||
|
, HasDirs env
|
||||||
|
, HasLog env
|
||||||
|
, MonadIO m
|
||||||
|
, MonadMask m
|
||||||
|
)
|
||||||
|
=> m ()
|
||||||
|
rmTmp = do
|
||||||
|
tmpdir <- liftIO getCanonicalTemporaryDirectory
|
||||||
|
ghcup_dirs <- liftIO $ handleIO (\_ -> pure []) $ findFiles
|
||||||
|
tmpdir
|
||||||
|
(makeRegexOpts compExtended
|
||||||
|
execBlank
|
||||||
|
([s|^ghcup-.*$|] :: ByteString)
|
||||||
|
)
|
||||||
|
forM_ ghcup_dirs $ \f -> do
|
||||||
|
let p = tmpdir </> f
|
||||||
|
logDebug $ "rm -rf " <> T.pack p
|
||||||
|
rmPathForcibly p
|
||||||
|
|||||||
@@ -35,6 +35,7 @@ import GHCup.Types.Optics
|
|||||||
import GHCup.Types.JSON ( )
|
import GHCup.Types.JSON ( )
|
||||||
import GHCup.Utils.Dirs
|
import GHCup.Utils.Dirs
|
||||||
import GHCup.Utils.File
|
import GHCup.Utils.File
|
||||||
|
import GHCup.Utils.Logger
|
||||||
import GHCup.Utils.Prelude
|
import GHCup.Utils.Prelude
|
||||||
import GHCup.Version
|
import GHCup.Version
|
||||||
|
|
||||||
|
|||||||
@@ -23,6 +23,7 @@ import GHCup.Types
|
|||||||
import GHCup.Types.Optics
|
import GHCup.Types.Optics
|
||||||
import GHCup.Types.JSON ( )
|
import GHCup.Types.JSON ( )
|
||||||
import GHCup.Utils.File
|
import GHCup.Utils.File
|
||||||
|
import GHCup.Utils.Logger
|
||||||
import GHCup.Utils.Prelude
|
import GHCup.Utils.Prelude
|
||||||
import GHCup.Utils.String.QQ
|
import GHCup.Utils.String.QQ
|
||||||
|
|
||||||
|
|||||||
@@ -417,6 +417,7 @@ data Settings = Settings
|
|||||||
, urlSource :: URLSource
|
, urlSource :: URLSource
|
||||||
, noNetwork :: Bool
|
, noNetwork :: Bool
|
||||||
, gpgSetting :: GPGSetting
|
, gpgSetting :: GPGSetting
|
||||||
|
, noColor :: Bool -- this also exists in LoggerConfig
|
||||||
}
|
}
|
||||||
deriving (Show, GHC.Generic)
|
deriving (Show, GHC.Generic)
|
||||||
|
|
||||||
@@ -576,11 +577,12 @@ data LogLevel = Warn
|
|||||||
deriving (Eq, Ord, Show)
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
data LoggerConfig = LoggerConfig
|
data LoggerConfig = LoggerConfig
|
||||||
{ lcPrintDebug :: Bool -- ^ whether to print debug in colorOutter
|
{ lcPrintDebug :: Bool -- ^ whether to print debug in colorOutter
|
||||||
, colorOutter :: T.Text -> IO () -- ^ how to write the color output
|
, consoleOutter :: T.Text -> IO () -- ^ how to write the console output
|
||||||
, rawOutter :: T.Text -> IO () -- ^ how to write the full raw output
|
, fileOutter :: T.Text -> IO () -- ^ how to write the file output
|
||||||
|
, fancyColors :: Bool
|
||||||
}
|
}
|
||||||
deriving Show
|
deriving Show
|
||||||
|
|
||||||
instance NFData LoggerConfig where
|
instance NFData LoggerConfig where
|
||||||
rnf (LoggerConfig !lcPrintDebug !_ !_) = rnf lcPrintDebug
|
rnf (LoggerConfig !lcPrintDebug !_ !_ !fancyColors) = rnf (lcPrintDebug, fancyColors)
|
||||||
|
|||||||
@@ -24,6 +24,8 @@ module GHCup.Types.JSON where
|
|||||||
import GHCup.Types
|
import GHCup.Types
|
||||||
import GHCup.Utils.MegaParsec
|
import GHCup.Utils.MegaParsec
|
||||||
import GHCup.Utils.Prelude
|
import GHCup.Utils.Prelude
|
||||||
|
import GHCup.Utils.Logger () -- TH is broken shite and needs GHCup.Utils.Logger for linking, although we don't depend on the file.
|
||||||
|
-- This is due to the boot file.
|
||||||
|
|
||||||
import Control.Applicative ( (<|>) )
|
import Control.Applicative ( (<|>) )
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
|
|||||||
@@ -23,12 +23,9 @@ import GHCup.Types
|
|||||||
|
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import Data.ByteString ( ByteString )
|
import Data.ByteString ( ByteString )
|
||||||
import Data.Text ( Text )
|
|
||||||
import Optics
|
import Optics
|
||||||
import URI.ByteString
|
import URI.ByteString
|
||||||
import System.Console.Pretty
|
|
||||||
|
|
||||||
import qualified Data.Text as T
|
|
||||||
|
|
||||||
makePrisms ''Tool
|
makePrisms ''Tool
|
||||||
makePrisms ''Architecture
|
makePrisms ''Architecture
|
||||||
@@ -117,80 +114,6 @@ getDirs :: ( MonadReader env m
|
|||||||
getDirs = gets @"dirs"
|
getDirs = gets @"dirs"
|
||||||
|
|
||||||
|
|
||||||
logInfo :: ( MonadReader env m
|
|
||||||
, LabelOptic' "loggerConfig" A_Lens env LoggerConfig
|
|
||||||
, MonadIO m
|
|
||||||
)
|
|
||||||
=> Text
|
|
||||||
-> m ()
|
|
||||||
logInfo = logInternal Info
|
|
||||||
|
|
||||||
logWarn :: ( MonadReader env m
|
|
||||||
, LabelOptic' "loggerConfig" A_Lens env LoggerConfig
|
|
||||||
, MonadIO m
|
|
||||||
)
|
|
||||||
=> Text
|
|
||||||
-> m ()
|
|
||||||
logWarn = logInternal Warn
|
|
||||||
|
|
||||||
logDebug :: ( MonadReader env m
|
|
||||||
, LabelOptic' "loggerConfig" A_Lens env LoggerConfig
|
|
||||||
, MonadIO m
|
|
||||||
)
|
|
||||||
=> Text
|
|
||||||
-> m ()
|
|
||||||
logDebug = logInternal Debug
|
|
||||||
|
|
||||||
logError :: ( MonadReader env m
|
|
||||||
, LabelOptic' "loggerConfig" A_Lens env LoggerConfig
|
|
||||||
, MonadIO m
|
|
||||||
)
|
|
||||||
=> Text
|
|
||||||
-> m ()
|
|
||||||
logError = logInternal Error
|
|
||||||
|
|
||||||
|
|
||||||
logInternal :: ( MonadReader env m
|
|
||||||
, LabelOptic' "loggerConfig" A_Lens env LoggerConfig
|
|
||||||
, MonadIO m
|
|
||||||
) => LogLevel
|
|
||||||
-> Text
|
|
||||||
-> m ()
|
|
||||||
logInternal logLevel msg = do
|
|
||||||
LoggerConfig {..} <- gets @"loggerConfig"
|
|
||||||
let style' = case logLevel of
|
|
||||||
Debug -> style Bold . color Blue
|
|
||||||
Info -> style Bold . color Green
|
|
||||||
Warn -> style Bold . color Yellow
|
|
||||||
Error -> style Bold . color Red
|
|
||||||
let l = case logLevel of
|
|
||||||
Debug -> style' "[ Debug ]"
|
|
||||||
Info -> style' "[ Info ]"
|
|
||||||
Warn -> style' "[ Warn ]"
|
|
||||||
Error -> style' "[ Error ]"
|
|
||||||
let strs = T.split (== '\n') msg
|
|
||||||
let out = case strs of
|
|
||||||
[] -> T.empty
|
|
||||||
(x:xs) ->
|
|
||||||
foldr (\a b -> a <> "\n" <> b) mempty
|
|
||||||
. ((l <> " " <> x) :)
|
|
||||||
. fmap (\line' -> style' "[ ... ] " <> line' )
|
|
||||||
$ xs
|
|
||||||
|
|
||||||
when (lcPrintDebug || (not lcPrintDebug && (logLevel /= Debug)))
|
|
||||||
$ liftIO $ colorOutter out
|
|
||||||
|
|
||||||
-- raw output
|
|
||||||
let lr = case logLevel of
|
|
||||||
Debug -> "Debug:"
|
|
||||||
Info -> "Info:"
|
|
||||||
Warn -> "Warn:"
|
|
||||||
Error -> "Error:"
|
|
||||||
let outr = lr <> " " <> msg <> "\n"
|
|
||||||
liftIO $ rawOutter outr
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
getLogCleanup :: ( MonadReader env m
|
getLogCleanup :: ( MonadReader env m
|
||||||
, LabelOptic' "logCleanup" A_Lens env (IO ())
|
, LabelOptic' "logCleanup" A_Lens env (IO ())
|
||||||
)
|
)
|
||||||
|
|||||||
@@ -35,6 +35,7 @@ import GHCup.Types.Optics
|
|||||||
import GHCup.Types.JSON ( )
|
import GHCup.Types.JSON ( )
|
||||||
import GHCup.Utils.Dirs
|
import GHCup.Utils.Dirs
|
||||||
import GHCup.Utils.File
|
import GHCup.Utils.File
|
||||||
|
import GHCup.Utils.Logger
|
||||||
import GHCup.Utils.MegaParsec
|
import GHCup.Utils.MegaParsec
|
||||||
import GHCup.Utils.Prelude
|
import GHCup.Utils.Prelude
|
||||||
import GHCup.Utils.String.QQ
|
import GHCup.Utils.String.QQ
|
||||||
@@ -85,8 +86,37 @@ import qualified Data.Map.Strict as Map
|
|||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Text.Encoding as E
|
import qualified Data.Text.Encoding as E
|
||||||
import qualified Text.Megaparsec as MP
|
import qualified Text.Megaparsec as MP
|
||||||
|
import qualified Data.List.NonEmpty as NE
|
||||||
|
|
||||||
|
|
||||||
|
-- $setup
|
||||||
|
-- >>> :set -XOverloadedStrings
|
||||||
|
-- >>> :set -XDataKinds
|
||||||
|
-- >>> :set -XTypeApplications
|
||||||
|
-- >>> :set -XQuasiQuotes
|
||||||
|
-- >>> import System.Directory
|
||||||
|
-- >>> import URI.ByteString
|
||||||
|
-- >>> import qualified Data.Text as T
|
||||||
|
-- >>> import GHCup.Utils.Prelude
|
||||||
|
-- >>> import GHCup.Download
|
||||||
|
-- >>> import GHCup.Version
|
||||||
|
-- >>> import GHCup.Errors
|
||||||
|
-- >>> import GHCup.Types
|
||||||
|
-- >>> import GHCup.Types.Optics
|
||||||
|
-- >>> import Optics
|
||||||
|
-- >>> import GHCup.Utils.Version.QQ
|
||||||
|
-- >>> import qualified Data.Text.Encoding as E
|
||||||
|
-- >>> import Control.Monad.Reader
|
||||||
|
-- >>> import Haskus.Utils.Variant.Excepts
|
||||||
|
-- >>> import Text.PrettyPrint.HughesPJClass ( prettyShow )
|
||||||
|
-- >>> let lc = LoggerConfig { lcPrintDebug = False, consoleOutter = mempty, fileOutter = mempty, fancyColors = False }
|
||||||
|
-- >>> dirs' <- getAllDirs
|
||||||
|
-- >>> let installedVersions = [ ([pver|8.10.7|], Nothing), ([pver|8.10.4|], Nothing), ([pver|8.8.4|], Nothing), ([pver|8.8.3|], Nothing) ]
|
||||||
|
-- >>> let settings = Settings True False Never Curl False GHCupURL True GPGNone False
|
||||||
|
-- >>> let leanAppState = LeanAppState settings dirs' defaultKeyBindings lc
|
||||||
|
-- >>> cwd <- getCurrentDirectory
|
||||||
|
-- >>> (Right ref) <- pure $ parseURI strictURIParserOptions $ "file://" <> E.encodeUtf8 (T.pack cwd) <> "/data/metadata/" <> (urlBaseName . view pathL' $ ghcupURL)
|
||||||
|
-- >>> (VRight r) <- (fmap . fmap) _ghcupDownloads $ flip runReaderT leanAppState . runE @'[DigestError, GPGError, JSONError , DownloadFailed , FileDoesNotExistError] $ liftE $ getBase ref
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
@@ -462,33 +492,50 @@ hlsGHCVersions :: ( MonadReader env m
|
|||||||
)
|
)
|
||||||
=> m [Version]
|
=> m [Version]
|
||||||
hlsGHCVersions = do
|
hlsGHCVersions = do
|
||||||
h <- hlsSet
|
h <- hlsSet
|
||||||
vers <- forM h $ \h' -> do
|
fromMaybe [] <$> forM h hlsGHCVersions'
|
||||||
bins <- hlsServerBinaries h'
|
|
||||||
pure $ fmap
|
|
||||||
(version
|
hlsGHCVersions' :: ( MonadReader env m
|
||||||
. T.pack
|
, HasDirs env
|
||||||
. fromJust
|
, MonadIO m
|
||||||
. stripPrefix "haskell-language-server-"
|
, MonadThrow m
|
||||||
. head
|
, MonadCatch m
|
||||||
. splitOn "~"
|
)
|
||||||
)
|
=> Version
|
||||||
bins
|
-> m [Version]
|
||||||
pure . sortBy (flip compare) . rights . concat . maybeToList $ vers
|
hlsGHCVersions' v' = do
|
||||||
|
bins <- hlsServerBinaries v' Nothing
|
||||||
|
let vers = fmap
|
||||||
|
(version
|
||||||
|
. T.pack
|
||||||
|
. fromJust
|
||||||
|
. stripPrefix "haskell-language-server-"
|
||||||
|
. head
|
||||||
|
. splitOn "~"
|
||||||
|
)
|
||||||
|
bins
|
||||||
|
pure . sortBy (flip compare) . rights $ vers
|
||||||
|
|
||||||
|
|
||||||
-- | Get all server binaries for an hls version, if any.
|
-- | Get all server binaries for an hls version, if any.
|
||||||
hlsServerBinaries :: (MonadReader env m, HasDirs env, MonadIO m)
|
hlsServerBinaries :: (MonadReader env m, HasDirs env, MonadIO m)
|
||||||
=> Version
|
=> Version
|
||||||
|
-> Maybe Version -- ^ optional GHC version
|
||||||
-> m [FilePath]
|
-> m [FilePath]
|
||||||
hlsServerBinaries ver = do
|
hlsServerBinaries ver mghcVer = do
|
||||||
Dirs {..} <- getDirs
|
Dirs {..} <- getDirs
|
||||||
liftIO $ handleIO (\_ -> pure []) $ findFiles
|
liftIO $ handleIO (\_ -> pure []) $ findFiles
|
||||||
binDir
|
binDir
|
||||||
(makeRegexOpts
|
(makeRegexOpts
|
||||||
compExtended
|
compExtended
|
||||||
execBlank
|
execBlank
|
||||||
([s|^haskell-language-server-.*~|] <> escapeVerRex ver <> E.encodeUtf8 (T.pack exeExt) <> [s|$|] :: ByteString
|
([s|^haskell-language-server-|]
|
||||||
|
<> maybe [s|.*|] escapeVerRex mghcVer
|
||||||
|
<> [s|~|]
|
||||||
|
<> escapeVerRex ver
|
||||||
|
<> E.encodeUtf8 (T.pack exeExt)
|
||||||
|
<> [s|$|] :: ByteString
|
||||||
)
|
)
|
||||||
)
|
)
|
||||||
|
|
||||||
@@ -517,7 +564,7 @@ hlsWrapperBinary ver = do
|
|||||||
-- | Get all binaries for an hls version, if any.
|
-- | Get all binaries for an hls version, if any.
|
||||||
hlsAllBinaries :: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m) => Version -> m [FilePath]
|
hlsAllBinaries :: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m) => Version -> m [FilePath]
|
||||||
hlsAllBinaries ver = do
|
hlsAllBinaries ver = do
|
||||||
hls <- hlsServerBinaries ver
|
hls <- hlsServerBinaries ver Nothing
|
||||||
wrapper <- hlsWrapperBinary ver
|
wrapper <- hlsWrapperBinary ver
|
||||||
pure (maybeToList wrapper ++ hls)
|
pure (maybeToList wrapper ++ hls)
|
||||||
|
|
||||||
@@ -558,34 +605,83 @@ matchMajor v' major' minor' = case getMajorMinorV v' of
|
|||||||
Just (x, y) -> x == major' && y == minor'
|
Just (x, y) -> x == major' && y == minor'
|
||||||
Nothing -> False
|
Nothing -> False
|
||||||
|
|
||||||
|
-- | Match PVP prefix.
|
||||||
|
--
|
||||||
|
-- >>> matchPVPrefix [pver|8.8|] [pver|8.8.4|]
|
||||||
|
-- True
|
||||||
|
-- >>> matchPVPrefix [pver|8|] [pver|8.8.4|]
|
||||||
|
-- True
|
||||||
|
-- >>> matchPVPrefix [pver|8.10|] [pver|8.8.4|]
|
||||||
|
-- False
|
||||||
|
-- >>> matchPVPrefix [pver|8.10|] [pver|8.10.7|]
|
||||||
|
-- True
|
||||||
|
matchPVPrefix :: PVP -> PVP -> Bool
|
||||||
|
matchPVPrefix (toL -> prefix) (toL -> full) = and $ zipWith (==) prefix full
|
||||||
|
|
||||||
-- | Get the latest installed full GHC version that satisfies X.Y.
|
toL :: PVP -> [Int]
|
||||||
-- This reads `ghcupGHCBaseDir`.
|
toL (PVP inner) = fmap fromIntegral $ NE.toList inner
|
||||||
getGHCForMajor :: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m)
|
|
||||||
=> Int -- ^ major version component
|
|
||||||
-> Int -- ^ minor version component
|
-- | Get the latest installed full GHC version that satisfies the given (possibly partial)
|
||||||
-> Maybe Text -- ^ the target triple
|
-- PVP version.
|
||||||
-> m (Maybe GHCTargetVersion)
|
getGHCForPVP :: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m)
|
||||||
getGHCForMajor major' minor' mt = do
|
=> PVP
|
||||||
|
-> Maybe Text -- ^ the target triple
|
||||||
|
-> m (Maybe GHCTargetVersion)
|
||||||
|
getGHCForPVP pvpIn mt = do
|
||||||
ghcs <- rights <$> getInstalledGHCs
|
ghcs <- rights <$> getInstalledGHCs
|
||||||
|
-- we're permissive here... failed parse just means we have no match anyway
|
||||||
|
let ghcs' = catMaybes $ flip fmap ghcs $ \GHCTargetVersion{..} -> do
|
||||||
|
pvp_ <- versionToPVP _tvVersion
|
||||||
|
pure (pvp_, _tvTarget)
|
||||||
|
|
||||||
pure
|
getGHCForPVP' pvpIn ghcs' mt
|
||||||
. lastMay
|
|
||||||
. sortBy (\x y -> compare (_tvVersion x) (_tvVersion y))
|
-- | Like 'getGHCForPVP', except with explicit input parameter.
|
||||||
. filter
|
--
|
||||||
(\GHCTargetVersion {..} ->
|
-- >>> fmap prettyShow $ getGHCForPVP' [pver|8|] installedVersions Nothing
|
||||||
_tvTarget == mt && matchMajor _tvVersion major' minor'
|
-- "Just 8.10.7"
|
||||||
)
|
-- >>> fmap prettyShow $ getGHCForPVP' [pver|8.8|] installedVersions Nothing
|
||||||
$ ghcs
|
-- "Just 8.8.4"
|
||||||
|
-- >>> fmap prettyShow $ getGHCForPVP' [pver|8.10.4|] installedVersions Nothing
|
||||||
|
-- "Just 8.10.4"
|
||||||
|
getGHCForPVP' :: MonadThrow m
|
||||||
|
=> PVP
|
||||||
|
-> [(PVP, Maybe Text)] -- ^ installed GHCs
|
||||||
|
-> Maybe Text -- ^ the target triple
|
||||||
|
-> m (Maybe GHCTargetVersion)
|
||||||
|
getGHCForPVP' pvpIn ghcs' mt = do
|
||||||
|
let mResult = lastMay
|
||||||
|
. sortBy (\(x, _) (y, _) -> compare x y)
|
||||||
|
. filter
|
||||||
|
(\(pvp_, target) ->
|
||||||
|
target == mt && matchPVPrefix pvp_ pvpIn
|
||||||
|
)
|
||||||
|
$ ghcs'
|
||||||
|
forM mResult $ \(pvp_, target) -> do
|
||||||
|
ver' <- pvpToVersion pvp_
|
||||||
|
pure (GHCTargetVersion target ver')
|
||||||
|
|
||||||
|
|
||||||
-- | Get the latest available ghc for X.Y major version.
|
-- | Get the latest available ghc for the given PVP version, which
|
||||||
getLatestGHCFor :: Int -- ^ major version component
|
-- may only contain parts.
|
||||||
-> Int -- ^ minor version component
|
--
|
||||||
-> GHCupDownloads
|
-- >>> (fmap . fmap) fst $ getLatestToolFor GHC [pver|8|] r
|
||||||
-> Maybe (Version, VersionInfo)
|
-- Just (PVP {_pComponents = 8 :| [10,7]})
|
||||||
getLatestGHCFor major' minor' dls =
|
-- >>> (fmap . fmap) fst $ getLatestToolFor GHC [pver|8.8|] r
|
||||||
preview (ix GHC % to Map.toDescList) dls >>= lastMay . filter (\(v, _) -> matchMajor v major' minor')
|
-- Just (PVP {_pComponents = 8 :| [8,4]})
|
||||||
|
-- >>> (fmap . fmap) fst $ getLatestToolFor GHC [pver|8.8.4|] r
|
||||||
|
-- Just (PVP {_pComponents = 8 :| [8,4]})
|
||||||
|
getLatestToolFor :: MonadThrow m
|
||||||
|
=> Tool
|
||||||
|
-> PVP
|
||||||
|
-> GHCupDownloads
|
||||||
|
-> m (Maybe (PVP, VersionInfo))
|
||||||
|
getLatestToolFor tool pvpIn dls = do
|
||||||
|
let ls = fromMaybe [] $ preview (ix tool % to Map.toDescList) dls
|
||||||
|
let ps = catMaybes $ fmap (\(v, vi) -> (,vi) <$> versionToPVP v) ls
|
||||||
|
pure . headMay . filter (\(v, _) -> matchPVPrefix pvpIn v) $ ps
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
@@ -689,11 +785,10 @@ intoSubdir bdir tardir = case tardir of
|
|||||||
-- | Get the tool version that has this tag. If multiple have it,
|
-- | Get the tool version that has this tag. If multiple have it,
|
||||||
-- picks the greatest version.
|
-- picks the greatest version.
|
||||||
getTagged :: Tag
|
getTagged :: Tag
|
||||||
-> AffineFold (Map.Map Version VersionInfo) (Version, VersionInfo)
|
-> Fold (Map.Map Version VersionInfo) (Version, VersionInfo)
|
||||||
getTagged tag =
|
getTagged tag =
|
||||||
to (Map.filter (\VersionInfo {..} -> tag `elem` _viTags))
|
to (Map.toDescList . Map.filter (\VersionInfo {..} -> tag `elem` _viTags))
|
||||||
% to Map.toDescList
|
% folding id
|
||||||
% _head
|
|
||||||
|
|
||||||
getLatest :: GHCupDownloads -> Tool -> Maybe (Version, VersionInfo)
|
getLatest :: GHCupDownloads -> Tool -> Maybe (Version, VersionInfo)
|
||||||
getLatest av tool = headOf (ix tool % getTagged Latest) av
|
getLatest av tool = headOf (ix tool % getTagged Latest) av
|
||||||
@@ -824,7 +919,7 @@ getChangeLog :: GHCupDownloads -> Tool -> Either Version Tag -> Maybe URI
|
|||||||
getChangeLog dls tool (Left v') =
|
getChangeLog dls tool (Left v') =
|
||||||
preview (ix tool % ix v' % viChangeLog % _Just) dls
|
preview (ix tool % ix v' % viChangeLog % _Just) dls
|
||||||
getChangeLog dls tool (Right tag) =
|
getChangeLog dls tool (Right tag) =
|
||||||
preview (ix tool % getTagged tag % to snd % viChangeLog % _Just) dls
|
preview (ix tool % pre (getTagged tag) % to snd % viChangeLog % _Just) dls
|
||||||
|
|
||||||
|
|
||||||
-- | Execute a build action while potentially cleaning up:
|
-- | Execute a build action while potentially cleaning up:
|
||||||
|
|||||||
@@ -38,6 +38,7 @@ import GHCup.Types
|
|||||||
import GHCup.Types.JSON ( )
|
import GHCup.Types.JSON ( )
|
||||||
import GHCup.Types.Optics
|
import GHCup.Types.Optics
|
||||||
import GHCup.Utils.MegaParsec
|
import GHCup.Utils.MegaParsec
|
||||||
|
import GHCup.Utils.Logger
|
||||||
import GHCup.Utils.Prelude
|
import GHCup.Utils.Prelude
|
||||||
|
|
||||||
import Control.Exception.Safe
|
import Control.Exception.Safe
|
||||||
|
|||||||
@@ -105,6 +105,11 @@ findFiles path regex = do
|
|||||||
contents <- listDirectory path
|
contents <- listDirectory path
|
||||||
pure $ filter (match regex) contents
|
pure $ filter (match regex) contents
|
||||||
|
|
||||||
|
findFilesDeep :: FilePath -> Regex -> IO [FilePath]
|
||||||
|
findFilesDeep path regex = do
|
||||||
|
contents <- getDirectoryContentsRecursive path
|
||||||
|
pure $ filter (match regex) contents
|
||||||
|
|
||||||
findFiles' :: FilePath -> MP.Parsec Void Text a -> IO [FilePath]
|
findFiles' :: FilePath -> MP.Parsec Void Text a -> IO [FilePath]
|
||||||
findFiles' path parser = do
|
findFiles' path parser = do
|
||||||
contents <- listDirectory path
|
contents <- listDirectory path
|
||||||
|
|||||||
5
lib/GHCup/Utils/File/Common.hs-boot
Normal file
5
lib/GHCup/Utils/File/Common.hs-boot
Normal file
@@ -0,0 +1,5 @@
|
|||||||
|
module GHCup.Utils.File.Common where
|
||||||
|
|
||||||
|
import Text.Regex.Posix
|
||||||
|
|
||||||
|
findFiles :: FilePath -> Regex -> IO [FilePath]
|
||||||
@@ -17,6 +17,7 @@ module GHCup.Utils.File.Posix where
|
|||||||
|
|
||||||
import GHCup.Utils.File.Common
|
import GHCup.Utils.File.Common
|
||||||
import GHCup.Utils.Prelude
|
import GHCup.Utils.Prelude
|
||||||
|
import GHCup.Utils.Logger
|
||||||
import GHCup.Types
|
import GHCup.Types
|
||||||
import GHCup.Types.Optics
|
import GHCup.Types.Optics
|
||||||
|
|
||||||
@@ -34,8 +35,7 @@ import Data.Sequence ( Seq, (|>) )
|
|||||||
import Data.List
|
import Data.List
|
||||||
import Data.Word8
|
import Data.Word8
|
||||||
import GHC.IO.Exception
|
import GHC.IO.Exception
|
||||||
import System.Console.Pretty hiding ( Pretty )
|
import System.Console.Terminal.Common
|
||||||
import System.Console.Regions
|
|
||||||
import System.IO.Error
|
import System.IO.Error
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.Directory
|
import System.Directory
|
||||||
@@ -51,6 +51,7 @@ import qualified Data.Sequence as Sq
|
|||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Text.Encoding as E
|
import qualified Data.Text.Encoding as E
|
||||||
import qualified System.Posix.Process as SPP
|
import qualified System.Posix.Process as SPP
|
||||||
|
import qualified System.Console.Terminal.Posix as TP
|
||||||
import qualified Data.ByteString as BS
|
import qualified Data.ByteString as BS
|
||||||
import qualified Data.ByteString.Lazy as BL
|
import qualified Data.ByteString.Lazy as BL
|
||||||
import qualified "unix-bytestring" System.Posix.IO.ByteString
|
import qualified "unix-bytestring" System.Posix.IO.ByteString
|
||||||
@@ -87,9 +88,9 @@ execLogged exe args chdir lfile env = do
|
|||||||
let logfile = logsDir </> lfile <> ".log"
|
let logfile = logsDir </> lfile <> ".log"
|
||||||
liftIO $ bracket (openFd logfile WriteOnly (Just newFilePerms) defaultFileFlags{ append = True })
|
liftIO $ bracket (openFd logfile WriteOnly (Just newFilePerms) defaultFileFlags{ append = True })
|
||||||
closeFd
|
closeFd
|
||||||
(action verbose)
|
(action verbose noColor)
|
||||||
where
|
where
|
||||||
action verbose fd = do
|
action verbose no_color fd = do
|
||||||
actionWithPipes $ \(stdoutRead, stdoutWrite) -> do
|
actionWithPipes $ \(stdoutRead, stdoutWrite) -> do
|
||||||
-- start the thread that logs to stdout
|
-- start the thread that logs to stdout
|
||||||
pState <- newEmptyMVar
|
pState <- newEmptyMVar
|
||||||
@@ -100,7 +101,7 @@ execLogged exe args chdir lfile env = do
|
|||||||
$ EX.finally
|
$ EX.finally
|
||||||
(if verbose
|
(if verbose
|
||||||
then tee fd stdoutRead
|
then tee fd stdoutRead
|
||||||
else printToRegion fd stdoutRead 6 pState
|
else printToRegion fd stdoutRead 6 pState no_color
|
||||||
)
|
)
|
||||||
(putMVar done ())
|
(putMVar done ())
|
||||||
|
|
||||||
@@ -137,46 +138,57 @@ execLogged exe args chdir lfile env = do
|
|||||||
|
|
||||||
-- Reads fdIn and logs the output in a continous scrolling area
|
-- Reads fdIn and logs the output in a continous scrolling area
|
||||||
-- of 'size' terminal lines. Also writes to a log file.
|
-- of 'size' terminal lines. Also writes to a log file.
|
||||||
printToRegion :: Fd -> Fd -> Int -> MVar Bool -> IO ()
|
printToRegion :: Fd -> Fd -> Int -> MVar Bool -> Bool -> IO ()
|
||||||
printToRegion fileFd fdIn size pState = do
|
printToRegion fileFd fdIn size pState no_color = do
|
||||||
void $ displayConsoleRegions $ do
|
-- init region
|
||||||
rs <-
|
forM_ [1..size] $ \_ -> BS.putStr "\n"
|
||||||
liftIO
|
|
||||||
. fmap Sq.fromList
|
void $ flip runStateT mempty
|
||||||
. sequence
|
$ do
|
||||||
. replicate size
|
handle
|
||||||
. openConsoleRegion
|
(\(ex :: SomeException) -> do
|
||||||
$ Linear
|
ps <- liftIO $ takeMVar pState
|
||||||
flip runStateT mempty
|
when ps (liftIO $ BS.putStr (pos1 <> moveLineUp size <> clearScreen))
|
||||||
$ handle
|
throw ex
|
||||||
(\(ex :: SomeException) -> do
|
) $ readTilEOF lineAction fdIn
|
||||||
ps <- liftIO $ takeMVar pState
|
|
||||||
when ps (forM_ rs (liftIO . closeConsoleRegion))
|
|
||||||
throw ex
|
|
||||||
)
|
|
||||||
$ readTilEOF (lineAction rs) fdIn
|
|
||||||
|
|
||||||
where
|
where
|
||||||
|
clearScreen :: ByteString
|
||||||
|
clearScreen = "\x1b[0J"
|
||||||
|
clearLine :: ByteString
|
||||||
|
clearLine = "\x1b[2K"
|
||||||
|
moveLineUp :: Int -> ByteString
|
||||||
|
moveLineUp n = "\x1b[" <> E.encodeUtf8 (T.pack (show n)) <> "A"
|
||||||
|
moveLineDown :: Int -> ByteString
|
||||||
|
moveLineDown n = "\x1b[" <> E.encodeUtf8 (T.pack (show n)) <> "B"
|
||||||
|
pos1 :: ByteString
|
||||||
|
pos1 = "\r"
|
||||||
|
overwriteNthLine :: Int -> ByteString -> ByteString
|
||||||
|
overwriteNthLine n str = pos1 <> moveLineUp n <> clearLine <> str <> moveLineDown n <> pos1
|
||||||
|
|
||||||
|
blue :: ByteString -> ByteString
|
||||||
|
blue bs
|
||||||
|
| no_color = bs
|
||||||
|
| otherwise = "\x1b[0;34m" <> bs <> "\x1b[0m"
|
||||||
|
|
||||||
-- action to perform line by line
|
-- action to perform line by line
|
||||||
-- TODO: do this with vty for efficiency
|
|
||||||
lineAction :: (MonadMask m, MonadIO m)
|
lineAction :: (MonadMask m, MonadIO m)
|
||||||
=> Seq ConsoleRegion
|
=> ByteString
|
||||||
-> ByteString
|
|
||||||
-> StateT (Seq ByteString) m ()
|
-> StateT (Seq ByteString) m ()
|
||||||
lineAction rs = \bs' -> do
|
lineAction = \bs' -> do
|
||||||
void $ liftIO $ SPIB.fdWrite fileFd (bs' <> "\n")
|
void $ liftIO $ SPIB.fdWrite fileFd (bs' <> "\n")
|
||||||
modify (swapRegs bs')
|
modify (swapRegs bs')
|
||||||
regs <- get
|
liftIO TP.size >>= \case
|
||||||
liftIO $ forM_ (Sq.zip regs rs) $ \(bs, r) -> setConsoleRegion r $ do
|
Nothing -> pure ()
|
||||||
w <- consoleWidth
|
Just (Window _ w) -> do
|
||||||
return
|
regs <- get
|
||||||
. T.pack
|
liftIO $ forM_ (Sq.zip regs (Sq.fromList [0..(Sq.length regs - 1)])) $ \(bs, i) -> do
|
||||||
. color Blue
|
BS.putStr
|
||||||
. T.unpack
|
. overwriteNthLine (size - i)
|
||||||
. decUTF8Safe
|
. trim w
|
||||||
. trim w
|
. blue
|
||||||
. (\b -> "[ " <> E.encodeUtf8 (T.pack lfile) <> " ] " <> b)
|
. (\b -> "[ " <> E.encodeUtf8 (T.pack lfile) <> " ] " <> b)
|
||||||
$ bs
|
$ bs
|
||||||
|
|
||||||
swapRegs :: a -> Seq a -> Seq a
|
swapRegs :: a -> Seq a -> Seq a
|
||||||
swapRegs bs = \regs -> if
|
swapRegs bs = \regs -> if
|
||||||
|
|||||||
@@ -1,5 +1,7 @@
|
|||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE QuasiQuotes #-}
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
{-|
|
{-|
|
||||||
Module : GHCup.Utils.Logger
|
Module : GHCup.Utils.Logger
|
||||||
@@ -16,21 +18,97 @@ module GHCup.Utils.Logger where
|
|||||||
|
|
||||||
import GHCup.Types
|
import GHCup.Types
|
||||||
import GHCup.Types.Optics
|
import GHCup.Types.Optics
|
||||||
import GHCup.Utils.File
|
import {-# SOURCE #-} GHCup.Utils.File.Common
|
||||||
import GHCup.Utils.String.QQ
|
import GHCup.Utils.String.QQ
|
||||||
|
|
||||||
import Control.Exception.Safe
|
import Control.Exception.Safe
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.IO.Class
|
import Control.Monad.IO.Class
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
|
import Data.Text ( Text )
|
||||||
|
import Optics
|
||||||
import Prelude hiding ( appendFile )
|
import Prelude hiding ( appendFile )
|
||||||
|
import System.Console.Pretty
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.IO.Error
|
import System.IO.Error
|
||||||
import Text.Regex.Posix
|
import Text.Regex.Posix
|
||||||
|
|
||||||
import qualified Data.ByteString as B
|
import qualified Data.ByteString as B
|
||||||
import GHCup.Utils.Prelude
|
import GHCup.Utils.Prelude
|
||||||
|
import qualified Data.Text as T
|
||||||
|
|
||||||
|
logInfo :: ( MonadReader env m
|
||||||
|
, LabelOptic' "loggerConfig" A_Lens env LoggerConfig
|
||||||
|
, MonadIO m
|
||||||
|
)
|
||||||
|
=> Text
|
||||||
|
-> m ()
|
||||||
|
logInfo = logInternal Info
|
||||||
|
|
||||||
|
logWarn :: ( MonadReader env m
|
||||||
|
, LabelOptic' "loggerConfig" A_Lens env LoggerConfig
|
||||||
|
, MonadIO m
|
||||||
|
)
|
||||||
|
=> Text
|
||||||
|
-> m ()
|
||||||
|
logWarn = logInternal Warn
|
||||||
|
|
||||||
|
logDebug :: ( MonadReader env m
|
||||||
|
, LabelOptic' "loggerConfig" A_Lens env LoggerConfig
|
||||||
|
, MonadIO m
|
||||||
|
)
|
||||||
|
=> Text
|
||||||
|
-> m ()
|
||||||
|
logDebug = logInternal Debug
|
||||||
|
|
||||||
|
logError :: ( MonadReader env m
|
||||||
|
, LabelOptic' "loggerConfig" A_Lens env LoggerConfig
|
||||||
|
, MonadIO m
|
||||||
|
)
|
||||||
|
=> Text
|
||||||
|
-> m ()
|
||||||
|
logError = logInternal Error
|
||||||
|
|
||||||
|
|
||||||
|
logInternal :: ( MonadReader env m
|
||||||
|
, LabelOptic' "loggerConfig" A_Lens env LoggerConfig
|
||||||
|
, MonadIO m
|
||||||
|
) => LogLevel
|
||||||
|
-> Text
|
||||||
|
-> m ()
|
||||||
|
logInternal logLevel msg = do
|
||||||
|
LoggerConfig {..} <- gets @"loggerConfig"
|
||||||
|
let color' c = if fancyColors then color c else id
|
||||||
|
let style' = case logLevel of
|
||||||
|
Debug -> style Bold . color' Blue
|
||||||
|
Info -> style Bold . color' Green
|
||||||
|
Warn -> style Bold . color' Yellow
|
||||||
|
Error -> style Bold . color' Red
|
||||||
|
let l = case logLevel of
|
||||||
|
Debug -> style' "[ Debug ]"
|
||||||
|
Info -> style' "[ Info ]"
|
||||||
|
Warn -> style' "[ Warn ]"
|
||||||
|
Error -> style' "[ Error ]"
|
||||||
|
let strs = T.split (== '\n') msg
|
||||||
|
let out = case strs of
|
||||||
|
[] -> T.empty
|
||||||
|
(x:xs) ->
|
||||||
|
foldr (\a b -> a <> "\n" <> b) mempty
|
||||||
|
. ((l <> " " <> x) :)
|
||||||
|
. fmap (\line' -> style' "[ ... ] " <> line' )
|
||||||
|
$ xs
|
||||||
|
|
||||||
|
when (lcPrintDebug || (not lcPrintDebug && (logLevel /= Debug)))
|
||||||
|
$ liftIO $ consoleOutter out
|
||||||
|
|
||||||
|
-- raw output
|
||||||
|
let lr = case logLevel of
|
||||||
|
Debug -> "Debug:"
|
||||||
|
Info -> "Info:"
|
||||||
|
Warn -> "Warn:"
|
||||||
|
Error -> "Error:"
|
||||||
|
let outr = lr <> " " <> msg <> "\n"
|
||||||
|
liftIO $ fileOutter outr
|
||||||
|
|
||||||
|
|
||||||
initGHCupFileLogging :: ( MonadReader env m
|
initGHCupFileLogging :: ( MonadReader env m
|
||||||
|
|||||||
21
lib/GHCup/Utils/Logger.hs-boot
Normal file
21
lib/GHCup/Utils/Logger.hs-boot
Normal file
@@ -0,0 +1,21 @@
|
|||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
|
module GHCup.Utils.Logger where
|
||||||
|
|
||||||
|
import GHCup.Types
|
||||||
|
|
||||||
|
import Control.Monad.IO.Class
|
||||||
|
import Control.Monad.Reader
|
||||||
|
import Data.Text ( Text )
|
||||||
|
import Optics
|
||||||
|
|
||||||
|
logWarn :: ( MonadReader env m
|
||||||
|
, LabelOptic' "loggerConfig" A_Lens env LoggerConfig
|
||||||
|
, MonadIO m
|
||||||
|
)
|
||||||
|
=> Text
|
||||||
|
-> m ()
|
||||||
|
|
||||||
@@ -22,7 +22,9 @@ module GHCup.Utils.Prelude where
|
|||||||
#if defined(IS_WINDOWS)
|
#if defined(IS_WINDOWS)
|
||||||
import GHCup.Types
|
import GHCup.Types
|
||||||
#endif
|
#endif
|
||||||
|
import GHCup.Errors
|
||||||
import GHCup.Types.Optics
|
import GHCup.Types.Optics
|
||||||
|
import {-# SOURCE #-} GHCup.Utils.Logger
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Exception.Safe
|
import Control.Exception.Safe
|
||||||
@@ -31,13 +33,14 @@ import Control.Monad.IO.Class
|
|||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import Data.Bifunctor
|
import Data.Bifunctor
|
||||||
import Data.ByteString ( ByteString )
|
import Data.ByteString ( ByteString )
|
||||||
import Data.List ( nub, intercalate, stripPrefix, isPrefixOf )
|
import Data.List ( nub, intercalate, stripPrefix, isPrefixOf, dropWhileEnd )
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Foldable
|
import Data.Foldable
|
||||||
|
import Data.List.NonEmpty ( NonEmpty( (:|) ))
|
||||||
import Data.String
|
import Data.String
|
||||||
import Data.Text ( Text )
|
import Data.Text ( Text )
|
||||||
import Data.Versions
|
import Data.Versions
|
||||||
import Data.Word8
|
import Data.Word8 hiding ( isDigit )
|
||||||
import Haskus.Utils.Types.List
|
import Haskus.Utils.Types.List
|
||||||
import Haskus.Utils.Variant.Excepts
|
import Haskus.Utils.Variant.Excepts
|
||||||
import Text.PrettyPrint.HughesPJClass ( prettyShow, Pretty )
|
import Text.PrettyPrint.HughesPJClass ( prettyShow, Pretty )
|
||||||
@@ -58,6 +61,7 @@ import qualified Data.ByteString as B
|
|||||||
import qualified Data.ByteString.Lazy as L
|
import qualified Data.ByteString.Lazy as L
|
||||||
import qualified Data.Strict.Maybe as S
|
import qualified Data.Strict.Maybe as S
|
||||||
import qualified Data.List.Split as Split
|
import qualified Data.List.Split as Split
|
||||||
|
import qualified Data.List.NonEmpty as NE
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Text.Encoding as E
|
import qualified Data.Text.Encoding as E
|
||||||
import qualified Data.Text.Encoding.Error as E
|
import qualified Data.Text.Encoding.Error as E
|
||||||
@@ -295,12 +299,28 @@ removeLensFieldLabel str' =
|
|||||||
maybe str' T.unpack . T.stripPrefix (T.pack "_") . T.pack $ str'
|
maybe str' T.unpack . T.stripPrefix (T.pack "_") . T.pack $ str'
|
||||||
|
|
||||||
|
|
||||||
pvpToVersion :: PVP -> Version
|
pvpToVersion :: MonadThrow m => PVP -> m Version
|
||||||
pvpToVersion =
|
pvpToVersion =
|
||||||
either (\_ -> error "Couldn't convert PVP to Version") id
|
either (\_ -> throwM $ ParseError "Couldn't convert PVP to Version") pure . version . prettyPVP
|
||||||
. version
|
|
||||||
. prettyPVP
|
|
||||||
|
|
||||||
|
versionToPVP :: MonadThrow m => Version -> m PVP
|
||||||
|
versionToPVP v = either (\_ -> alternative v) pure . pvp . prettyVer $ v
|
||||||
|
where
|
||||||
|
alternative :: MonadThrow m => Version -> m PVP
|
||||||
|
alternative v' = case NE.takeWhile isDigit (_vChunks v') of
|
||||||
|
[] -> throwM $ ParseError "Couldn't convert Version to PVP"
|
||||||
|
xs -> pure $ pvpFromList (unsafeDigit <$> xs)
|
||||||
|
|
||||||
|
isDigit :: VChunk -> Bool
|
||||||
|
isDigit (Digits _ :| []) = True
|
||||||
|
isDigit _ = False
|
||||||
|
|
||||||
|
unsafeDigit :: VChunk -> Int
|
||||||
|
unsafeDigit (Digits x :| []) = fromIntegral x
|
||||||
|
unsafeDigit _ = error "unsafeDigit: wrong input"
|
||||||
|
|
||||||
|
pvpFromList :: [Int] -> PVP
|
||||||
|
pvpFromList = PVP . NE.fromList . fmap fromIntegral
|
||||||
|
|
||||||
-- | Safe 'decodeUtf8With'. Replaces an invalid input byte with
|
-- | Safe 'decodeUtf8With'. Replaces an invalid input byte with
|
||||||
-- the Unicode replacement character U+FFFD.
|
-- the Unicode replacement character U+FFFD.
|
||||||
@@ -508,6 +528,10 @@ recover action =
|
|||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
|
||||||
|
copyFileE :: (CopyError :< xs, MonadCatch m, MonadIO m) => FilePath -> FilePath -> Excepts xs m ()
|
||||||
|
copyFileE from = handleIO (throwE . CopyError . show) . liftIO . copyFile from
|
||||||
|
|
||||||
|
|
||||||
-- | Gathering monoidal values
|
-- | Gathering monoidal values
|
||||||
--
|
--
|
||||||
-- >>> traverseFold (pure . (:["0"])) ["1","2"]
|
-- >>> traverseFold (pure . (:["0"])) ["1","2"]
|
||||||
@@ -528,6 +552,8 @@ forFold = \t -> (`traverseFold` t)
|
|||||||
--
|
--
|
||||||
-- >>> stripNewline "foo\n\n\n"
|
-- >>> stripNewline "foo\n\n\n"
|
||||||
-- "foo"
|
-- "foo"
|
||||||
|
-- >>> stripNewline "foo\n\n\nfoo"
|
||||||
|
-- "foofoo"
|
||||||
-- >>> stripNewline "foo\r"
|
-- >>> stripNewline "foo\r"
|
||||||
-- "foo"
|
-- "foo"
|
||||||
-- >>> stripNewline "foo"
|
-- >>> stripNewline "foo"
|
||||||
@@ -539,10 +565,29 @@ stripNewline :: String -> String
|
|||||||
stripNewline = filter (`notElem` "\n\r")
|
stripNewline = filter (`notElem` "\n\r")
|
||||||
|
|
||||||
|
|
||||||
|
-- | Strip @\\r@ and @\\n@ from end of 'String'.
|
||||||
|
--
|
||||||
|
-- >>> stripNewlineEnd "foo\n\n\n"
|
||||||
|
-- "foo"
|
||||||
|
-- >>> stripNewlineEnd "foo\n\n\nfoo"
|
||||||
|
-- "foo\n\n\nfoo"
|
||||||
|
-- >>> stripNewlineEnd "foo\r"
|
||||||
|
-- "foo"
|
||||||
|
-- >>> stripNewlineEnd "foo"
|
||||||
|
-- "foo"
|
||||||
|
--
|
||||||
|
-- prop> \t -> stripNewlineEnd (t <> "\n") === stripNewlineEnd t
|
||||||
|
-- prop> \t -> not (any (isNewLine . c2w) t) ==> stripNewlineEnd t == t
|
||||||
|
stripNewlineEnd :: String -> String
|
||||||
|
stripNewlineEnd = dropWhileEnd (`elem` "\n\r")
|
||||||
|
|
||||||
|
|
||||||
-- | Strip @\\r@ and @\\n@ from 'Text's
|
-- | Strip @\\r@ and @\\n@ from 'Text's
|
||||||
--
|
--
|
||||||
-- >>> stripNewline' "foo\n\n\n"
|
-- >>> stripNewline' "foo\n\n\n"
|
||||||
-- "foo"
|
-- "foo"
|
||||||
|
-- >>> stripNewline' "foo\n\n\nfoo"
|
||||||
|
-- "foofoo"
|
||||||
-- >>> stripNewline' "foo\r"
|
-- >>> stripNewline' "foo\r"
|
||||||
-- "foo"
|
-- "foo"
|
||||||
-- >>> stripNewline' "foo"
|
-- >>> stripNewline' "foo"
|
||||||
|
|||||||
43
lib/System/Console/Terminal/Common.hs
Normal file
43
lib/System/Console/Terminal/Common.hs
Normal file
@@ -0,0 +1,43 @@
|
|||||||
|
{-# LANGUAGE CPP #-}
|
||||||
|
{-# LANGUAGE DeriveDataTypeable #-}
|
||||||
|
{-# LANGUAGE DeriveTraversable #-}
|
||||||
|
|
||||||
|
#if __GLASGOW_HASKELL__ >= 702
|
||||||
|
#define LANGUAGE_DeriveGeneric
|
||||||
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
#endif
|
||||||
|
|
||||||
|
module System.Console.Terminal.Common
|
||||||
|
( Window(..)
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Data.Data (Typeable, Data)
|
||||||
|
|
||||||
|
#if __GLASGOW_HASKELL__ < 710
|
||||||
|
import Data.Foldable (Foldable)
|
||||||
|
import Data.Traversable (Traversable)
|
||||||
|
#endif
|
||||||
|
|
||||||
|
#ifdef LANGUAGE_DeriveGeneric
|
||||||
|
import GHC.Generics
|
||||||
|
( Generic
|
||||||
|
#if __GLASGOW_HASKELL__ >= 706
|
||||||
|
, Generic1
|
||||||
|
#endif
|
||||||
|
)
|
||||||
|
#endif
|
||||||
|
|
||||||
|
-- | Terminal window width and height
|
||||||
|
data Window a = Window
|
||||||
|
{ height :: !a
|
||||||
|
, width :: !a
|
||||||
|
} deriving
|
||||||
|
( Show, Eq, Read, Data, Typeable
|
||||||
|
, Foldable, Functor, Traversable
|
||||||
|
#ifdef LANGUAGE_DeriveGeneric
|
||||||
|
, Generic
|
||||||
|
#if __GLASGOW_HASKELL__ >= 706
|
||||||
|
, Generic1
|
||||||
|
#endif
|
||||||
|
#endif
|
||||||
|
)
|
||||||
65
lib/System/Console/Terminal/Posix.hsc
Normal file
65
lib/System/Console/Terminal/Posix.hsc
Normal file
@@ -0,0 +1,65 @@
|
|||||||
|
{-# LANGUAGE CApiFFI #-}
|
||||||
|
|
||||||
|
module System.Console.Terminal.Posix
|
||||||
|
( size, fdSize, hSize
|
||||||
|
) where
|
||||||
|
|
||||||
|
import System.Console.Terminal.Common
|
||||||
|
import Control.Exception (catch)
|
||||||
|
import Data.Typeable (cast)
|
||||||
|
import Foreign
|
||||||
|
import Foreign.C.Error
|
||||||
|
import Foreign.C.Types
|
||||||
|
import GHC.IO.FD (FD(FD, fdFD))
|
||||||
|
import GHC.IO.Handle.Internals (withHandle_)
|
||||||
|
import GHC.IO.Handle.Types (Handle, Handle__(Handle__, haDevice))
|
||||||
|
#if defined(__GLASGOW_HASKELL__) && (__GLASGOW_HASKELL__ < 706)
|
||||||
|
import Prelude hiding (catch)
|
||||||
|
#endif
|
||||||
|
import System.Posix.Types (Fd(Fd))
|
||||||
|
|
||||||
|
#include <sys/ioctl.h>
|
||||||
|
#include <unistd.h>
|
||||||
|
|
||||||
|
|
||||||
|
#let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t (y__); }, y__)
|
||||||
|
|
||||||
|
|
||||||
|
-- Interesting part of @struct winsize@
|
||||||
|
data CWin = CWin CUShort CUShort
|
||||||
|
|
||||||
|
instance Storable CWin where
|
||||||
|
sizeOf _ = (#size struct winsize)
|
||||||
|
alignment _ = (#alignment struct winsize)
|
||||||
|
peek ptr = do
|
||||||
|
row <- (#peek struct winsize, ws_row) ptr
|
||||||
|
col <- (#peek struct winsize, ws_col) ptr
|
||||||
|
return $ CWin row col
|
||||||
|
poke ptr (CWin row col) = do
|
||||||
|
(#poke struct winsize, ws_row) ptr row
|
||||||
|
(#poke struct winsize, ws_col) ptr col
|
||||||
|
|
||||||
|
|
||||||
|
fdSize :: Integral n => Fd -> IO (Maybe (Window n))
|
||||||
|
fdSize (Fd fd) = with (CWin 0 0) $ \ws -> do
|
||||||
|
_ <- throwErrnoIfMinus1 "ioctl" $
|
||||||
|
ioctl fd (#const TIOCGWINSZ) ws
|
||||||
|
CWin row col <- peek ws
|
||||||
|
return . Just $ Window (fromIntegral row) (fromIntegral col)
|
||||||
|
`catch`
|
||||||
|
handler
|
||||||
|
where
|
||||||
|
handler :: IOError -> IO (Maybe (Window h))
|
||||||
|
handler _ = return Nothing
|
||||||
|
|
||||||
|
foreign import capi "sys/ioctl.h ioctl"
|
||||||
|
ioctl :: CInt -> CULong -> Ptr CWin -> IO CInt
|
||||||
|
|
||||||
|
size :: Integral n => IO (Maybe (Window n))
|
||||||
|
size = fdSize (Fd (#const STDOUT_FILENO))
|
||||||
|
|
||||||
|
hSize :: Integral n => Handle -> IO (Maybe (Window n))
|
||||||
|
hSize h = withHandle_ "hSize" h $ \Handle__ { haDevice = dev } ->
|
||||||
|
case cast dev of
|
||||||
|
Nothing -> return Nothing
|
||||||
|
Just FD { fdFD = fd } -> fdSize (Fd fd)
|
||||||
@@ -21,7 +21,7 @@
|
|||||||
|
|
||||||
plat="$(uname -s)"
|
plat="$(uname -s)"
|
||||||
arch=$(uname -m)
|
arch=$(uname -m)
|
||||||
ghver="0.1.16.2"
|
ghver="0.1.17.1"
|
||||||
base_url="https://downloads.haskell.org/~ghcup"
|
base_url="https://downloads.haskell.org/~ghcup"
|
||||||
|
|
||||||
export GHCUP_SKIP_UPDATE_CHECK=yes
|
export GHCUP_SKIP_UPDATE_CHECK=yes
|
||||||
@@ -52,41 +52,57 @@ esac
|
|||||||
|
|
||||||
|
|
||||||
die() {
|
die() {
|
||||||
(>&2 printf "\\033[0;31m%s\\033[0m\\n" "$1")
|
if [ -n "${NO_COLOR}" ] ; then
|
||||||
|
(>&2 printf "%s\\n" "$1")
|
||||||
|
else
|
||||||
|
(>&2 printf "\\033[0;31m%s\\033[0m\\n" "$1")
|
||||||
|
fi
|
||||||
exit 2
|
exit 2
|
||||||
}
|
}
|
||||||
|
|
||||||
warn() {
|
warn() {
|
||||||
case "${plat}" in
|
if [ -n "${NO_COLOR}" ] ; then
|
||||||
MSYS*|MINGW*)
|
printf "%s\\n" "$1"
|
||||||
echo -e "\\033[0;35m$1\\033[0m"
|
else
|
||||||
;;
|
case "${plat}" in
|
||||||
*)
|
MSYS*|MINGW*)
|
||||||
printf "\\033[0;35m%s\\033[0m\\n" "$1"
|
echo -e "\\033[0;35m$1\\033[0m"
|
||||||
;;
|
;;
|
||||||
esac
|
*)
|
||||||
|
printf "\\033[0;35m%s\\033[0m\\n" "$1"
|
||||||
|
;;
|
||||||
|
esac
|
||||||
|
fi
|
||||||
}
|
}
|
||||||
|
|
||||||
yellow() {
|
yellow() {
|
||||||
case "${plat}" in
|
if [ -n "${NO_COLOR}" ] ; then
|
||||||
MSYS*|MINGW*)
|
printf "%s\\n" "$1"
|
||||||
echo -e "\\033[0;33m$1\\033[0m"
|
else
|
||||||
;;
|
case "${plat}" in
|
||||||
*)
|
MSYS*|MINGW*)
|
||||||
printf "\\033[0;33m%s\\033[0m\\n" "$1"
|
echo -e "\\033[0;33m$1\\033[0m"
|
||||||
;;
|
;;
|
||||||
esac
|
*)
|
||||||
|
printf "\\033[0;33m%s\\033[0m\\n" "$1"
|
||||||
|
;;
|
||||||
|
esac
|
||||||
|
fi
|
||||||
}
|
}
|
||||||
|
|
||||||
green() {
|
green() {
|
||||||
case "${plat}" in
|
if [ -n "${NO_COLOR}" ] ; then
|
||||||
MSYS*|MINGW*)
|
printf "%s\\n" "$1"
|
||||||
echo -e "\\033[0;32m$1\\033[0m"
|
else
|
||||||
;;
|
case "${plat}" in
|
||||||
*)
|
MSYS*|MINGW*)
|
||||||
printf "\\033[0;32m%s\\033[0m\\n" "$1"
|
echo -e "\\033[0;32m$1\\033[0m"
|
||||||
;;
|
;;
|
||||||
esac
|
*)
|
||||||
|
printf "\\033[0;32m%s\\033[0m\\n" "$1"
|
||||||
|
;;
|
||||||
|
esac
|
||||||
|
fi
|
||||||
}
|
}
|
||||||
|
|
||||||
edo() {
|
edo() {
|
||||||
|
|||||||
@@ -4,9 +4,6 @@ packages:
|
|||||||
- .
|
- .
|
||||||
|
|
||||||
extra-deps:
|
extra-deps:
|
||||||
- git: https://github.com/bgamari/terminal-size
|
|
||||||
commit: 34ea816bd63f75f800eedac12c6908c6f3736036
|
|
||||||
|
|
||||||
- git: https://github.com/hasufell/libarchive
|
- git: https://github.com/hasufell/libarchive
|
||||||
commit: 8587aab78dd515928024ecd82c8f215e06db85cd
|
commit: 8587aab78dd515928024ecd82c8f215e06db85cd
|
||||||
|
|
||||||
|
|||||||
Reference in New Issue
Block a user