Skip to content
Snippets Groups Projects
Verified Commit 5d94d0bf authored by Julian Ospald's avatar Julian Ospald :tea:
Browse files

Also check for GHC and Cabal updates on start

parent 72bcfa92
No related branches found
No related tags found
No related merge requests found
......@@ -46,6 +46,7 @@ import Language.Haskell.TH
import Options.Applicative hiding ( style )
import Options.Applicative.Help.Pretty ( text )
import Prelude hiding ( appendFile )
import Safe
import System.Console.Pretty
import System.Environment
import System.Exit
......@@ -1030,7 +1031,9 @@ printListResult lr = do
putStrLn $ formatted
checkForUpdates :: (MonadFail m, MonadLogger m) => GHCupDownloads -> m ()
checkForUpdates :: (MonadIO m, MonadFail m, MonadLogger m)
=> GHCupDownloads
-> m ()
checkForUpdates dls = do
forM_ (getLatest dls GHCup) $ \l -> do
(Right ghc_ver) <- pure $ version $ prettyPVP ghcUpVer
......@@ -1038,6 +1041,24 @@ checkForUpdates dls = do
$ $(logWarn)
[i|New GHCup version available: #{prettyVer l}. To upgrade, run 'ghcup upgrade'|]
forM_ (getLatest dls GHC) $ \l -> do
mghc_ver <- latestInstalled GHC
forM mghc_ver $ \ghc_ver ->
when (l > ghc_ver)
$ $(logWarn)
[i|New GHC version available: #{prettyVer l}. To upgrade, run 'ghcup install #{prettyVer l}'|]
forM_ (getLatest dls Cabal) $ \l -> do
mcabal_ver <- latestInstalled Cabal
forM mcabal_ver $ \cabal_ver ->
when (l > cabal_ver)
$ $(logWarn)
[i|New Cabal version available: #{prettyVer l}. To upgrade, run 'ghcup install-cabal #{prettyVer l}'|]
where
latestInstalled tool = (fmap lVer . lastMay)
<$> liftIO (listVersions dls (Just tool) (Just ListInstalled))
prettyDebugInfo :: DebugInfo -> String
prettyDebugInfo DebugInfo {..} = [i|Debug Info
......
......@@ -326,6 +326,7 @@ executable ghcup
, optparse-applicative
, pretty-terminal
, resourcet
, safe
, string-interpolate
, table-layout
, template-haskell
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment