| Copyright | (c) Julian Ospald 2020 | 
|---|---|
| License | LGPL-3.0 | 
| Maintainer | hasufell@hasufell.de | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
GHCup.Types
Contents
Description
Synopsis
- data LoggerConfig = LoggerConfig {
- lcPrintDebug :: Bool
 - consoleOutter :: Text -> IO ()
 - fileOutter :: Text -> IO ()
 - fancyColors :: Bool
 
 - data LogLevel
 - data VersionRange
 - data VersionCmp
 - data GitBranch = GitBranch {}
 - data GHCTargetVersion = GHCTargetVersion {
- _tvTarget :: Maybe Text
 - _tvVersion :: Version
 
 - data PlatformRequest = PlatformRequest {}
 - data PlatformResult = PlatformResult {}
 - data SetGHC
 - data DebugInfo = DebugInfo {}
 - data GPGSetting
 - data Downloader
 - data KeepDirs
 - data Dirs = Dirs {}
 - data Settings = Settings {
- cache :: Bool
 - noVerify :: Bool
 - keepDirs :: KeepDirs
 - downloader :: Downloader
 - verbose :: Bool
 - urlSource :: URLSource
 - noNetwork :: Bool
 - gpgSetting :: GPGSetting
 - noColor :: Bool
 
 - data LeanAppState = LeanAppState {}
 - data AppState = AppState {}
 - data KeyBindings = KeyBindings {
- bUp :: Key
 - bDown :: Key
 - bQuit :: Key
 - bInstall :: Key
 - bUninstall :: Key
 - bSet :: Key
 - bChangelog :: Key
 - bShowAllVersions :: Key
 - bShowAllTools :: Key
 
 - data UserKeyBindings = UserKeyBindings {}
 - data UserSettings = UserSettings {}
 - data URLSource
 - data TarDir
 - data DownloadInfo = DownloadInfo {}
 - data LinuxDistro
 - data Platform
- = Linux LinuxDistro
 - | Darwin
 - | FreeBSD
 - | Windows
 
 - data Architecture
 - data Tag
- = Latest
 - | Recommended
 - | Prerelease
 - | Base PVP
 - | Old
 - | UnknownTag String
 
 - data VersionInfo = VersionInfo {}
 - data GlobalTool = ShimGen
 - data Tool
 - type PlatformVersionSpec = Map (Maybe VersionRange) DownloadInfo
 - type PlatformSpec = Map Platform PlatformVersionSpec
 - type ArchitectureSpec = Map Architecture PlatformSpec
 - type ToolVersionSpec = Map Version VersionInfo
 - type GHCupDownloads = Map Tool ToolVersionSpec
 - data Requirements = Requirements {
- _distroPKGs :: [Text]
 - _notes :: Text
 
 - type PlatformReqVersionSpec = Map (Maybe VersionRange) Requirements
 - type PlatformReqSpec = Map Platform PlatformReqVersionSpec
 - type ToolReqVersionSpec = Map (Maybe Version) PlatformReqSpec
 - type ToolRequirements = Map Tool ToolReqVersionSpec
 - data GHCupInfo = GHCupInfo {}
 - data Key
 - tagToString :: Tag -> String
 - archToString :: Architecture -> String
 - platformToString :: Platform -> String
 - distroToString :: LinuxDistro -> String
 - defaultUserSettings :: UserSettings
 - fromSettings :: Settings -> Maybe KeyBindings -> UserSettings
 - defaultKeyBindings :: KeyBindings
 - platResToString :: PlatformResult -> String
 - pfReqToString :: PlatformRequest -> String
 - mkTVer :: Version -> GHCTargetVersion
 - tVerToText :: GHCTargetVersion -> Text
 
Documentation
data LoggerConfig Source #
Constructors
| LoggerConfig | |
Fields 
  | |
Instances
| Show LoggerConfig Source # | |
Defined in GHCup.Types Methods showsPrec :: Int -> LoggerConfig -> ShowS # show :: LoggerConfig -> String # showList :: [LoggerConfig] -> ShowS #  | |
| NFData LoggerConfig Source # | |
Defined in GHCup.Types Methods rnf :: LoggerConfig -> () #  | |
data VersionRange Source #
A version range. Supports && and ||, but not arbitrary combinations. This is a little simplified.
Constructors
| SimpleRange (NonEmpty VersionCmp) | |
| OrRange (NonEmpty VersionCmp) VersionRange | 
Instances
data VersionCmp Source #
A comparator and a version.
Constructors
| VR_gt Versioning | |
| VR_gteq Versioning | |
| VR_lt Versioning | |
| VR_lteq Versioning | |
| VR_eq Versioning | 
Instances
Instances
| Eq GitBranch Source # | |
| Ord GitBranch Source # | |
| Show GitBranch Source # | |
data GHCTargetVersion Source #
A GHC identified by the target platform triple and the version.
Constructors
| GHCTargetVersion | |
Fields 
  | |
Instances
data PlatformRequest Source #
Constructors
| PlatformRequest | |
Fields 
  | |
Instances
data PlatformResult Source #
Constructors
| PlatformResult | |
Fields  | |
Instances
Constructors
| SetGHCOnly | unversioned   | 
| SetGHC_XY | ghc-x.y  | 
| SetGHC_XYZ | ghc-x.y.z  | 
Constructors
| DebugInfo | |
Fields 
  | |
data GPGSetting Source #
Instances
data Downloader Source #
Instances
Instances
| Eq KeepDirs Source # | |
| Ord KeepDirs Source # | |
Defined in GHCup.Types  | |
| Show KeepDirs Source # | |
| Generic KeepDirs Source # | |
| NFData KeepDirs Source # | |
Defined in GHCup.Types  | |
| FromJSON KeepDirs Source # | |
| ToJSON KeepDirs Source # | |
Defined in GHCup.Types.JSON  | |
| type Rep KeepDirs Source # | |
Defined in GHCup.Types type Rep KeepDirs = D1 ('MetaData "KeepDirs" "GHCup.Types" "ghcup-0.1.17.2-Ahtg9kL7JBD8qp8VPp2UR7" 'False) (C1 ('MetaCons "Always" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Errors" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Never" 'PrefixI 'False) (U1 :: Type -> Type)))  | |
Constructors
| Dirs | |
Instances
Constructors
| Settings | |
Fields 
  | |
Instances
data LeanAppState Source #
Constructors
| LeanAppState | |
Fields 
  | |
Instances
Constructors
| AppState | |
Fields 
  | |
Instances
| Show AppState Source # | |
| Generic AppState Source # | |
| NFData AppState Source # | |
Defined in GHCup.Types  | |
| type Rep AppState Source # | |
Defined in GHCup.Types type Rep AppState = D1 ('MetaData "AppState" "GHCup.Types" "ghcup-0.1.17.2-Ahtg9kL7JBD8qp8VPp2UR7" 'False) (C1 ('MetaCons "AppState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "settings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Settings) :*: (S1 ('MetaSel ('Just "dirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Dirs) :*: S1 ('MetaSel ('Just "keyBindings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyBindings))) :*: (S1 ('MetaSel ('Just "ghcupInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GHCupInfo) :*: (S1 ('MetaSel ('Just "pfreq") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PlatformRequest) :*: S1 ('MetaSel ('Just "loggerConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LoggerConfig)))))  | |
data KeyBindings Source #
Constructors
| KeyBindings | |
Fields 
  | |
Instances
data UserKeyBindings Source #
Constructors
| UserKeyBindings | |
Instances
data UserSettings Source #
Constructors
| UserSettings | |
Fields 
  | |
Instances
Where to fetch GHCupDownloads from.
Constructors
| GHCupURL | |
| OwnSource URI | |
| OwnSpec GHCupInfo | |
| AddSource (Either GHCupInfo URI) | merge with GHCupURL  | 
Instances
| Show URLSource Source # | |
| Generic URLSource Source # | |
| NFData URLSource Source # | |
Defined in GHCup.Types  | |
| FromJSON URLSource Source # | |
| ToJSON URLSource Source # | |
Defined in GHCup.Types.JSON  | |
| type Rep URLSource Source # | |
Defined in GHCup.Types type Rep URLSource = D1 ('MetaData "URLSource" "GHCup.Types" "ghcup-0.1.17.2-Ahtg9kL7JBD8qp8VPp2UR7" 'False) ((C1 ('MetaCons "GHCupURL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OwnSource" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 URI))) :+: (C1 ('MetaCons "OwnSpec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GHCupInfo)) :+: C1 ('MetaCons "AddSource" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Either GHCupInfo URI)))))  | |
How to descend into a tar archive.
Instances
| Eq TarDir Source # | |
| Ord TarDir Source # | |
| Show TarDir Source # | |
| Generic TarDir Source # | |
| NFData TarDir Source # | |
Defined in GHCup.Types  | |
| FromJSON TarDir Source # | |
| ToJSON TarDir Source # | |
Defined in GHCup.Types.JSON  | |
| Pretty TarDir Source # | |
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> TarDir -> Doc # pPrintList :: PrettyLevel -> [TarDir] -> Doc #  | |
| type Rep TarDir Source # | |
Defined in GHCup.Types type Rep TarDir = D1 ('MetaData "TarDir" "GHCup.Types" "ghcup-0.1.17.2-Ahtg9kL7JBD8qp8VPp2UR7" 'False) (C1 ('MetaCons "RealDir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FilePath)) :+: C1 ('MetaCons "RegexDir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String)))  | |
data DownloadInfo Source #
An encapsulation of a download. This can be used to download, extract and install a tool.
Instances
data LinuxDistro Source #
Constructors
| Debian | |
| Ubuntu | |
| Mint | |
| Fedora | |
| CentOS | |
| RedHat | |
| Alpine | |
| AmazonLinux | |
| Gentoo | |
| Exherbo | |
| UnknownLinux | must exit  | 
Instances
Constructors
| Linux LinuxDistro | must exit  | 
| Darwin | must exit  | 
| FreeBSD | |
| Windows | must exit  | 
Instances
data Architecture Source #
Instances
A tag. These are currently attached to a version of a tool.
Constructors
| Latest | |
| Recommended | |
| Prerelease | |
| Base PVP | |
| Old | old versions are hidden by default in TUI  | 
| UnknownTag String | used for upwardscompat  | 
Instances
data VersionInfo Source #
All necessary information of a tool version, including source download and per-architecture downloads.
Constructors
| VersionInfo | |
Fields 
  | |
Instances
data GlobalTool Source #
Constructors
| ShimGen | 
Instances
An installable tool.
Instances
| Bounded Tool Source # | |
| Enum Tool Source # | |
| Eq Tool Source # | |
| Ord Tool Source # | |
| Show Tool Source # | |
| Generic Tool Source # | |
| NFData Tool Source # | |
Defined in GHCup.Types  | |
| FromJSON Tool Source # | |
| ToJSON Tool Source # | |
Defined in GHCup.Types.JSON  | |
| ToJSONKey Tool Source # | |
Defined in GHCup.Types.JSON  | |
| FromJSONKey Tool Source # | |
Defined in GHCup.Types.JSON  | |
| Pretty Tool Source # | |
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> Tool -> Doc # pPrintList :: PrettyLevel -> [Tool] -> Doc #  | |
| type Rep Tool Source # | |
Defined in GHCup.Types type Rep Tool = D1 ('MetaData "Tool" "GHCup.Types" "ghcup-0.1.17.2-Ahtg9kL7JBD8qp8VPp2UR7" 'False) ((C1 ('MetaCons "GHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cabal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GHCup" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HLS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Stack" 'PrefixI 'False) (U1 :: Type -> Type))))  | |
type PlatformVersionSpec = Map (Maybe VersionRange) DownloadInfo Source #
type ToolVersionSpec = Map Version VersionInfo Source #
type GHCupDownloads = Map Tool ToolVersionSpec Source #
Description of all binary and source downloads. This is a tree of nested maps.
data Requirements Source #
Constructors
| Requirements | |
Fields 
  | |
Instances
type ToolReqVersionSpec = Map (Maybe Version) PlatformReqSpec Source #
type ToolRequirements = Map Tool ToolReqVersionSpec Source #
Constructors
| GHCupInfo | |
Instances
| Show GHCupInfo Source # | |
| Generic GHCupInfo Source # | |
| NFData GHCupInfo Source # | |
Defined in GHCup.Types  | |
| FromJSON GHCupInfo Source # | |
| ToJSON GHCupInfo Source # | |
Defined in GHCup.Types.JSON  | |
| type Rep GHCupInfo Source # | |
Defined in GHCup.Types type Rep GHCupInfo = D1 ('MetaData "GHCupInfo" "GHCup.Types" "ghcup-0.1.17.2-Ahtg9kL7JBD8qp8VPp2UR7" 'False) (C1 ('MetaCons "GHCupInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "_toolRequirements") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ToolRequirements) :*: (S1 ('MetaSel ('Just "_ghcupDownloads") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GHCupDownloads) :*: S1 ('MetaSel ('Just "_globalTools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map GlobalTool DownloadInfo)))))  | |
Constructors
| KEsc | |
| KChar Char | |
| KBS | |
| KEnter | |
| KLeft | |
| KRight | |
| KUp | |
| KDown | |
| KUpLeft | |
| KUpRight | |
| KDownLeft | |
| KDownRight | |
| KCenter | |
| KFun Int | |
| KBackTab | |
| KPrtScr | |
| KPause | |
| KIns | |
| KHome | |
| KPageUp | |
| KDel | |
| KEnd | |
| KPageDown | |
| KBegin | |
| KMenu | 
Instances
tagToString :: Tag -> String Source #
archToString :: Architecture -> String Source #
platformToString :: Platform -> String Source #
distroToString :: LinuxDistro -> String Source #
fromSettings :: Settings -> Maybe KeyBindings -> UserSettings Source #
mkTVer :: Version -> GHCTargetVersion Source #
tVerToText :: GHCTargetVersion -> Text Source #
Orphan instances
| Pretty Versioning Source # | |
Methods pPrintPrec :: PrettyLevel -> Rational -> Versioning -> Doc # pPrint :: Versioning -> Doc # pPrintList :: PrettyLevel -> [Versioning] -> Doc #  | |
| Pretty Version Source # | |
Methods pPrintPrec :: PrettyLevel -> Rational -> Version -> Doc # pPrintList :: PrettyLevel -> [Version] -> Doc #  | |
| Show (IO ()) Source # | |
| NFData (URIRef Absolute) Source # | |
| Show (a -> b) Source # | |