Improve documentation
This commit is contained in:
		
							parent
							
								
									ec6bbdbf06
								
							
						
					
					
						commit
						826900cc41
					
				
							
								
								
									
										75
									
								
								lib/GHCup.hs
									
									
									
									
									
								
							
							
						
						
									
										75
									
								
								lib/GHCup.hs
									
									
									
									
									
								
							@ -11,6 +11,21 @@
 | 
				
			|||||||
{-# LANGUAGE TypeFamilies          #-}
 | 
					{-# LANGUAGE TypeFamilies          #-}
 | 
				
			||||||
{-# LANGUAGE ViewPatterns          #-}
 | 
					{-# LANGUAGE ViewPatterns          #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup
 | 
				
			||||||
 | 
					Description : GHCup installation functions
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					This module contains the main functions that correspond
 | 
				
			||||||
 | 
					to the command line interface, like installation, listing versions
 | 
				
			||||||
 | 
					and so on.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					These are the entry points.
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup where
 | 
					module GHCup where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -76,7 +91,8 @@ import qualified Data.Text.Encoding            as E
 | 
				
			|||||||
    -------------------------
 | 
					    -------------------------
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Like 'installGHCBin', except takes the 'DownloadInfo' as
 | 
				
			||||||
 | 
					-- argument instead of looking it up from 'GHCupDownloads'.
 | 
				
			||||||
installGHCBindist :: ( MonadFail m
 | 
					installGHCBindist :: ( MonadFail m
 | 
				
			||||||
                     , MonadMask m
 | 
					                     , MonadMask m
 | 
				
			||||||
                     , MonadCatch m
 | 
					                     , MonadCatch m
 | 
				
			||||||
@ -85,9 +101,9 @@ installGHCBindist :: ( MonadFail m
 | 
				
			|||||||
                     , MonadResource m
 | 
					                     , MonadResource m
 | 
				
			||||||
                     , MonadIO m
 | 
					                     , MonadIO m
 | 
				
			||||||
                     )
 | 
					                     )
 | 
				
			||||||
              => DownloadInfo
 | 
					                  => DownloadInfo    -- ^ where/how to download
 | 
				
			||||||
              -> Version
 | 
					                  -> Version         -- ^ the version to install
 | 
				
			||||||
              -> PlatformRequest
 | 
					                  -> PlatformRequest -- ^ the platform to install on
 | 
				
			||||||
                  -> Excepts
 | 
					                  -> Excepts
 | 
				
			||||||
                       '[ AlreadyInstalled
 | 
					                       '[ AlreadyInstalled
 | 
				
			||||||
                        , BuildFailed
 | 
					                        , BuildFailed
 | 
				
			||||||
@ -149,6 +165,11 @@ installGHCBindist dlinfo ver (PlatformRequest {..}) = do
 | 
				
			|||||||
    | otherwise = []
 | 
					    | otherwise = []
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Installs GHC into @~\/.ghcup\/ghc/\<ver\>@ and places the
 | 
				
			||||||
 | 
					-- following symlinks in @~\/.ghcup\/bin@:
 | 
				
			||||||
 | 
					--
 | 
				
			||||||
 | 
					--   * @ghc-x.y.z -> ..\/ghc\/x.y.z\/bin/ghc@
 | 
				
			||||||
 | 
					--   * @ghc-x.y   -> ..\/ghc\/x.y.z\/bin/ghc@ (if x.y.z is the latest x.y version)
 | 
				
			||||||
installGHCBin :: ( MonadFail m
 | 
					installGHCBin :: ( MonadFail m
 | 
				
			||||||
                 , MonadMask m
 | 
					                 , MonadMask m
 | 
				
			||||||
                 , MonadCatch m
 | 
					                 , MonadCatch m
 | 
				
			||||||
@ -157,9 +178,9 @@ installGHCBin :: ( MonadFail m
 | 
				
			|||||||
                 , MonadResource m
 | 
					                 , MonadResource m
 | 
				
			||||||
                 , MonadIO m
 | 
					                 , MonadIO m
 | 
				
			||||||
                 )
 | 
					                 )
 | 
				
			||||||
              => GHCupDownloads
 | 
					              => GHCupDownloads  -- ^ the download info to look up the tarball from
 | 
				
			||||||
              -> Version
 | 
					              -> Version         -- ^ the version to install
 | 
				
			||||||
              -> PlatformRequest
 | 
					              -> PlatformRequest -- ^ the platform to install on
 | 
				
			||||||
              -> Excepts
 | 
					              -> Excepts
 | 
				
			||||||
                   '[ AlreadyInstalled
 | 
					                   '[ AlreadyInstalled
 | 
				
			||||||
                    , BuildFailed
 | 
					                    , BuildFailed
 | 
				
			||||||
@ -179,6 +200,8 @@ installGHCBin bDls ver pfreq = do
 | 
				
			|||||||
  installGHCBindist dlinfo ver pfreq
 | 
					  installGHCBindist dlinfo ver pfreq
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Like 'installCabalBin', except takes the 'DownloadInfo' as
 | 
				
			||||||
 | 
					-- argument instead of looking it up from 'GHCupDownloads'.
 | 
				
			||||||
installCabalBindist :: ( MonadMask m
 | 
					installCabalBindist :: ( MonadMask m
 | 
				
			||||||
                       , MonadCatch m
 | 
					                       , MonadCatch m
 | 
				
			||||||
                       , MonadReader Settings m
 | 
					                       , MonadReader Settings m
 | 
				
			||||||
@ -255,6 +278,9 @@ installCabalBindist dlinfo ver (PlatformRequest {..}) = do
 | 
				
			|||||||
      Overwrite
 | 
					      Overwrite
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Installs cabal into @~\/.ghcup\/bin/cabal-\<ver\> and
 | 
				
			||||||
 | 
					-- creates a default @cabal -> cabal-x.y.z.q@ symlink for
 | 
				
			||||||
 | 
					-- the latest installed version.
 | 
				
			||||||
installCabalBin :: ( MonadMask m
 | 
					installCabalBin :: ( MonadMask m
 | 
				
			||||||
                   , MonadCatch m
 | 
					                   , MonadCatch m
 | 
				
			||||||
                   , MonadReader Settings m
 | 
					                   , MonadReader Settings m
 | 
				
			||||||
@ -293,15 +319,15 @@ installCabalBin bDls ver pfreq = do
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Set GHC symlinks in ~/.ghcup/bin for the requested GHC version. The behavior depends
 | 
					-- | Set GHC symlinks in @~\/.ghcup\/bin@ for the requested GHC version. The behavior depends
 | 
				
			||||||
-- on `SetGHC`:
 | 
					-- on `SetGHC`:
 | 
				
			||||||
--
 | 
					--
 | 
				
			||||||
--   * SetGHCOnly: ~/.ghcup/bin/ghc -> ~/.ghcup/ghc/<ver>/bin/ghc
 | 
					--   * SetGHCOnly: @~\/.ghcup\/bin\/ghc -> ~\/.ghcup\/ghc\/\<ver\>\/bin\/ghc@
 | 
				
			||||||
--   * SetGHC_XY: ~/.ghcup/bin/ghc-X.Y -> ~/.ghcup/ghc/<ver>/bin/ghc
 | 
					--   * SetGHC_XY: @~\/.ghcup\/bin\/ghc-X.Y -> ~\/.ghcup\/ghc\/\<ver\>\/bin\/ghc@
 | 
				
			||||||
--   * SetGHC_XYZ: ~/.ghcup/bin/ghc-<ver> -> ~/.ghcup/ghc/<ver>/bin/ghc
 | 
					--   * SetGHC_XYZ: @~\/.ghcup\/bin\/ghc-\<ver\> -> ~\/.ghcup\/ghc\/\<ver\>\/bin\/ghc@
 | 
				
			||||||
--
 | 
					--
 | 
				
			||||||
-- Additionally creates a ~/.ghcup/share -> ~/.ghcup/ghc/<ver>/share symlink
 | 
					-- Additionally creates a @~\/.ghcup\/share -> ~\/.ghcup\/ghc\/\<ver\>\/share symlink@
 | 
				
			||||||
-- for `SetGHCOnly` constructor.
 | 
					-- for 'SetGHCOnly' constructor.
 | 
				
			||||||
setGHC :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
					setGHC :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
				
			||||||
       => GHCTargetVersion
 | 
					       => GHCTargetVersion
 | 
				
			||||||
       -> SetGHC
 | 
					       -> SetGHC
 | 
				
			||||||
@ -366,7 +392,7 @@ setGHC ver sghc = do
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Set the ~/.ghcup/bin/cabal symlink.
 | 
					-- | Set the @~\/.ghcup\/bin\/cabal@ symlink.
 | 
				
			||||||
setCabal :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
					setCabal :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
				
			||||||
         => Version
 | 
					         => Version
 | 
				
			||||||
         -> Excepts '[NotInstalled] m ()
 | 
					         -> Excepts '[NotInstalled] m ()
 | 
				
			||||||
@ -406,10 +432,13 @@ setCabal ver = do
 | 
				
			|||||||
    ------------------
 | 
					    ------------------
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Filter data type for 'listVersions'.
 | 
				
			||||||
data ListCriteria = ListInstalled
 | 
					data ListCriteria = ListInstalled
 | 
				
			||||||
                  | ListSet
 | 
					                  | ListSet
 | 
				
			||||||
                  deriving Show
 | 
					                  deriving Show
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | A list result describes a single tool version
 | 
				
			||||||
 | 
					-- and various of its properties.
 | 
				
			||||||
data ListResult = ListResult
 | 
					data ListResult = ListResult
 | 
				
			||||||
  { lTool      :: Tool
 | 
					  { lTool      :: Tool
 | 
				
			||||||
  , lVer       :: Version
 | 
					  , lVer       :: Version
 | 
				
			||||||
@ -424,6 +453,7 @@ data ListResult = ListResult
 | 
				
			|||||||
  deriving (Eq, Ord, Show)
 | 
					  deriving (Eq, Ord, Show)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Extract all available tool versions and their tags.
 | 
				
			||||||
availableToolVersions :: GHCupDownloads -> Tool -> Map.Map Version [Tag]
 | 
					availableToolVersions :: GHCupDownloads -> Tool -> Map.Map Version [Tag]
 | 
				
			||||||
availableToolVersions av tool = view
 | 
					availableToolVersions av tool = view
 | 
				
			||||||
  (at tool % non Map.empty % to (fmap (_viTags)))
 | 
					  (at tool % non Map.empty % to (fmap (_viTags)))
 | 
				
			||||||
@ -552,7 +582,11 @@ listVersions av lt criteria pfreq = do
 | 
				
			|||||||
    --------------------
 | 
					    --------------------
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | This function may throw and crash in various ways.
 | 
					-- | Delete a ghc version and all its symlinks.
 | 
				
			||||||
 | 
					--
 | 
				
			||||||
 | 
					-- This may leave GHCup without a "set" version.
 | 
				
			||||||
 | 
					-- Will try to fix the ghc-x.y symlink after removal (e.g. to an
 | 
				
			||||||
 | 
					-- older version).
 | 
				
			||||||
rmGHCVer :: (MonadThrow m, MonadLogger m, MonadIO m, MonadFail m)
 | 
					rmGHCVer :: (MonadThrow m, MonadLogger m, MonadIO m, MonadFail m)
 | 
				
			||||||
         => GHCTargetVersion
 | 
					         => GHCTargetVersion
 | 
				
			||||||
         -> Excepts '[NotInstalled] m ()
 | 
					         -> Excepts '[NotInstalled] m ()
 | 
				
			||||||
@ -591,7 +625,8 @@ rmGHCVer ver = do
 | 
				
			|||||||
    else throwE (NotInstalled GHC (ver ^. tvVersion % to prettyVer))
 | 
					    else throwE (NotInstalled GHC (ver ^. tvVersion % to prettyVer))
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | This function may throw and crash in various ways.
 | 
					-- | Delete a cabal version. Will try to fix the @cabal@ symlink
 | 
				
			||||||
 | 
					-- after removal (e.g. setting it to an older version).
 | 
				
			||||||
rmCabalVer :: (MonadThrow m, MonadLogger m, MonadIO m, MonadFail m)
 | 
					rmCabalVer :: (MonadThrow m, MonadLogger m, MonadIO m, MonadFail m)
 | 
				
			||||||
           => Version
 | 
					           => Version
 | 
				
			||||||
           -> Excepts '[NotInstalled] m ()
 | 
					           -> Excepts '[NotInstalled] m ()
 | 
				
			||||||
@ -640,6 +675,8 @@ getDebugInfo = do
 | 
				
			|||||||
    ---------------
 | 
					    ---------------
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Compile a GHC from sourc. This behaves wrt symlinks and installation
 | 
				
			||||||
 | 
					-- the same as 'installGHCBin'.
 | 
				
			||||||
compileGHC :: ( MonadMask m
 | 
					compileGHC :: ( MonadMask m
 | 
				
			||||||
              , MonadReader Settings m
 | 
					              , MonadReader Settings m
 | 
				
			||||||
              , MonadThrow m
 | 
					              , MonadThrow m
 | 
				
			||||||
@ -821,6 +858,8 @@ Stage1Only = YES|]
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Compile a cabal from sourc. This behaves wrt symlinks and installation
 | 
				
			||||||
 | 
					-- the same as 'installCabalBin'.
 | 
				
			||||||
compileCabal :: ( MonadReader Settings m
 | 
					compileCabal :: ( MonadReader Settings m
 | 
				
			||||||
                , MonadResource m
 | 
					                , MonadResource m
 | 
				
			||||||
                , MonadMask m
 | 
					                , MonadMask m
 | 
				
			||||||
@ -940,6 +979,8 @@ compileCabal dls tver bghc jobs patchdir PlatformRequest{..} = do
 | 
				
			|||||||
    ---------------------
 | 
					    ---------------------
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Upgrade ghcup and place it in @~\/.ghcup\/bin\/ghcup@,
 | 
				
			||||||
 | 
					-- if no path is provided.
 | 
				
			||||||
upgradeGHCup :: ( MonadMask m
 | 
					upgradeGHCup :: ( MonadMask m
 | 
				
			||||||
                , MonadReader Settings m
 | 
					                , MonadReader Settings m
 | 
				
			||||||
                , MonadCatch m
 | 
					                , MonadCatch m
 | 
				
			||||||
@ -991,7 +1032,7 @@ upgradeGHCup dls mtarget force pfreq = do
 | 
				
			|||||||
    -------------
 | 
					    -------------
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Creates ghc-x.y.z and ghc-x.y symlinks. This is used for
 | 
					-- | Creates @ghc-x.y.z@ and @ghc-x.y@ symlinks. This is used for
 | 
				
			||||||
-- both installing from source and bindist.
 | 
					-- both installing from source and bindist.
 | 
				
			||||||
postGHCInstall :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
					postGHCInstall :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
				
			||||||
               => GHCTargetVersion
 | 
					               => GHCTargetVersion
 | 
				
			||||||
 | 
				
			|||||||
@ -2,6 +2,18 @@
 | 
				
			|||||||
{-# LANGUAGE QuasiQuotes       #-}
 | 
					{-# LANGUAGE QuasiQuotes       #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Data.GHCupDownloads
 | 
				
			||||||
 | 
					Description : Download information
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					This is the module to add additional ghc/cabal etc. versions,
 | 
				
			||||||
 | 
					fix URLs, add tags, etc.
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Data.GHCupDownloads
 | 
					module GHCup.Data.GHCupDownloads
 | 
				
			||||||
  ( ghcupDownloads
 | 
					  ( ghcupDownloads
 | 
				
			||||||
  )
 | 
					  )
 | 
				
			||||||
 | 
				
			|||||||
@ -1,3 +1,12 @@
 | 
				
			|||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Data.GHCupInfo
 | 
				
			||||||
 | 
					Description :
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Data.GHCupInfo where
 | 
					module GHCup.Data.GHCupInfo where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           GHCup.Data.GHCupDownloads
 | 
					import           GHCup.Data.GHCupDownloads
 | 
				
			||||||
 | 
				
			|||||||
@ -1,6 +1,15 @@
 | 
				
			|||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
{-# LANGUAGE QuasiQuotes       #-}
 | 
					{-# LANGUAGE QuasiQuotes       #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Data.ToolRequirements
 | 
				
			||||||
 | 
					Description : Tool requirements
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Data.ToolRequirements where
 | 
					module GHCup.Data.ToolRequirements where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           GHCup.Types
 | 
					import           GHCup.Types
 | 
				
			||||||
 | 
				
			|||||||
@ -9,6 +9,23 @@
 | 
				
			|||||||
{-# LANGUAGE TypeFamilies          #-}
 | 
					{-# LANGUAGE TypeFamilies          #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Download
 | 
				
			||||||
 | 
					Description : Downloading
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					Module for handling all download related functions.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					Generally we support downloading via:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  - curl (default)
 | 
				
			||||||
 | 
					  - wget
 | 
				
			||||||
 | 
					  - internal downloader (only when compiled)
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Download where
 | 
					module GHCup.Download where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
#if defined(INTERNAL_DOWNLOADER)
 | 
					#if defined(INTERNAL_DOWNLOADER)
 | 
				
			||||||
 | 
				
			|||||||
@ -3,6 +3,15 @@
 | 
				
			|||||||
{-# LANGUAGE StandaloneDeriving #-}
 | 
					{-# LANGUAGE StandaloneDeriving #-}
 | 
				
			||||||
{-# LANGUAGE DataKinds #-}
 | 
					{-# LANGUAGE DataKinds #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Errors
 | 
				
			||||||
 | 
					Description : GHCup error types
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Errors where
 | 
					module GHCup.Errors where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           GHCup.Types
 | 
					import           GHCup.Types
 | 
				
			||||||
 | 
				
			|||||||
@ -6,6 +6,15 @@
 | 
				
			|||||||
{-# LANGUAGE TemplateHaskell       #-}
 | 
					{-# LANGUAGE TemplateHaskell       #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Plaform
 | 
				
			||||||
 | 
					Description : Retrieving platform information
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Platform where
 | 
					module GHCup.Platform where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
				
			|||||||
@ -1,5 +1,14 @@
 | 
				
			|||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Requirements
 | 
				
			||||||
 | 
					Description : Requirements utilities
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Requirements where
 | 
					module GHCup.Requirements where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           GHCup.Types
 | 
					import           GHCup.Types
 | 
				
			||||||
 | 
				
			|||||||
@ -2,6 +2,15 @@
 | 
				
			|||||||
{-# LANGUAGE DeriveGeneric     #-}
 | 
					{-# LANGUAGE DeriveGeneric     #-}
 | 
				
			||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Types
 | 
				
			||||||
 | 
					Description : GHCup types
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Types where
 | 
					module GHCup.Types where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           Data.Map.Strict                ( Map )
 | 
					import           Data.Map.Strict                ( Map )
 | 
				
			||||||
 | 
				
			|||||||
@ -10,6 +10,15 @@
 | 
				
			|||||||
{-# LANGUAGE TemplateHaskell       #-}
 | 
					{-# LANGUAGE TemplateHaskell       #-}
 | 
				
			||||||
{-# LANGUAGE TypeFamilies          #-}
 | 
					{-# LANGUAGE TypeFamilies          #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Types.JSON
 | 
				
			||||||
 | 
					Description : GHCup JSON types/instances
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Types.JSON where
 | 
					module GHCup.Types.JSON where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           GHCup.Types
 | 
					import           GHCup.Types
 | 
				
			||||||
 | 
				
			|||||||
@ -1,5 +1,14 @@
 | 
				
			|||||||
{-# LANGUAGE TemplateHaskell #-}
 | 
					{-# LANGUAGE TemplateHaskell #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Types.Optics
 | 
				
			||||||
 | 
					Description : GHCup optics
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Types.Optics where
 | 
					module GHCup.Types.Optics where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           GHCup.Types
 | 
					import           GHCup.Types
 | 
				
			||||||
 | 
				
			|||||||
@ -6,7 +6,18 @@
 | 
				
			|||||||
{-# LANGUAGE TemplateHaskell       #-}
 | 
					{-# LANGUAGE TemplateHaskell       #-}
 | 
				
			||||||
{-# LANGUAGE ViewPatterns          #-}
 | 
					{-# LANGUAGE ViewPatterns          #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Utils
 | 
				
			||||||
 | 
					Description : GHCup domain specific utilities
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					This module contains GHCup helpers specific to
 | 
				
			||||||
 | 
					installation and introspection of files/versions etc.
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Utils
 | 
					module GHCup.Utils
 | 
				
			||||||
  ( module GHCup.Utils.Dirs
 | 
					  ( module GHCup.Utils.Dirs
 | 
				
			||||||
  , module GHCup.Utils
 | 
					  , module GHCup.Utils
 | 
				
			||||||
@ -93,7 +104,7 @@ ghcLinkDestination tool ver =
 | 
				
			|||||||
  "../ghc/" <> E.encodeUtf8 (prettyTVer ver) <> "/bin/" <> tool
 | 
					  "../ghc/" <> E.encodeUtf8 (prettyTVer ver) <> "/bin/" <> tool
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- e.g. ghc-8.6.5
 | 
					-- | Removes the minor GHC symlinks, e.g. ghc-8.6.5.
 | 
				
			||||||
rmMinorSymlinks :: (MonadIO m, MonadLogger m) => GHCTargetVersion -> m ()
 | 
					rmMinorSymlinks :: (MonadIO m, MonadLogger m) => GHCTargetVersion -> m ()
 | 
				
			||||||
rmMinorSymlinks GHCTargetVersion {..} = do
 | 
					rmMinorSymlinks GHCTargetVersion {..} = do
 | 
				
			||||||
  bindir <- liftIO $ ghcupBinDir
 | 
					  bindir <- liftIO $ ghcupBinDir
 | 
				
			||||||
@ -112,7 +123,7 @@ rmMinorSymlinks GHCTargetVersion {..} = do
 | 
				
			|||||||
    liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
 | 
					    liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- Removes the set ghc version for the given target, if any.
 | 
					-- | Removes the set ghc version for the given target, if any.
 | 
				
			||||||
rmPlain :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
					rmPlain :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
				
			||||||
  => Maybe Text -- ^ target
 | 
					  => Maybe Text -- ^ target
 | 
				
			||||||
        -> Excepts '[NotInstalled] m ()
 | 
					        -> Excepts '[NotInstalled] m ()
 | 
				
			||||||
@ -131,7 +142,7 @@ rmPlain target = do
 | 
				
			|||||||
    liftIO $ hideError doesNotExistErrorType $ deleteFile hdc_file
 | 
					    liftIO $ hideError doesNotExistErrorType $ deleteFile hdc_file
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- e.g. ghc-8.6
 | 
					-- | Remove the major GHC symlink, e.g. ghc-8.6.
 | 
				
			||||||
rmMajorSymlinks :: (MonadThrow m, MonadLogger m, MonadIO m)
 | 
					rmMajorSymlinks :: (MonadThrow m, MonadLogger m, MonadIO m)
 | 
				
			||||||
                => GHCTargetVersion
 | 
					                => GHCTargetVersion
 | 
				
			||||||
                -> m ()
 | 
					                -> m ()
 | 
				
			||||||
@ -162,18 +173,21 @@ rmMajorSymlinks GHCTargetVersion {..} = do
 | 
				
			|||||||
    -----------------------------------
 | 
					    -----------------------------------
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Whethe the given GHC versin is installed.
 | 
				
			||||||
ghcInstalled :: GHCTargetVersion -> IO Bool
 | 
					ghcInstalled :: GHCTargetVersion -> IO Bool
 | 
				
			||||||
ghcInstalled ver = do
 | 
					ghcInstalled ver = do
 | 
				
			||||||
  ghcdir <- ghcupGHCDir ver
 | 
					  ghcdir <- ghcupGHCDir ver
 | 
				
			||||||
  doesDirectoryExist ghcdir
 | 
					  doesDirectoryExist ghcdir
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Whether the given GHC version is installed from source.
 | 
				
			||||||
ghcSrcInstalled :: GHCTargetVersion -> IO Bool
 | 
					ghcSrcInstalled :: GHCTargetVersion -> IO Bool
 | 
				
			||||||
ghcSrcInstalled ver = do
 | 
					ghcSrcInstalled ver = do
 | 
				
			||||||
  ghcdir <- ghcupGHCDir ver
 | 
					  ghcdir <- ghcupGHCDir ver
 | 
				
			||||||
  doesFileExist (ghcdir </> ghcUpSrcBuiltFile)
 | 
					  doesFileExist (ghcdir </> ghcUpSrcBuiltFile)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Whether the given GHC version is set as the current.
 | 
				
			||||||
ghcSet :: (MonadThrow m, MonadIO m)
 | 
					ghcSet :: (MonadThrow m, MonadIO m)
 | 
				
			||||||
       => Maybe Text   -- ^ the target of the GHC version, if any
 | 
					       => Maybe Text   -- ^ the target of the GHC version, if any
 | 
				
			||||||
                       --  (e.g. armv7-unknown-linux-gnueabihf)
 | 
					                       --  (e.g. armv7-unknown-linux-gnueabihf)
 | 
				
			||||||
@ -219,6 +233,7 @@ getInstalledGHCs = do
 | 
				
			|||||||
    Left  _ -> pure $ Left f
 | 
					    Left  _ -> pure $ Left f
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Get all installed cabals, by matching on @~\/.ghcup\/bin/cabal-*@.
 | 
				
			||||||
getInstalledCabals :: IO [Either (Path Rel) Version]
 | 
					getInstalledCabals :: IO [Either (Path Rel) Version]
 | 
				
			||||||
getInstalledCabals = do
 | 
					getInstalledCabals = do
 | 
				
			||||||
  bindir <- liftIO $ ghcupBinDir
 | 
					  bindir <- liftIO $ ghcupBinDir
 | 
				
			||||||
@ -233,12 +248,14 @@ getInstalledCabals = do
 | 
				
			|||||||
  pure $ maybe vs (\x -> Right x:vs) cs
 | 
					  pure $ maybe vs (\x -> Right x:vs) cs
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Whether the given cabal version is installed.
 | 
				
			||||||
cabalInstalled :: Version -> IO Bool
 | 
					cabalInstalled :: Version -> IO Bool
 | 
				
			||||||
cabalInstalled ver = do
 | 
					cabalInstalled ver = do
 | 
				
			||||||
  vers <- fmap rights $ getInstalledCabals
 | 
					  vers <- fmap rights $ getInstalledCabals
 | 
				
			||||||
  pure $ elem ver $ vers
 | 
					  pure $ elem ver $ vers
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- Return the currently set cabal version, if any.
 | 
				
			||||||
cabalSet :: (MonadIO m, MonadThrow m) => m (Maybe Version)
 | 
					cabalSet :: (MonadIO m, MonadThrow m) => m (Maybe Version)
 | 
				
			||||||
cabalSet = do
 | 
					cabalSet = do
 | 
				
			||||||
  cabalbin <- (</> [rel|cabal|]) <$> liftIO ghcupBinDir
 | 
					  cabalbin <- (</> [rel|cabal|]) <$> liftIO ghcupBinDir
 | 
				
			||||||
@ -257,11 +274,13 @@ cabalSet = do
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    -----------------------------------------
 | 
					    -----------------------------------------
 | 
				
			||||||
    --[ Major version introspection (X.Y) ]--
 | 
					    --[ Major version introspection (X.Y) ]--
 | 
				
			||||||
    -----------------------------------------
 | 
					    -----------------------------------------
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Extract (major, minor) from any version.
 | 
				
			||||||
getMajorMinorV :: MonadThrow m => Version -> m (Int, Int)
 | 
					getMajorMinorV :: MonadThrow m => Version -> m (Int, Int)
 | 
				
			||||||
getMajorMinorV Version {..} = case _vChunks of
 | 
					getMajorMinorV Version {..} = case _vChunks of
 | 
				
			||||||
  ([Digits x] : [Digits y] : _) -> pure (fromIntegral x, fromIntegral y)
 | 
					  ([Digits x] : [Digits y] : _) -> pure (fromIntegral x, fromIntegral y)
 | 
				
			||||||
@ -415,11 +434,12 @@ urlBaseName :: MonadThrow m
 | 
				
			|||||||
urlBaseName = parseRel . snd . B.breakEnd (== _slash) . urlDecode False
 | 
					urlBaseName = parseRel . snd . B.breakEnd (== _slash) . urlDecode False
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- Get tool files from '~/.ghcup/bin/ghc/<ver>/bin/*'
 | 
					-- | Get tool files from @~\/.ghcup\/bin\/ghc\/\<ver\>\/bin\/\*@
 | 
				
			||||||
-- while ignoring *-<ver> symlinks and accounting for cross triple prefix.
 | 
					-- while ignoring @*-\<ver\>@ symlinks and accounting for cross triple prefix.
 | 
				
			||||||
--
 | 
					--
 | 
				
			||||||
-- Returns unversioned relative files, e.g.:
 | 
					-- Returns unversioned relative files, e.g.:
 | 
				
			||||||
--   ["hsc2hs","haddock","hpc","runhaskell","ghc","ghc-pkg","ghci","runghc","hp2ps"]
 | 
					--
 | 
				
			||||||
 | 
					--   - @["hsc2hs","haddock","hpc","runhaskell","ghc","ghc-pkg","ghci","runghc","hp2ps"]@
 | 
				
			||||||
ghcToolFiles :: (MonadThrow m, MonadFail m, MonadIO m)
 | 
					ghcToolFiles :: (MonadThrow m, MonadFail m, MonadIO m)
 | 
				
			||||||
             => GHCTargetVersion
 | 
					             => GHCTargetVersion
 | 
				
			||||||
             -> Excepts '[NotInstalled] m [Path Rel]
 | 
					             -> Excepts '[NotInstalled] m [Path Rel]
 | 
				
			||||||
@ -466,7 +486,7 @@ ghcToolFiles ver = do
 | 
				
			|||||||
  isHadrian = fmap (/= SymbolicLink) . getFileType
 | 
					  isHadrian = fmap (/= SymbolicLink) . getFileType
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | This file, when residing in ~/.ghcup/ghc/<ver>/ signals that
 | 
					-- | This file, when residing in @~\/.ghcup\/ghc\/\<ver\>\/@ signals that
 | 
				
			||||||
-- this GHC was built from source. It contains the build config.
 | 
					-- this GHC was built from source. It contains the build config.
 | 
				
			||||||
ghcUpSrcBuiltFile :: Path Rel
 | 
					ghcUpSrcBuiltFile :: Path Rel
 | 
				
			||||||
ghcUpSrcBuiltFile = [rel|.ghcup_src_built|]
 | 
					ghcUpSrcBuiltFile = [rel|.ghcup_src_built|]
 | 
				
			||||||
@ -504,6 +524,7 @@ applyPatches pdir ddir = do
 | 
				
			|||||||
      !? PatchFailed
 | 
					      !? PatchFailed
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | https://gitlab.haskell.org/ghc/ghc/-/issues/17353
 | 
				
			||||||
darwinNotarization :: Platform -> Path Abs -> IO (Either ProcessError ())
 | 
					darwinNotarization :: Platform -> Path Abs -> IO (Either ProcessError ())
 | 
				
			||||||
darwinNotarization Darwin path = exec
 | 
					darwinNotarization Darwin path = exec
 | 
				
			||||||
  "xattr"
 | 
					  "xattr"
 | 
				
			||||||
 | 
				
			|||||||
@ -2,6 +2,15 @@
 | 
				
			|||||||
{-# LANGUAGE QuasiQuotes           #-}
 | 
					{-# LANGUAGE QuasiQuotes           #-}
 | 
				
			||||||
{-# LANGUAGE ViewPatterns          #-}
 | 
					{-# LANGUAGE ViewPatterns          #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Utils.Dirs
 | 
				
			||||||
 | 
					Description : Definition of GHCup directories
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Utils.Dirs where
 | 
					module GHCup.Utils.Dirs where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
				
			|||||||
@ -3,6 +3,18 @@
 | 
				
			|||||||
{-# LANGUAGE FlexibleContexts  #-}
 | 
					{-# LANGUAGE FlexibleContexts  #-}
 | 
				
			||||||
{-# LANGUAGE TemplateHaskell   #-}
 | 
					{-# LANGUAGE TemplateHaskell   #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Utils.File
 | 
				
			||||||
 | 
					Description : File and unix APIs
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					This module handles file and executable handling.
 | 
				
			||||||
 | 
					Some of these functions use sophisticated logging.
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Utils.File where
 | 
					module GHCup.Utils.File where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           GHCup.Utils.Dirs
 | 
					import           GHCup.Utils.Dirs
 | 
				
			||||||
 | 
				
			|||||||
@ -1,5 +1,16 @@
 | 
				
			|||||||
{-# LANGUAGE QuasiQuotes           #-}
 | 
					{-# LANGUAGE QuasiQuotes           #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Utils.Logger
 | 
				
			||||||
 | 
					Description : logger definition
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					Here we define our main logger.
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Utils.Logger where
 | 
					module GHCup.Utils.Logger where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           GHCup.Utils
 | 
					import           GHCup.Utils
 | 
				
			||||||
 | 
				
			|||||||
@ -1,6 +1,15 @@
 | 
				
			|||||||
{-# LANGUAGE CPP                  #-}
 | 
					{-# LANGUAGE CPP                  #-}
 | 
				
			||||||
{-# LANGUAGE OverloadedStrings    #-}
 | 
					{-# LANGUAGE OverloadedStrings    #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Utils.MegaParsec
 | 
				
			||||||
 | 
					Description : MegaParsec utilities
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Utils.MegaParsec where
 | 
					module GHCup.Utils.MegaParsec where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           GHCup.Types
 | 
					import           GHCup.Types
 | 
				
			||||||
 | 
				
			|||||||
@ -8,6 +8,17 @@
 | 
				
			|||||||
{-# LANGUAGE TypeFamilies        #-}
 | 
					{-# LANGUAGE TypeFamilies        #-}
 | 
				
			||||||
{-# LANGUAGE TypeOperators       #-}
 | 
					{-# LANGUAGE TypeOperators       #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Utils.Prelude
 | 
				
			||||||
 | 
					Description : MegaParsec utilities
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					GHCup specific prelude. Lots of Excepts functionality.
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Utils.Prelude where
 | 
					module GHCup.Utils.Prelude where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           Control.Applicative
 | 
					import           Control.Applicative
 | 
				
			||||||
 | 
				
			|||||||
@ -1,25 +1,35 @@
 | 
				
			|||||||
{-# LANGUAGE TemplateHaskell #-}
 | 
					{-# LANGUAGE TemplateHaskell #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | QuasiQuoter for non-interpolated strings, texts and bytestrings.
 | 
					{-|
 | 
				
			||||||
--
 | 
					Module      : GHCup.Utils.String.QQ
 | 
				
			||||||
-- The "s" quoter contains a multi-line string with no interpolation at all,
 | 
					Description : String quasi quoters
 | 
				
			||||||
-- except that the leading newline is trimmed and carriage returns stripped.
 | 
					Copyright   : (c) Audrey Tang <audreyt@audreyt.org> 2019, Julian Ospald <hasufell@posteo.de> 2020
 | 
				
			||||||
--
 | 
					License     : GPL-3
 | 
				
			||||||
-- @
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
-- {-\# LANGUAGE QuasiQuotes #-}
 | 
					Stability   : experimental
 | 
				
			||||||
-- import Data.Text (Text)
 | 
					Portability : POSIX
 | 
				
			||||||
-- import Data.String.QQ
 | 
					
 | 
				
			||||||
-- foo :: Text -- "String", "ByteString" etc also works
 | 
					QuasiQuoter for non-interpolated strings, texts and bytestrings.
 | 
				
			||||||
-- foo = [s|
 | 
					
 | 
				
			||||||
-- Well here is a
 | 
					The "s" quoter contains a multi-line string with no interpolation at all,
 | 
				
			||||||
--     multi-line string!
 | 
					except that the leading newline is trimmed and carriage returns stripped.
 | 
				
			||||||
-- |]
 | 
					
 | 
				
			||||||
-- @
 | 
					@
 | 
				
			||||||
--
 | 
					{-\# LANGUAGE QuasiQuotes #-}
 | 
				
			||||||
-- Any instance of the IsString type is permitted.
 | 
					import Data.Text (Text)
 | 
				
			||||||
--
 | 
					import Data.String.QQ
 | 
				
			||||||
-- (For GHC versions 6, write "[$s||]" instead of "[s||]".)
 | 
					foo :: Text -- "String", "ByteString" etc also works
 | 
				
			||||||
--
 | 
					foo = [s|
 | 
				
			||||||
 | 
					Well here is a
 | 
				
			||||||
 | 
					    multi-line string!
 | 
				
			||||||
 | 
					|]
 | 
				
			||||||
 | 
					@
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					Any instance of the IsString type is permitted.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					(For GHC versions 6, write "[$s||]" instead of "[s||]".)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Utils.String.QQ
 | 
					module GHCup.Utils.String.QQ
 | 
				
			||||||
  ( s
 | 
					  ( s
 | 
				
			||||||
  )
 | 
					  )
 | 
				
			||||||
 | 
				
			|||||||
@ -7,6 +7,15 @@
 | 
				
			|||||||
{-# LANGUAGE TemplateHaskell    #-}
 | 
					{-# LANGUAGE TemplateHaskell    #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Utils.Version.QQ
 | 
				
			||||||
 | 
					Description : Version quasi-quoters
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Utils.Version.QQ where
 | 
					module GHCup.Utils.Version.QQ where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           Data.Data
 | 
					import           Data.Data
 | 
				
			||||||
 | 
				
			|||||||
@ -1,6 +1,15 @@
 | 
				
			|||||||
{-# LANGUAGE QuasiQuotes       #-}
 | 
					{-# LANGUAGE QuasiQuotes       #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{-|
 | 
				
			||||||
 | 
					Module      : GHCup.Version
 | 
				
			||||||
 | 
					Description : Static version information
 | 
				
			||||||
 | 
					Copyright   : (c) Julian Ospald, 2020
 | 
				
			||||||
 | 
					License     : GPL-3
 | 
				
			||||||
 | 
					Maintainer  : hasufell@hasufell.de
 | 
				
			||||||
 | 
					Stability   : experimental
 | 
				
			||||||
 | 
					Portability : POSIX
 | 
				
			||||||
 | 
					-}
 | 
				
			||||||
module GHCup.Version where
 | 
					module GHCup.Version where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           GHCup.Utils.Version.QQ
 | 
					import           GHCup.Utils.Version.QQ
 | 
				
			||||||
@ -15,8 +24,10 @@ import qualified Data.Text                     as T
 | 
				
			|||||||
ghcupURL :: URI
 | 
					ghcupURL :: URI
 | 
				
			||||||
ghcupURL = [uri|https://www.haskell.org/ghcup/data/ghcup-0.0.2.json|]
 | 
					ghcupURL = [uri|https://www.haskell.org/ghcup/data/ghcup-0.0.2.json|]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | The curren ghcup version.
 | 
				
			||||||
ghcUpVer :: PVP
 | 
					ghcUpVer :: PVP
 | 
				
			||||||
ghcUpVer = [pver|0.1.8|]
 | 
					ghcUpVer = [pver|0.1.8|]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | ghcup version as numeric string.
 | 
				
			||||||
numericVer :: String
 | 
					numericVer :: String
 | 
				
			||||||
numericVer = T.unpack . prettyPVP $ ghcUpVer
 | 
					numericVer = T.unpack . prettyPVP $ ghcUpVer
 | 
				
			||||||
 | 
				
			|||||||
		Loading…
	
		Reference in New Issue
	
	Block a user