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 Tool
- data LogLevel
- data Settings = Settings {
- cache :: Bool
- metaCache :: Integer
- metaMode :: MetaMode
- noVerify :: Bool
- keepDirs :: KeepDirs
- downloader :: Downloader
- verbose :: Bool
- urlSource :: [NewURLSource]
- noNetwork :: Bool
- gpgSetting :: GPGSetting
- noColor :: Bool
- platformOverride :: Maybe PlatformRequest
- mirrors :: DownloadMirrors
- defGHCConfOptions :: [String]
- pager :: PagerConfig
- guessVersion :: Bool
- data KeepDirs
- data LinuxDistro
- data Platform
- data VersionRange
- data MetaMode
- data VersionPattern
- data Tag
- data BuildSystem
- data Downloader
- data KeyCombination = KeyCombination {}
- data DownloadMirror = DownloadMirror {}
- data Dirs = Dirs {}
- data ProcessError
- data CapturedProcess = CapturedProcess {}
- type PromptQuestion = Text
- data PromptResponse
- data Requirements = Requirements {
- _distroPKGs :: [Text]
- _notes :: Text
- newtype MapIgnoreUnknownKeys k v = MapIgnoreUnknownKeys {
- unMapIgnoreUnknownKeys :: Map k v
- data AppState = AppState {}
- data LeanAppState = LeanAppState {}
- data DownloadInfo = DownloadInfo {}
- data GitBranch = GitBranch {}
- data GHCupInfo = GHCupInfo {}
- type ToolRequirements = Map Tool ToolReqVersionSpec
- type GHCupDownloads = Map Tool ToolVersionSpec
- type ToolReqVersionSpec = Map (Maybe Version) PlatformReqSpec
- type PlatformReqSpec = MapIgnoreUnknownKeys Platform PlatformReqVersionSpec
- type PlatformReqVersionSpec = Map (Maybe VersionRange) Requirements
- type ToolVersionSpec = Map GHCTargetVersion VersionInfo
- data GHCTargetVersion = GHCTargetVersion {
- _tvTarget :: Maybe Text
- _tvVersion :: Version
- data VersionInfo = VersionInfo {}
- type ArchitectureSpec = MapIgnoreUnknownKeys Architecture PlatformSpec
- data Architecture
- type PlatformSpec = MapIgnoreUnknownKeys Platform PlatformVersionSpec
- type PlatformVersionSpec = Map (Maybe VersionRange) DownloadInfo
- tagToString :: Tag -> String
- archToString :: Architecture -> String
- platformToString :: Platform -> String
- distroToString :: LinuxDistro -> String
- allDistros :: [LinuxDistro]
- data TarDir
- newtype DownloadMirrors = DM (Map Text DownloadMirror)
- data URLSource
- data NewURLSource
- data ChannelAlias
- channelAliasText :: ChannelAlias -> Text
- fromURLSource :: URLSource -> [NewURLSource]
- convert' :: Either (Either GHCupInfo SetupInfo) URI -> NewURLSource
- data UserSettings = UserSettings {
- uCache :: Maybe Bool
- uMetaCache :: Maybe Integer
- uMetaMode :: Maybe MetaMode
- uNoVerify :: Maybe Bool
- uVerbose :: Maybe Bool
- uKeepDirs :: Maybe KeepDirs
- uDownloader :: Maybe Downloader
- uKeyBindings :: Maybe UserKeyBindings
- uUrlSource :: Maybe URLSource
- uNoNetwork :: Maybe Bool
- uGPGSetting :: Maybe GPGSetting
- uPlatformOverride :: Maybe PlatformRequest
- uMirrors :: Maybe DownloadMirrors
- uDefGHCConfOptions :: Maybe [String]
- uPager :: Maybe PagerConfig
- uGuessVersion :: Maybe Bool
- data UserKeyBindings = UserKeyBindings {}
- data GPGSetting
- data PlatformRequest = PlatformRequest {}
- data PagerConfig = PagerConfig {}
- defaultUserSettings :: UserSettings
- fromSettings :: Settings -> Maybe KeyBindings -> UserSettings
- data KeyBindings = KeyBindings {}
- defaultKeyBindings :: KeyBindings
- data LoggerConfig = LoggerConfig {
- lcPrintDebug :: Bool
- consoleOutter :: Text -> IO ()
- fileOutter :: Text -> IO ()
- fancyColors :: Bool
- fromAppState :: AppState -> LeanAppState
- defaultPagerConfig :: PagerConfig
- allPagerConfig :: String -> PagerConfig
- defaultMetaCache :: Integer
- defaultSettings :: Settings
- data MSYS2Env
- data DebugInfo = DebugInfo {
- diDirs :: Dirs
- diArch :: Architecture
- diPlatform :: PlatformResult
- diChannels :: [(ChannelAlias, URI)]
- diShimGenURL :: URI
- data PlatformResult = PlatformResult {}
- data SetGHC
- data SetHLS
- platResToString :: PlatformResult -> String
- pfReqToString :: PlatformRequest -> String
- mkTVer :: Version -> GHCTargetVersion
- tVerToText :: GHCTargetVersion -> Text
- data VersionCmp
- data InstallDir
- data InstallDirResolved
- fromInstallDir :: InstallDirResolved -> FilePath
- isSafeDir :: InstallDirResolved -> Bool
- data ToolVersion
- data GuessMode
- data Key
- data Modifier
- data ArchiveResult
Documentation
An installable tool.
Instances
Constructors
Settings | |
Fields
|
Instances
ToJSON Settings Source # | |||||
Generic Settings Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show Settings Source # | |||||
NFData Settings Source # | |||||
Defined in GHCup.Types | |||||
type Rep Settings Source # | |||||
Defined in GHCup.Types type Rep Settings = D1 ('MetaData "Settings" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "Settings" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "cache") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "metaCache") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer)) :*: (S1 ('MetaSel ('Just "metaMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MetaMode) :*: S1 ('MetaSel ('Just "noVerify") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "keepDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeepDirs) :*: S1 ('MetaSel ('Just "downloader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Downloader)) :*: (S1 ('MetaSel ('Just "verbose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "urlSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [NewURLSource])))) :*: (((S1 ('MetaSel ('Just "noNetwork") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "gpgSetting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GPGSetting)) :*: (S1 ('MetaSel ('Just "noColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "platformOverride") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe PlatformRequest)))) :*: ((S1 ('MetaSel ('Just "mirrors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DownloadMirrors) :*: S1 ('MetaSel ('Just "defGHCConfOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [String])) :*: (S1 ('MetaSel ('Just "pager") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PagerConfig) :*: S1 ('MetaSel ('Just "guessVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))))) |
Instances
FromJSON KeepDirs Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON KeepDirs Source # | |||||
Generic KeepDirs Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show KeepDirs Source # | |||||
NFData KeepDirs Source # | |||||
Defined in GHCup.Types | |||||
Eq KeepDirs Source # | |||||
Ord KeepDirs Source # | |||||
Defined in GHCup.Types | |||||
type Rep KeepDirs Source # | |||||
Defined in GHCup.Types type Rep KeepDirs = D1 ('MetaData "KeepDirs" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" '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))) |
data LinuxDistro Source #
Constructors
Debian | |
Ubuntu | |
Mint | |
Fedora | |
CentOS | |
RedHat | |
Alpine | |
AmazonLinux | |
Rocky | |
Void | |
Gentoo | |
Exherbo | |
OpenSUSE | |
UnknownLinux |
Instances
FromJSON LinuxDistro Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON LinuxDistro Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: LinuxDistro -> Value # toEncoding :: LinuxDistro -> Encoding # toJSONList :: [LinuxDistro] -> Value # toEncodingList :: [LinuxDistro] -> Encoding # omitField :: LinuxDistro -> Bool # | |||||
Bounded LinuxDistro Source # | |||||
Defined in GHCup.Types | |||||
Enum LinuxDistro Source # | |||||
Defined in GHCup.Types Methods succ :: LinuxDistro -> LinuxDistro # pred :: LinuxDistro -> LinuxDistro # toEnum :: Int -> LinuxDistro # fromEnum :: LinuxDistro -> Int # enumFrom :: LinuxDistro -> [LinuxDistro] # enumFromThen :: LinuxDistro -> LinuxDistro -> [LinuxDistro] # enumFromTo :: LinuxDistro -> LinuxDistro -> [LinuxDistro] # enumFromThenTo :: LinuxDistro -> LinuxDistro -> LinuxDistro -> [LinuxDistro] # | |||||
Generic LinuxDistro Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show LinuxDistro Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> LinuxDistro -> ShowS # show :: LinuxDistro -> String # showList :: [LinuxDistro] -> ShowS # | |||||
NFData LinuxDistro Source # | |||||
Defined in GHCup.Types Methods rnf :: LinuxDistro -> () # | |||||
Eq LinuxDistro Source # | |||||
Defined in GHCup.Types | |||||
Ord LinuxDistro Source # | |||||
Defined in GHCup.Types Methods compare :: LinuxDistro -> LinuxDistro -> Ordering # (<) :: LinuxDistro -> LinuxDistro -> Bool # (<=) :: LinuxDistro -> LinuxDistro -> Bool # (>) :: LinuxDistro -> LinuxDistro -> Bool # (>=) :: LinuxDistro -> LinuxDistro -> Bool # max :: LinuxDistro -> LinuxDistro -> LinuxDistro # min :: LinuxDistro -> LinuxDistro -> LinuxDistro # | |||||
Pretty LinuxDistro Source # | |||||
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> LinuxDistro -> Doc # pPrint :: LinuxDistro -> Doc # pPrintList :: PrettyLevel -> [LinuxDistro] -> Doc # | |||||
type Rep LinuxDistro Source # | |||||
Defined in GHCup.Types type Rep LinuxDistro = D1 ('MetaData "LinuxDistro" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (((C1 ('MetaCons "Debian" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ubuntu" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mint" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Fedora" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CentOS" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RedHat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Alpine" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "AmazonLinux" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Rocky" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Void" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Gentoo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exherbo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OpenSUSE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownLinux" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Instances
FromJSON Platform Source # | |||||
Defined in GHCup.Types.JSON | |||||
FromJSONKey Platform Source # | |||||
Defined in GHCup.Types.JSON Methods | |||||
ToJSON Platform Source # | |||||
ToJSONKey Platform Source # | |||||
Defined in GHCup.Types.JSON | |||||
Generic Platform Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show Platform Source # | |||||
NFData Platform Source # | |||||
Defined in GHCup.Types | |||||
Eq Platform Source # | |||||
Ord Platform Source # | |||||
Defined in GHCup.Types | |||||
Pretty Platform Source # | |||||
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> Platform -> Doc # pPrintList :: PrettyLevel -> [Platform] -> Doc # | |||||
type Rep Platform Source # | |||||
Defined in GHCup.Types type Rep Platform = D1 ('MetaData "Platform" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) ((C1 ('MetaCons "Linux" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LinuxDistro)) :+: C1 ('MetaCons "Darwin" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FreeBSD" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OpenBSD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Windows" 'PrefixI 'False) (U1 :: Type -> Type)))) |
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
FromJSON VersionRange Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON VersionRange Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: VersionRange -> Value # toEncoding :: VersionRange -> Encoding # toJSONList :: [VersionRange] -> Value # toEncodingList :: [VersionRange] -> Encoding # omitField :: VersionRange -> Bool # | |||||
Generic VersionRange Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show VersionRange Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> VersionRange -> ShowS # show :: VersionRange -> String # showList :: [VersionRange] -> ShowS # | |||||
NFData VersionRange Source # | |||||
Defined in GHCup.Types Methods rnf :: VersionRange -> () # | |||||
Eq VersionRange Source # | |||||
Defined in GHCup.Types | |||||
Ord VersionRange Source # | |||||
Defined in GHCup.Types Methods compare :: VersionRange -> VersionRange -> Ordering # (<) :: VersionRange -> VersionRange -> Bool # (<=) :: VersionRange -> VersionRange -> Bool # (>) :: VersionRange -> VersionRange -> Bool # (>=) :: VersionRange -> VersionRange -> Bool # max :: VersionRange -> VersionRange -> VersionRange # min :: VersionRange -> VersionRange -> VersionRange # | |||||
Pretty VersionRange Source # | |||||
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> VersionRange -> Doc # pPrint :: VersionRange -> Doc # pPrintList :: PrettyLevel -> [VersionRange] -> Doc # | |||||
FromJSONKey (Maybe VersionRange) Source # | |||||
Defined in GHCup.Types.JSON Methods fromJSONKey :: FromJSONKeyFunction (Maybe VersionRange) # fromJSONKeyList :: FromJSONKeyFunction [Maybe VersionRange] # | |||||
ToJSONKey (Maybe VersionRange) Source # | |||||
Defined in GHCup.Types.JSON Methods | |||||
type Rep VersionRange Source # | |||||
Defined in GHCup.Types type Rep VersionRange = D1 ('MetaData "VersionRange" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "SimpleRange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty VersionCmp))) :+: C1 ('MetaCons "OrRange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty VersionCmp)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VersionRange))) |
Instances
FromJSON MetaMode Source # | |
Defined in GHCup.Types.JSON | |
ToJSON MetaMode Source # | |
Generic MetaMode Source # | |
Defined in GHCup.Types | |
Read MetaMode Source # | |
Show MetaMode Source # | |
NFData MetaMode Source # | |
Defined in GHCup.Types | |
Eq MetaMode Source # | |
type Rep MetaMode Source # | |
data VersionPattern Source #
Constructors
CabalVer | |
GitHashShort | |
GitHashLong | |
GitDescribe | |
GitBranchName | |
S String |
Instances
Show VersionPattern Source # | |
Defined in GHCup.Types Methods showsPrec :: Int -> VersionPattern -> ShowS # show :: VersionPattern -> String # showList :: [VersionPattern] -> ShowS # | |
Eq VersionPattern Source # | |
Defined in GHCup.Types Methods (==) :: VersionPattern -> VersionPattern -> Bool # (/=) :: VersionPattern -> VersionPattern -> Bool # |
A tag. These are currently attached to a version of a tool.
Constructors
Latest | the latest version of a tool (unique per tool) |
Recommended | the recommended version of a tool (unique per tool) |
Prerelease | denotes a prerelease version
(a version should either be |
LatestPrerelease | the latest prerelease (unique per tool) |
Nightly | denotes a nightly version
(a version should either be |
LatestNightly | the latest nightly (unique per tool) |
Base PVP | the base version shipped with GHC |
Old | old versions are hidden by default in TUI |
Experimental | an experiemntal version/bindist |
UnknownTag String | used for upwardscompat |
Instances
FromJSON Tag Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON Tag Source # | |||||
Generic Tag Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show Tag Source # | |||||
NFData Tag Source # | |||||
Defined in GHCup.Types | |||||
Eq Tag Source # | |||||
Ord Tag Source # | |||||
Pretty Tag Source # | |||||
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> Tag -> Doc # pPrintList :: PrettyLevel -> [Tag] -> Doc # | |||||
type Rep Tag Source # | |||||
Defined in GHCup.Types type Rep Tag = D1 ('MetaData "Tag" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (((C1 ('MetaCons "Latest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Recommended" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Prerelease" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LatestPrerelease" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Nightly" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "LatestNightly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Base" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PVP))) :+: (C1 ('MetaCons "Old" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Experimental" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String)))))) |
data BuildSystem Source #
Instances
Show BuildSystem Source # | |
Defined in GHCup.Types Methods showsPrec :: Int -> BuildSystem -> ShowS # show :: BuildSystem -> String # showList :: [BuildSystem] -> ShowS # | |
Eq BuildSystem Source # | |
Defined in GHCup.Types |
data Downloader Source #
Instances
FromJSON Downloader Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON Downloader Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: Downloader -> Value # toEncoding :: Downloader -> Encoding # toJSONList :: [Downloader] -> Value # toEncodingList :: [Downloader] -> Encoding # omitField :: Downloader -> Bool # | |||||
Generic Downloader Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show Downloader Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> Downloader -> ShowS # show :: Downloader -> String # showList :: [Downloader] -> ShowS # | |||||
NFData Downloader Source # | |||||
Defined in GHCup.Types Methods rnf :: Downloader -> () # | |||||
Eq Downloader Source # | |||||
Defined in GHCup.Types | |||||
Ord Downloader Source # | |||||
Defined in GHCup.Types Methods compare :: Downloader -> Downloader -> Ordering # (<) :: Downloader -> Downloader -> Bool # (<=) :: Downloader -> Downloader -> Bool # (>) :: Downloader -> Downloader -> Bool # (>=) :: Downloader -> Downloader -> Bool # max :: Downloader -> Downloader -> Downloader # min :: Downloader -> Downloader -> Downloader # | |||||
type Rep Downloader Source # | |||||
data KeyCombination Source #
Constructors
KeyCombination | |
Instances
FromJSON KeyCombination Source # | |||||
Defined in GHCup.Types.JSON Methods parseJSON :: Value -> Parser KeyCombination # parseJSONList :: Value -> Parser [KeyCombination] # | |||||
ToJSON KeyCombination Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: KeyCombination -> Value # toEncoding :: KeyCombination -> Encoding # toJSONList :: [KeyCombination] -> Value # toEncodingList :: [KeyCombination] -> Encoding # omitField :: KeyCombination -> Bool # | |||||
Generic KeyCombination Source # | |||||
Defined in GHCup.Types Associated Types
Methods from :: KeyCombination -> Rep KeyCombination x # to :: Rep KeyCombination x -> KeyCombination # | |||||
Read KeyCombination Source # | |||||
Defined in GHCup.Types Methods readsPrec :: Int -> ReadS KeyCombination # readList :: ReadS [KeyCombination] # | |||||
Show KeyCombination Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> KeyCombination -> ShowS # show :: KeyCombination -> String # showList :: [KeyCombination] -> ShowS # | |||||
NFData KeyCombination Source # | |||||
Defined in GHCup.Types Methods rnf :: KeyCombination -> () # | |||||
Eq KeyCombination Source # | |||||
Defined in GHCup.Types Methods (==) :: KeyCombination -> KeyCombination -> Bool # (/=) :: KeyCombination -> KeyCombination -> Bool # | |||||
Ord KeyCombination Source # | |||||
Defined in GHCup.Types Methods compare :: KeyCombination -> KeyCombination -> Ordering # (<) :: KeyCombination -> KeyCombination -> Bool # (<=) :: KeyCombination -> KeyCombination -> Bool # (>) :: KeyCombination -> KeyCombination -> Bool # (>=) :: KeyCombination -> KeyCombination -> Bool # max :: KeyCombination -> KeyCombination -> KeyCombination # min :: KeyCombination -> KeyCombination -> KeyCombination # | |||||
type Rep KeyCombination Source # | |||||
Defined in GHCup.Types type Rep KeyCombination = D1 ('MetaData "KeyCombination" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "KeyCombination" 'PrefixI 'True) (S1 ('MetaSel ('Just "key") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Key) :*: S1 ('MetaSel ('Just "mods") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Modifier]))) |
data DownloadMirror Source #
Constructors
DownloadMirror | |
Fields
|
Instances
FromJSON DownloadMirror Source # | |||||
Defined in GHCup.Types.JSON Methods parseJSON :: Value -> Parser DownloadMirror # parseJSONList :: Value -> Parser [DownloadMirror] # | |||||
ToJSON DownloadMirror Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: DownloadMirror -> Value # toEncoding :: DownloadMirror -> Encoding # toJSONList :: [DownloadMirror] -> Value # toEncodingList :: [DownloadMirror] -> Encoding # omitField :: DownloadMirror -> Bool # | |||||
Generic DownloadMirror Source # | |||||
Defined in GHCup.Types Associated Types
Methods from :: DownloadMirror -> Rep DownloadMirror x # to :: Rep DownloadMirror x -> DownloadMirror # | |||||
Show DownloadMirror Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> DownloadMirror -> ShowS # show :: DownloadMirror -> String # showList :: [DownloadMirror] -> ShowS # | |||||
NFData DownloadMirror Source # | |||||
Defined in GHCup.Types Methods rnf :: DownloadMirror -> () # | |||||
Eq DownloadMirror Source # | |||||
Defined in GHCup.Types Methods (==) :: DownloadMirror -> DownloadMirror -> Bool # (/=) :: DownloadMirror -> DownloadMirror -> Bool # | |||||
Ord DownloadMirror Source # | |||||
Defined in GHCup.Types Methods compare :: DownloadMirror -> DownloadMirror -> Ordering # (<) :: DownloadMirror -> DownloadMirror -> Bool # (<=) :: DownloadMirror -> DownloadMirror -> Bool # (>) :: DownloadMirror -> DownloadMirror -> Bool # (>=) :: DownloadMirror -> DownloadMirror -> Bool # max :: DownloadMirror -> DownloadMirror -> DownloadMirror # min :: DownloadMirror -> DownloadMirror -> DownloadMirror # | |||||
type Rep DownloadMirror Source # | |||||
Defined in GHCup.Types type Rep DownloadMirror = D1 ('MetaData "DownloadMirror" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "DownloadMirror" 'PrefixI 'True) (S1 ('MetaSel ('Just "authority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Authority) :*: S1 ('MetaSel ('Just "pathPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)))) |
Constructors
Dirs | |
Instances
Generic Dirs Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show Dirs Source # | |||||
NFData Dirs Source # | |||||
Defined in GHCup.Types | |||||
LabelOptic "dirs" A_Lens Dirs Dirs Dirs Dirs Source # | |||||
Defined in GHCup.Types.Optics | |||||
type Rep Dirs Source # | |||||
Defined in GHCup.Types type Rep Dirs = D1 ('MetaData "Dirs" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "Dirs" 'PrefixI 'True) (((S1 ('MetaSel ('Just "baseDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GHCupPath) :*: S1 ('MetaSel ('Just "binDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FilePath)) :*: (S1 ('MetaSel ('Just "cacheDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GHCupPath) :*: S1 ('MetaSel ('Just "logsDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GHCupPath))) :*: ((S1 ('MetaSel ('Just "confDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GHCupPath) :*: S1 ('MetaSel ('Just "dbDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GHCupPath)) :*: (S1 ('MetaSel ('Just "recycleDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GHCupPath) :*: (S1 ('MetaSel ('Just "tmpDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GHCupPath) :*: S1 ('MetaSel ('Just "msys2Dir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FilePath)))))) |
data ProcessError Source #
Constructors
NonZeroExit Int FilePath [String] | |
PTerminated FilePath [String] | |
PStopped FilePath [String] | |
NoSuchPid FilePath [String] |
Instances
Show ProcessError Source # | |
Defined in GHCup.Types Methods showsPrec :: Int -> ProcessError -> ShowS # show :: ProcessError -> String # showList :: [ProcessError] -> ShowS # | |
HFErrorProject ProcessError Source # | |
Defined in GHCup.Errors | |
Pretty ProcessError Source # | |
Defined in GHCup.Errors Methods pPrintPrec :: PrettyLevel -> Rational -> ProcessError -> Doc # pPrint :: ProcessError -> Doc # pPrintList :: PrettyLevel -> [ProcessError] -> Doc # |
data CapturedProcess Source #
Constructors
CapturedProcess | |
Fields
|
Instances
Show CapturedProcess Source # | |
Defined in GHCup.Types Methods showsPrec :: Int -> CapturedProcess -> ShowS # show :: CapturedProcess -> String # showList :: [CapturedProcess] -> ShowS # | |
Eq CapturedProcess Source # | |
Defined in GHCup.Types Methods (==) :: CapturedProcess -> CapturedProcess -> Bool # (/=) :: CapturedProcess -> CapturedProcess -> Bool # |
type PromptQuestion = Text Source #
data PromptResponse Source #
Instances
Show PromptResponse Source # | |
Defined in GHCup.Types Methods showsPrec :: Int -> PromptResponse -> ShowS # show :: PromptResponse -> String # showList :: [PromptResponse] -> ShowS # | |
Eq PromptResponse Source # | |
Defined in GHCup.Types Methods (==) :: PromptResponse -> PromptResponse -> Bool # (/=) :: PromptResponse -> PromptResponse -> Bool # |
data Requirements Source #
Constructors
Requirements | |
Fields
|
Instances
FromJSON Requirements Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON Requirements Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: Requirements -> Value # toEncoding :: Requirements -> Encoding # toJSONList :: [Requirements] -> Value # toEncodingList :: [Requirements] -> Encoding # omitField :: Requirements -> Bool # | |||||
Generic Requirements Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show Requirements Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> Requirements -> ShowS # show :: Requirements -> String # showList :: [Requirements] -> ShowS # | |||||
NFData Requirements Source # | |||||
Defined in GHCup.Types Methods rnf :: Requirements -> () # | |||||
Eq Requirements Source # | |||||
Defined in GHCup.Types | |||||
type Rep Requirements Source # | |||||
Defined in GHCup.Types type Rep Requirements = D1 ('MetaData "Requirements" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "Requirements" 'PrefixI 'True) (S1 ('MetaSel ('Just "_distroPKGs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "_notes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) |
newtype MapIgnoreUnknownKeys k v Source #
Map with custom FromJSON instance which ignores unknown keys
Constructors
MapIgnoreUnknownKeys | |
Fields
|
Instances
(Ord k, FromJSONKey k, FromJSON v) => FromJSON (MapIgnoreUnknownKeys k v) Source # | Create a Map ignoring KeyValue pair which fail at parse of the key But if the key is parsed, the failures of parsing the value will not be ignored | ||||
Defined in GHCup.Types.JSON.MapIgnoreUnknownKeys Methods parseJSON :: Value -> Parser (MapIgnoreUnknownKeys k v) # parseJSONList :: Value -> Parser [MapIgnoreUnknownKeys k v] # omittedField :: Maybe (MapIgnoreUnknownKeys k v) # | |||||
ToJSON (Map k v) => ToJSON (MapIgnoreUnknownKeys k v) Source # | |||||
Defined in GHCup.Types.JSON.MapIgnoreUnknownKeys Methods toJSON :: MapIgnoreUnknownKeys k v -> Value # toEncoding :: MapIgnoreUnknownKeys k v -> Encoding # toJSONList :: [MapIgnoreUnknownKeys k v] -> Value # toEncodingList :: [MapIgnoreUnknownKeys k v] -> Encoding # omitField :: MapIgnoreUnknownKeys k v -> Bool # | |||||
Generic (MapIgnoreUnknownKeys k v) Source # | |||||
Defined in GHCup.Types Associated Types
Methods from :: MapIgnoreUnknownKeys k v -> Rep (MapIgnoreUnknownKeys k v) x # to :: Rep (MapIgnoreUnknownKeys k v) x -> MapIgnoreUnknownKeys k v # | |||||
(Show k, Show v) => Show (MapIgnoreUnknownKeys k v) Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> MapIgnoreUnknownKeys k v -> ShowS # show :: MapIgnoreUnknownKeys k v -> String # showList :: [MapIgnoreUnknownKeys k v] -> ShowS # | |||||
(NFData k, NFData v) => NFData (MapIgnoreUnknownKeys k v) Source # | |||||
Defined in GHCup.Types Methods rnf :: MapIgnoreUnknownKeys k v -> () # | |||||
(Eq k, Eq v) => Eq (MapIgnoreUnknownKeys k v) Source # | |||||
Defined in GHCup.Types Methods (==) :: MapIgnoreUnknownKeys k v -> MapIgnoreUnknownKeys k v -> Bool # (/=) :: MapIgnoreUnknownKeys k v -> MapIgnoreUnknownKeys k v -> Bool # | |||||
type Rep (MapIgnoreUnknownKeys k v) Source # | |||||
Defined in GHCup.Types type Rep (MapIgnoreUnknownKeys k v) = D1 ('MetaData "MapIgnoreUnknownKeys" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'True) (C1 ('MetaCons "MapIgnoreUnknownKeys" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMapIgnoreUnknownKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map k v)))) |
Constructors
AppState | |
Fields
|
Instances
Generic AppState Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show 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.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" '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 LeanAppState Source #
Constructors
LeanAppState | |
Fields
|
Instances
Generic LeanAppState Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show LeanAppState Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> LeanAppState -> ShowS # show :: LeanAppState -> String # showList :: [LeanAppState] -> ShowS # | |||||
NFData LeanAppState Source # | |||||
Defined in GHCup.Types Methods rnf :: LeanAppState -> () # | |||||
type Rep LeanAppState Source # | |||||
Defined in GHCup.Types type Rep LeanAppState = D1 ('MetaData "LeanAppState" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "LeanAppState" '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 "loggerConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LoggerConfig)))) |
data DownloadInfo Source #
An encapsulation of a download. This can be used to download, extract and install a tool.
Constructors
DownloadInfo | |
Instances
FromJSON DownloadInfo Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON DownloadInfo Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: DownloadInfo -> Value # toEncoding :: DownloadInfo -> Encoding # toJSONList :: [DownloadInfo] -> Value # toEncodingList :: [DownloadInfo] -> Encoding # omitField :: DownloadInfo -> Bool # | |||||
Generic DownloadInfo Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show DownloadInfo Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> DownloadInfo -> ShowS # show :: DownloadInfo -> String # showList :: [DownloadInfo] -> ShowS # | |||||
NFData DownloadInfo Source # | |||||
Defined in GHCup.Types Methods rnf :: DownloadInfo -> () # | |||||
Eq DownloadInfo Source # | |||||
Defined in GHCup.Types | |||||
Ord DownloadInfo Source # | |||||
Defined in GHCup.Types Methods compare :: DownloadInfo -> DownloadInfo -> Ordering # (<) :: DownloadInfo -> DownloadInfo -> Bool # (<=) :: DownloadInfo -> DownloadInfo -> Bool # (>) :: DownloadInfo -> DownloadInfo -> Bool # (>=) :: DownloadInfo -> DownloadInfo -> Bool # max :: DownloadInfo -> DownloadInfo -> DownloadInfo # min :: DownloadInfo -> DownloadInfo -> DownloadInfo # | |||||
type Rep DownloadInfo Source # | |||||
Defined in GHCup.Types type Rep DownloadInfo = D1 ('MetaData "DownloadInfo" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "DownloadInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_dlUri") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "_dlSubdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe TarDir)) :*: S1 ('MetaSel ('Just "_dlHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "_dlCSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Integer)) :*: (S1 ('MetaSel ('Just "_dlOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe FilePath)) :*: S1 ('MetaSel ('Just "_dlTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [Tag])))))) |
Instances
Show GitBranch Source # | |
Eq GitBranch Source # | |
Ord GitBranch Source # | |
Constructors
GHCupInfo | |
Instances
FromJSON GHCupInfo Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON GHCupInfo Source # | |||||
Generic GHCupInfo Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show GHCupInfo Source # | |||||
NFData GHCupInfo Source # | |||||
Defined in GHCup.Types | |||||
Eq GHCupInfo Source # | |||||
type Rep GHCupInfo Source # | |||||
Defined in GHCup.Types type Rep GHCupInfo = D1 ('MetaData "GHCupInfo" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" '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 "_metadataUpdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe URI))))) |
type ToolRequirements = Map Tool ToolReqVersionSpec Source #
type GHCupDownloads = Map Tool ToolVersionSpec Source #
Description of all binary and source downloads. This is a tree of nested maps.
type ToolReqVersionSpec = Map (Maybe Version) PlatformReqSpec Source #
data GHCTargetVersion Source #
A GHC identified by the target platform triple and the version.
Constructors
GHCTargetVersion | |
Fields
|
Instances
FromJSON GHCTargetVersion Source # | |||||
Defined in GHCup.Types.JSON Methods parseJSON :: Value -> Parser GHCTargetVersion # parseJSONList :: Value -> Parser [GHCTargetVersion] # | |||||
FromJSONKey GHCTargetVersion Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON GHCTargetVersion Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: GHCTargetVersion -> Value # toEncoding :: GHCTargetVersion -> Encoding # toJSONList :: [GHCTargetVersion] -> Value # toEncodingList :: [GHCTargetVersion] -> Encoding # omitField :: GHCTargetVersion -> Bool # | |||||
ToJSONKey GHCTargetVersion Source # | |||||
Defined in GHCup.Types.JSON | |||||
Generic GHCTargetVersion Source # | |||||
Defined in GHCup.Types Associated Types
Methods from :: GHCTargetVersion -> Rep GHCTargetVersion x # to :: Rep GHCTargetVersion x -> GHCTargetVersion # | |||||
Show GHCTargetVersion Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> GHCTargetVersion -> ShowS # show :: GHCTargetVersion -> String # showList :: [GHCTargetVersion] -> ShowS # | |||||
NFData GHCTargetVersion Source # | |||||
Defined in GHCup.Types Methods rnf :: GHCTargetVersion -> () # | |||||
Eq GHCTargetVersion Source # | |||||
Defined in GHCup.Types Methods (==) :: GHCTargetVersion -> GHCTargetVersion -> Bool # (/=) :: GHCTargetVersion -> GHCTargetVersion -> Bool # | |||||
Ord GHCTargetVersion Source # | |||||
Defined in GHCup.Types Methods compare :: GHCTargetVersion -> GHCTargetVersion -> Ordering # (<) :: GHCTargetVersion -> GHCTargetVersion -> Bool # (<=) :: GHCTargetVersion -> GHCTargetVersion -> Bool # (>) :: GHCTargetVersion -> GHCTargetVersion -> Bool # (>=) :: GHCTargetVersion -> GHCTargetVersion -> Bool # max :: GHCTargetVersion -> GHCTargetVersion -> GHCTargetVersion # min :: GHCTargetVersion -> GHCTargetVersion -> GHCTargetVersion # | |||||
Pretty GHCTargetVersion Source # | Assembles a path of the form: target-triple-version | ||||
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> GHCTargetVersion -> Doc # pPrint :: GHCTargetVersion -> Doc # pPrintList :: PrettyLevel -> [GHCTargetVersion] -> Doc # | |||||
type Rep GHCTargetVersion Source # | |||||
Defined in GHCup.Types type Rep GHCTargetVersion = D1 ('MetaData "GHCTargetVersion" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "GHCTargetVersion" 'PrefixI 'True) (S1 ('MetaSel ('Just "_tvTarget") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_tvVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Version))) |
data VersionInfo Source #
All necessary information of a tool version, including source download and per-architecture downloads.
Constructors
VersionInfo | |
Fields
|
Instances
FromJSON VersionInfo Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON VersionInfo Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: VersionInfo -> Value # toEncoding :: VersionInfo -> Encoding # toJSONList :: [VersionInfo] -> Value # toEncodingList :: [VersionInfo] -> Encoding # omitField :: VersionInfo -> Bool # | |||||
Generic VersionInfo Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show VersionInfo Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> VersionInfo -> ShowS # show :: VersionInfo -> String # showList :: [VersionInfo] -> ShowS # | |||||
NFData VersionInfo Source # | |||||
Defined in GHCup.Types Methods rnf :: VersionInfo -> () # | |||||
Eq VersionInfo Source # | |||||
Defined in GHCup.Types | |||||
type Rep VersionInfo Source # | |||||
Defined in GHCup.Types type Rep VersionInfo = D1 ('MetaData "VersionInfo" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "VersionInfo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "_viTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Tag]) :*: S1 ('MetaSel ('Just "_viReleaseDay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Day))) :*: (S1 ('MetaSel ('Just "_viChangeLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe URI)) :*: (S1 ('MetaSel ('Just "_viSourceDL") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe DownloadInfo)) :*: S1 ('MetaSel ('Just "_viTestDL") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe DownloadInfo))))) :*: ((S1 ('MetaSel ('Just "_viArch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ArchitectureSpec) :*: S1 ('MetaSel ('Just "_viPreInstall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "_viPostInstall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "_viPostRemove") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_viPreCompile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text))))))) |
data Architecture Source #
Instances
FromJSON Architecture Source # | |||||
Defined in GHCup.Types.JSON | |||||
FromJSONKey Architecture Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON Architecture Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: Architecture -> Value # toEncoding :: Architecture -> Encoding # toJSONList :: [Architecture] -> Value # toEncodingList :: [Architecture] -> Encoding # omitField :: Architecture -> Bool # | |||||
ToJSONKey Architecture Source # | |||||
Defined in GHCup.Types.JSON Methods | |||||
Bounded Architecture Source # | |||||
Defined in GHCup.Types | |||||
Enum Architecture Source # | |||||
Defined in GHCup.Types Methods succ :: Architecture -> Architecture # pred :: Architecture -> Architecture # toEnum :: Int -> Architecture # fromEnum :: Architecture -> Int # enumFrom :: Architecture -> [Architecture] # enumFromThen :: Architecture -> Architecture -> [Architecture] # enumFromTo :: Architecture -> Architecture -> [Architecture] # enumFromThenTo :: Architecture -> Architecture -> Architecture -> [Architecture] # | |||||
Generic Architecture Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show Architecture Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> Architecture -> ShowS # show :: Architecture -> String # showList :: [Architecture] -> ShowS # | |||||
NFData Architecture Source # | |||||
Defined in GHCup.Types Methods rnf :: Architecture -> () # | |||||
Eq Architecture Source # | |||||
Defined in GHCup.Types | |||||
Ord Architecture Source # | |||||
Defined in GHCup.Types Methods compare :: Architecture -> Architecture -> Ordering # (<) :: Architecture -> Architecture -> Bool # (<=) :: Architecture -> Architecture -> Bool # (>) :: Architecture -> Architecture -> Bool # (>=) :: Architecture -> Architecture -> Bool # max :: Architecture -> Architecture -> Architecture # min :: Architecture -> Architecture -> Architecture # | |||||
Pretty Architecture Source # | |||||
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> Architecture -> Doc # pPrint :: Architecture -> Doc # pPrintList :: PrettyLevel -> [Architecture] -> Doc # | |||||
type Rep Architecture Source # | |||||
Defined in GHCup.Types type Rep Architecture = D1 ('MetaData "Architecture" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (((C1 ('MetaCons "A_64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "A_32" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "A_PowerPC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "A_PowerPC64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "A_Sparc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "A_Sparc64" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "A_ARM" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "A_ARM64" 'PrefixI 'False) (U1 :: Type -> Type)))) |
type PlatformVersionSpec = Map (Maybe VersionRange) DownloadInfo Source #
tagToString :: Tag -> String Source #
archToString :: Architecture -> String Source #
platformToString :: Platform -> String Source #
distroToString :: LinuxDistro -> String Source #
allDistros :: [LinuxDistro] Source #
How to descend into a tar archive.
Instances
FromJSON TarDir Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON TarDir Source # | |||||
Generic TarDir Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show TarDir Source # | |||||
NFData TarDir Source # | |||||
Defined in GHCup.Types | |||||
Eq TarDir Source # | |||||
Ord TarDir Source # | |||||
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.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" '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))) |
newtype DownloadMirrors Source #
Constructors
DM (Map Text DownloadMirror) |
Instances
FromJSON DownloadMirrors Source # | |||||
Defined in GHCup.Types.JSON Methods parseJSON :: Value -> Parser DownloadMirrors # parseJSONList :: Value -> Parser [DownloadMirrors] # | |||||
ToJSON DownloadMirrors Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: DownloadMirrors -> Value # toEncoding :: DownloadMirrors -> Encoding # toJSONList :: [DownloadMirrors] -> Value # toEncodingList :: [DownloadMirrors] -> Encoding # omitField :: DownloadMirrors -> Bool # | |||||
Generic DownloadMirrors Source # | |||||
Defined in GHCup.Types Associated Types
Methods from :: DownloadMirrors -> Rep DownloadMirrors x # to :: Rep DownloadMirrors x -> DownloadMirrors # | |||||
Show DownloadMirrors Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> DownloadMirrors -> ShowS # show :: DownloadMirrors -> String # showList :: [DownloadMirrors] -> ShowS # | |||||
NFData DownloadMirrors Source # | |||||
Defined in GHCup.Types Methods rnf :: DownloadMirrors -> () # | |||||
Eq DownloadMirrors Source # | |||||
Defined in GHCup.Types Methods (==) :: DownloadMirrors -> DownloadMirrors -> Bool # (/=) :: DownloadMirrors -> DownloadMirrors -> Bool # | |||||
Ord DownloadMirrors Source # | |||||
Defined in GHCup.Types Methods compare :: DownloadMirrors -> DownloadMirrors -> Ordering # (<) :: DownloadMirrors -> DownloadMirrors -> Bool # (<=) :: DownloadMirrors -> DownloadMirrors -> Bool # (>) :: DownloadMirrors -> DownloadMirrors -> Bool # (>=) :: DownloadMirrors -> DownloadMirrors -> Bool # max :: DownloadMirrors -> DownloadMirrors -> DownloadMirrors # min :: DownloadMirrors -> DownloadMirrors -> DownloadMirrors # | |||||
type Rep DownloadMirrors Source # | |||||
Defined in GHCup.Types type Rep DownloadMirrors = D1 ('MetaData "DownloadMirrors" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'True) (C1 ('MetaCons "DM" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text DownloadMirror)))) |
Where to fetch GHCupDownloads from.
Constructors
GHCupURL | |
StackSetupURL | |
OwnSource [Either (Either GHCupInfo SetupInfo) URI] | complete source list |
OwnSpec (Either GHCupInfo SetupInfo) | |
AddSource [Either (Either GHCupInfo SetupInfo) URI] | merge with GHCupURL |
SimpleList [NewURLSource] |
Instances
FromJSON URLSource Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON URLSource Source # | |||||
Generic URLSource Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show URLSource Source # | |||||
NFData URLSource Source # | |||||
Defined in GHCup.Types | |||||
Eq URLSource Source # | |||||
type Rep URLSource Source # | |||||
Defined in GHCup.Types type Rep URLSource = D1 ('MetaData "URLSource" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) ((C1 ('MetaCons "GHCupURL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StackSetupURL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OwnSource" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Either (Either GHCupInfo SetupInfo) URI])))) :+: (C1 ('MetaCons "OwnSpec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Either GHCupInfo SetupInfo))) :+: (C1 ('MetaCons "AddSource" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Either (Either GHCupInfo SetupInfo) URI])) :+: C1 ('MetaCons "SimpleList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [NewURLSource]))))) |
data NewURLSource Source #
Constructors
NewGHCupURL | |
NewStackSetupURL | |
NewGHCupInfo GHCupInfo | |
NewSetupInfo SetupInfo | |
NewURI URI | |
NewChannelAlias ChannelAlias |
Instances
FromJSON NewURLSource Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON NewURLSource Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: NewURLSource -> Value # toEncoding :: NewURLSource -> Encoding # toJSONList :: [NewURLSource] -> Value # toEncodingList :: [NewURLSource] -> Encoding # omitField :: NewURLSource -> Bool # | |||||
Generic NewURLSource Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show NewURLSource Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> NewURLSource -> ShowS # show :: NewURLSource -> String # showList :: [NewURLSource] -> ShowS # | |||||
NFData NewURLSource Source # | |||||
Defined in GHCup.Types Methods rnf :: NewURLSource -> () # | |||||
Eq NewURLSource Source # | |||||
Defined in GHCup.Types | |||||
type Rep NewURLSource Source # | |||||
Defined in GHCup.Types type Rep NewURLSource = D1 ('MetaData "NewURLSource" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) ((C1 ('MetaCons "NewGHCupURL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NewStackSetupURL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NewGHCupInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GHCupInfo)))) :+: (C1 ('MetaCons "NewSetupInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SetupInfo)) :+: (C1 ('MetaCons "NewURI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 URI)) :+: C1 ('MetaCons "NewChannelAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ChannelAlias))))) |
data ChannelAlias Source #
Alias for ease of URLSource selection
Instances
FromJSON ChannelAlias Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON ChannelAlias Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: ChannelAlias -> Value # toEncoding :: ChannelAlias -> Encoding # toJSONList :: [ChannelAlias] -> Value # toEncodingList :: [ChannelAlias] -> Encoding # omitField :: ChannelAlias -> Bool # | |||||
Bounded ChannelAlias Source # | |||||
Defined in GHCup.Types | |||||
Enum ChannelAlias Source # | |||||
Defined in GHCup.Types Methods succ :: ChannelAlias -> ChannelAlias # pred :: ChannelAlias -> ChannelAlias # toEnum :: Int -> ChannelAlias # fromEnum :: ChannelAlias -> Int # enumFrom :: ChannelAlias -> [ChannelAlias] # enumFromThen :: ChannelAlias -> ChannelAlias -> [ChannelAlias] # enumFromTo :: ChannelAlias -> ChannelAlias -> [ChannelAlias] # enumFromThenTo :: ChannelAlias -> ChannelAlias -> ChannelAlias -> [ChannelAlias] # | |||||
Generic ChannelAlias Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show ChannelAlias Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> ChannelAlias -> ShowS # show :: ChannelAlias -> String # showList :: [ChannelAlias] -> ShowS # | |||||
NFData ChannelAlias Source # | |||||
Defined in GHCup.Types Methods rnf :: ChannelAlias -> () # | |||||
Eq ChannelAlias Source # | |||||
Defined in GHCup.Types | |||||
type Rep ChannelAlias Source # | |||||
Defined in GHCup.Types type Rep ChannelAlias = D1 ('MetaData "ChannelAlias" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) ((C1 ('MetaCons "DefaultChannel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StackChannel" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CrossChannel" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrereleasesChannel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VanillaChannel" 'PrefixI 'False) (U1 :: Type -> Type)))) |
channelAliasText :: ChannelAlias -> Text Source #
fromURLSource :: URLSource -> [NewURLSource] Source #
data UserSettings Source #
Constructors
UserSettings | |
Fields
|
Instances
FromJSON UserSettings Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON UserSettings Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: UserSettings -> Value # toEncoding :: UserSettings -> Encoding # toJSONList :: [UserSettings] -> Value # toEncodingList :: [UserSettings] -> Encoding # omitField :: UserSettings -> Bool # | |||||
Generic UserSettings Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show UserSettings Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> UserSettings -> ShowS # show :: UserSettings -> String # showList :: [UserSettings] -> ShowS # | |||||
Eq UserSettings Source # | |||||
Defined in GHCup.Types | |||||
type Rep UserSettings Source # | |||||
Defined in GHCup.Types type Rep UserSettings = D1 ('MetaData "UserSettings" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "UserSettings" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "uCache") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "uMetaCache") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Integer))) :*: (S1 ('MetaSel ('Just "uMetaMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe MetaMode)) :*: S1 ('MetaSel ('Just "uNoVerify") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "uVerbose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "uKeepDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe KeepDirs))) :*: (S1 ('MetaSel ('Just "uDownloader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Downloader)) :*: S1 ('MetaSel ('Just "uKeyBindings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe UserKeyBindings))))) :*: (((S1 ('MetaSel ('Just "uUrlSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe URLSource)) :*: S1 ('MetaSel ('Just "uNoNetwork") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "uGPGSetting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe GPGSetting)) :*: S1 ('MetaSel ('Just "uPlatformOverride") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe PlatformRequest)))) :*: ((S1 ('MetaSel ('Just "uMirrors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe DownloadMirrors)) :*: S1 ('MetaSel ('Just "uDefGHCConfOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [String]))) :*: (S1 ('MetaSel ('Just "uPager") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe PagerConfig)) :*: S1 ('MetaSel ('Just "uGuessVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool))))))) |
data UserKeyBindings Source #
Constructors
UserKeyBindings | |
Fields |
Instances
FromJSON UserKeyBindings Source # | |||||
Defined in GHCup.Types.JSON Methods parseJSON :: Value -> Parser UserKeyBindings # parseJSONList :: Value -> Parser [UserKeyBindings] # | |||||
ToJSON UserKeyBindings Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: UserKeyBindings -> Value # toEncoding :: UserKeyBindings -> Encoding # toJSONList :: [UserKeyBindings] -> Value # toEncodingList :: [UserKeyBindings] -> Encoding # omitField :: UserKeyBindings -> Bool # | |||||
Generic UserKeyBindings Source # | |||||
Defined in GHCup.Types Associated Types
Methods from :: UserKeyBindings -> Rep UserKeyBindings x # to :: Rep UserKeyBindings x -> UserKeyBindings # | |||||
Show UserKeyBindings Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> UserKeyBindings -> ShowS # show :: UserKeyBindings -> String # showList :: [UserKeyBindings] -> ShowS # | |||||
Eq UserKeyBindings Source # | |||||
Defined in GHCup.Types Methods (==) :: UserKeyBindings -> UserKeyBindings -> Bool # (/=) :: UserKeyBindings -> UserKeyBindings -> Bool # | |||||
type Rep UserKeyBindings Source # | |||||
Defined in GHCup.Types type Rep UserKeyBindings = D1 ('MetaData "UserKeyBindings" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "UserKeyBindings" 'PrefixI 'True) (((S1 ('MetaSel ('Just "kUp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe KeyCombination)) :*: S1 ('MetaSel ('Just "kDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe KeyCombination))) :*: (S1 ('MetaSel ('Just "kQuit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe KeyCombination)) :*: S1 ('MetaSel ('Just "kInstall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe KeyCombination)))) :*: ((S1 ('MetaSel ('Just "kUninstall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe KeyCombination)) :*: S1 ('MetaSel ('Just "kSet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe KeyCombination))) :*: (S1 ('MetaSel ('Just "kChangelog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe KeyCombination)) :*: S1 ('MetaSel ('Just "kShowAll") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe KeyCombination)))))) |
data GPGSetting Source #
Instances
FromJSON GPGSetting Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON GPGSetting Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: GPGSetting -> Value # toEncoding :: GPGSetting -> Encoding # toJSONList :: [GPGSetting] -> Value # toEncodingList :: [GPGSetting] -> Encoding # omitField :: GPGSetting -> Bool # | |||||
Generic GPGSetting Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show GPGSetting Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> GPGSetting -> ShowS # show :: GPGSetting -> String # showList :: [GPGSetting] -> ShowS # | |||||
NFData GPGSetting Source # | |||||
Defined in GHCup.Types Methods rnf :: GPGSetting -> () # | |||||
Eq GPGSetting Source # | |||||
Defined in GHCup.Types | |||||
Ord GPGSetting Source # | |||||
Defined in GHCup.Types Methods compare :: GPGSetting -> GPGSetting -> Ordering # (<) :: GPGSetting -> GPGSetting -> Bool # (<=) :: GPGSetting -> GPGSetting -> Bool # (>) :: GPGSetting -> GPGSetting -> Bool # (>=) :: GPGSetting -> GPGSetting -> Bool # max :: GPGSetting -> GPGSetting -> GPGSetting # min :: GPGSetting -> GPGSetting -> GPGSetting # | |||||
type Rep GPGSetting Source # | |||||
Defined in GHCup.Types type Rep GPGSetting = D1 ('MetaData "GPGSetting" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "GPGStrict" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GPGLax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GPGNone" 'PrefixI 'False) (U1 :: Type -> Type))) |
data PlatformRequest Source #
Constructors
PlatformRequest | |
Fields
|
Instances
FromJSON PlatformRequest Source # | |||||
Defined in GHCup.Types.JSON Methods parseJSON :: Value -> Parser PlatformRequest # parseJSONList :: Value -> Parser [PlatformRequest] # | |||||
ToJSON PlatformRequest Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: PlatformRequest -> Value # toEncoding :: PlatformRequest -> Encoding # toJSONList :: [PlatformRequest] -> Value # toEncodingList :: [PlatformRequest] -> Encoding # omitField :: PlatformRequest -> Bool # | |||||
Generic PlatformRequest Source # | |||||
Defined in GHCup.Types Associated Types
Methods from :: PlatformRequest -> Rep PlatformRequest x # to :: Rep PlatformRequest x -> PlatformRequest # | |||||
Show PlatformRequest Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> PlatformRequest -> ShowS # show :: PlatformRequest -> String # showList :: [PlatformRequest] -> ShowS # | |||||
NFData PlatformRequest Source # | |||||
Defined in GHCup.Types Methods rnf :: PlatformRequest -> () # | |||||
Eq PlatformRequest Source # | |||||
Defined in GHCup.Types Methods (==) :: PlatformRequest -> PlatformRequest -> Bool # (/=) :: PlatformRequest -> PlatformRequest -> Bool # | |||||
Pretty PlatformRequest Source # | |||||
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> PlatformRequest -> Doc # pPrint :: PlatformRequest -> Doc # pPrintList :: PrettyLevel -> [PlatformRequest] -> Doc # | |||||
type Rep PlatformRequest Source # | |||||
Defined in GHCup.Types type Rep PlatformRequest = D1 ('MetaData "PlatformRequest" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "PlatformRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "_rArch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Architecture) :*: (S1 ('MetaSel ('Just "_rPlatform") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Platform) :*: S1 ('MetaSel ('Just "_rVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Versioning))))) |
data PagerConfig Source #
Instances
FromJSON PagerConfig Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON PagerConfig Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: PagerConfig -> Value # toEncoding :: PagerConfig -> Encoding # toJSONList :: [PagerConfig] -> Value # toEncodingList :: [PagerConfig] -> Encoding # omitField :: PagerConfig -> Bool # | |||||
Generic PagerConfig Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show PagerConfig Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> PagerConfig -> ShowS # show :: PagerConfig -> String # showList :: [PagerConfig] -> ShowS # | |||||
NFData PagerConfig Source # | |||||
Defined in GHCup.Types Methods rnf :: PagerConfig -> () # | |||||
Eq PagerConfig Source # | |||||
Defined in GHCup.Types | |||||
type Rep PagerConfig Source # | |||||
Defined in GHCup.Types type Rep PagerConfig = D1 ('MetaData "PagerConfig" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "PagerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "pagerList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "pagerCmd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe String)))) |
fromSettings :: Settings -> Maybe KeyBindings -> UserSettings Source #
data KeyBindings Source #
Constructors
KeyBindings | |
Fields |
Instances
ToJSON KeyBindings Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: KeyBindings -> Value # toEncoding :: KeyBindings -> Encoding # toJSONList :: [KeyBindings] -> Value # toEncodingList :: [KeyBindings] -> Encoding # omitField :: KeyBindings -> Bool # | |||||
Generic KeyBindings Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show KeyBindings Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> KeyBindings -> ShowS # show :: KeyBindings -> String # showList :: [KeyBindings] -> ShowS # | |||||
NFData KeyBindings Source # | |||||
Defined in GHCup.Types Methods rnf :: KeyBindings -> () # | |||||
type Rep KeyBindings Source # | |||||
Defined in GHCup.Types type Rep KeyBindings = D1 ('MetaData "KeyBindings" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "KeyBindings" 'PrefixI 'True) (((S1 ('MetaSel ('Just "bUp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyCombination) :*: S1 ('MetaSel ('Just "bDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyCombination)) :*: (S1 ('MetaSel ('Just "bQuit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyCombination) :*: S1 ('MetaSel ('Just "bInstall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyCombination))) :*: ((S1 ('MetaSel ('Just "bUninstall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyCombination) :*: S1 ('MetaSel ('Just "bSet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyCombination)) :*: (S1 ('MetaSel ('Just "bChangelog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyCombination) :*: S1 ('MetaSel ('Just "bShowAllVersions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyCombination))))) |
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 -> () # |
fromAppState :: AppState -> LeanAppState Source #
allPagerConfig :: String -> PagerConfig Source #
Instances
Generic MSYS2Env Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Read MSYS2Env Source # | |||||
Show MSYS2Env Source # | |||||
NFData MSYS2Env Source # | |||||
Defined in GHCup.Types | |||||
Eq MSYS2Env Source # | |||||
Ord MSYS2Env Source # | |||||
Defined in GHCup.Types | |||||
type Rep MSYS2Env Source # | |||||
Defined in GHCup.Types type Rep MSYS2Env = D1 ('MetaData "MSYS2Env" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) ((C1 ('MetaCons "MSYS" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UCRT64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CLANG64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CLANGARM64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CLANG32" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MINGW64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MINGW32" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Constructors
DebugInfo | |
Fields
|
data PlatformResult Source #
Constructors
PlatformResult | |
Fields |
Instances
Generic PlatformResult Source # | |||||
Defined in GHCup.Types Associated Types
Methods from :: PlatformResult -> Rep PlatformResult x # to :: Rep PlatformResult x -> PlatformResult # | |||||
Show PlatformResult Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> PlatformResult -> ShowS # show :: PlatformResult -> String # showList :: [PlatformResult] -> ShowS # | |||||
NFData PlatformResult Source # | |||||
Defined in GHCup.Types Methods rnf :: PlatformResult -> () # | |||||
Eq PlatformResult Source # | |||||
Defined in GHCup.Types Methods (==) :: PlatformResult -> PlatformResult -> Bool # (/=) :: PlatformResult -> PlatformResult -> Bool # | |||||
Pretty PlatformResult Source # | |||||
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> PlatformResult -> Doc # pPrint :: PlatformResult -> Doc # pPrintList :: PrettyLevel -> [PlatformResult] -> Doc # | |||||
type Rep PlatformResult Source # | |||||
Defined in GHCup.Types type Rep PlatformResult = D1 ('MetaData "PlatformResult" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) (C1 ('MetaCons "PlatformResult" 'PrefixI 'True) (S1 ('MetaSel ('Just "_platform") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Platform) :*: S1 ('MetaSel ('Just "_distroVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Versioning)))) |
Constructors
SetGHCOnly | unversioned |
SetGHC_XY | ghc-x.y |
SetGHC_XYZ | ghc-x.y.z |
Constructors
SetHLSOnly | unversioned |
SetHLS_XYZ | haskell-language-server-a.b.c~x.y.z, where a.b.c is GHC version and x.y.z is HLS version |
mkTVer :: Version -> GHCTargetVersion Source #
tVerToText :: GHCTargetVersion -> Text Source #
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
FromJSON VersionCmp Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON VersionCmp Source # | |||||
Defined in GHCup.Types.JSON Methods toJSON :: VersionCmp -> Value # toEncoding :: VersionCmp -> Encoding # toJSONList :: [VersionCmp] -> Value # toEncodingList :: [VersionCmp] -> Encoding # omitField :: VersionCmp -> Bool # | |||||
Generic VersionCmp Source # | |||||
Defined in GHCup.Types Associated Types
| |||||
Show VersionCmp Source # | |||||
Defined in GHCup.Types Methods showsPrec :: Int -> VersionCmp -> ShowS # show :: VersionCmp -> String # showList :: [VersionCmp] -> ShowS # | |||||
NFData VersionCmp Source # | |||||
Defined in GHCup.Types Methods rnf :: VersionCmp -> () # | |||||
Eq VersionCmp Source # | |||||
Defined in GHCup.Types | |||||
Ord VersionCmp Source # | |||||
Defined in GHCup.Types Methods compare :: VersionCmp -> VersionCmp -> Ordering # (<) :: VersionCmp -> VersionCmp -> Bool # (<=) :: VersionCmp -> VersionCmp -> Bool # (>) :: VersionCmp -> VersionCmp -> Bool # (>=) :: VersionCmp -> VersionCmp -> Bool # max :: VersionCmp -> VersionCmp -> VersionCmp # min :: VersionCmp -> VersionCmp -> VersionCmp # | |||||
Pretty VersionCmp Source # | |||||
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> VersionCmp -> Doc # pPrint :: VersionCmp -> Doc # pPrintList :: PrettyLevel -> [VersionCmp] -> Doc # | |||||
type Rep VersionCmp Source # | |||||
Defined in GHCup.Types type Rep VersionCmp = D1 ('MetaData "VersionCmp" "GHCup.Types" "ghcup-0.1.50.2-Jfr5fzK8OmQ4YTAh4NXcyO" 'False) ((C1 ('MetaCons "VR_gt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Versioning)) :+: C1 ('MetaCons "VR_gteq" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Versioning))) :+: (C1 ('MetaCons "VR_lt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Versioning)) :+: (C1 ('MetaCons "VR_lteq" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Versioning)) :+: C1 ('MetaCons "VR_eq" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Versioning))))) |
data InstallDir Source #
Constructors
IsolateDir FilePath | |
GHCupInternal |
Instances
Show InstallDir Source # | |
Defined in GHCup.Types Methods showsPrec :: Int -> InstallDir -> ShowS # show :: InstallDir -> String # showList :: [InstallDir] -> ShowS # | |
Eq InstallDir Source # | |
Defined in GHCup.Types |
data InstallDirResolved Source #
Constructors
IsolateDirResolved FilePath | |
GHCupDir GHCupPath | |
GHCupBinDir FilePath |
Instances
Show InstallDirResolved Source # | |
Defined in GHCup.Types Methods showsPrec :: Int -> InstallDirResolved -> ShowS # show :: InstallDirResolved -> String # showList :: [InstallDirResolved] -> ShowS # | |
Eq InstallDirResolved Source # | |
Defined in GHCup.Types Methods (==) :: InstallDirResolved -> InstallDirResolved -> Bool # (/=) :: InstallDirResolved -> InstallDirResolved -> Bool # |
isSafeDir :: InstallDirResolved -> Bool Source #
data ToolVersion Source #
Constructors
GHCVersion GHCTargetVersion | |
ToolVersion Version | |
ToolTag Tag | |
ToolDay Day |
Instances
Show ToolVersion Source # | |
Defined in GHCup.Types Methods showsPrec :: Int -> ToolVersion -> ShowS # show :: ToolVersion -> String # showList :: [ToolVersion] -> ShowS # | |
Eq ToolVersion Source # | |
Defined in GHCup.Types | |
Pretty ToolVersion Source # | |
Defined in GHCup.Types Methods pPrintPrec :: PrettyLevel -> Rational -> ToolVersion -> Doc # pPrint :: ToolVersion -> Doc # pPrintList :: PrettyLevel -> [ToolVersion] -> Doc # |
Type representing our guessing modes when e.g. "incomplete" PVP version
is specified, such as ghcup set ghc 9.12
.
Constructors
GStrict | don't guess the proper tool version |
GLax | guess by using the metadata |
GLaxWithInstalled | guess by using metadata and installed versions |
Instances
Representations of non-modifier keys.
- KFun is indexed from 0 to 63. Range of supported FKeys varies by terminal and keyboard.
- KUpLeft, KUpRight, KDownLeft, KDownRight, KCenter support varies by terminal and keyboard.
- Actually, support for most of these but KEsc, KChar, KBS, and KEnter vary by terminal and keyboard.
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
FromJSON Key Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON Key Source # | |||||
Generic Key | |||||
Defined in Graphics.Vty.Input.Events Associated Types
| |||||
Read Key | |||||
Show Key | |||||
NFData Key | |||||
Defined in Graphics.Vty.Input.Events | |||||
Eq Key | |||||
Ord Key | |||||
Parse Key | |||||
Defined in Graphics.Vty.Config Methods parseValue :: Parser Key | |||||
type Rep Key | |||||
Defined in Graphics.Vty.Input.Events type Rep Key = D1 ('MetaData "Key" "Graphics.Vty.Input.Events" "vty-6.2-3xU0jwoIECI8IAySDJwyOV" 'False) ((((C1 ('MetaCons "KEsc" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Char)) :+: C1 ('MetaCons "KBS" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KEnter" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KRight" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KUpLeft" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KUpRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KDownLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KDownRight" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "KCenter" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KFun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "KBackTab" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KPrtScr" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KPause" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KIns" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KHome" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KPageUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KDel" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KPageDown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KBegin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KMenu" 'PrefixI 'False) (U1 :: Type -> Type)))))) |
Modifier keys. Key codes are interpreted such that users are more
likely to have Meta than Alt; for instance on the PC Linux console,
MMeta
will generally correspond to the physical Alt key.
Instances
FromJSON Modifier Source # | |||||
Defined in GHCup.Types.JSON | |||||
ToJSON Modifier Source # | |||||
Generic Modifier | |||||
Defined in Graphics.Vty.Input.Events Associated Types
| |||||
Read Modifier | |||||
Show Modifier | |||||
NFData Modifier | |||||
Defined in Graphics.Vty.Input.Events | |||||
Eq Modifier | |||||
Ord Modifier | |||||
Defined in Graphics.Vty.Input.Events | |||||
Parse Modifier | |||||
Defined in Graphics.Vty.Config Methods parseValue :: Parser Modifier | |||||
type Rep Modifier | |||||
Defined in Graphics.Vty.Input.Events type Rep Modifier = D1 ('MetaData "Modifier" "Graphics.Vty.Input.Events" "vty-6.2-3xU0jwoIECI8IAySDJwyOV" 'False) ((C1 ('MetaCons "MShift" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MCtrl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MMeta" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MAlt" 'PrefixI 'False) (U1 :: Type -> Type))) |
data ArchiveResult #
Constructors
ArchiveFatal | |
ArchiveFailed | |
ArchiveWarn | |
ArchiveRetry | |
ArchiveOk | |
ArchiveEOF |
Instances
Enum ArchiveResult | |||||
Defined in Codec.Archive.Types.Foreign Methods succ :: ArchiveResult -> ArchiveResult # pred :: ArchiveResult -> ArchiveResult # toEnum :: Int -> ArchiveResult # fromEnum :: ArchiveResult -> Int # enumFrom :: ArchiveResult -> [ArchiveResult] # enumFromThen :: ArchiveResult -> ArchiveResult -> [ArchiveResult] # enumFromTo :: ArchiveResult -> ArchiveResult -> [ArchiveResult] # enumFromThenTo :: ArchiveResult -> ArchiveResult -> ArchiveResult -> [ArchiveResult] # | |||||
Exception ArchiveResult | |||||
Defined in Codec.Archive.Types.Foreign Methods toException :: ArchiveResult -> SomeException # fromException :: SomeException -> Maybe ArchiveResult # displayException :: ArchiveResult -> String # | |||||
Generic ArchiveResult | |||||
Defined in Codec.Archive.Types.Foreign Associated Types
| |||||
Show ArchiveResult | |||||
Defined in Codec.Archive.Types.Foreign Methods showsPrec :: Int -> ArchiveResult -> ShowS # show :: ArchiveResult -> String # showList :: [ArchiveResult] -> ShowS # | |||||
NFData ArchiveResult | |||||
Defined in Codec.Archive.Types.Foreign Methods rnf :: ArchiveResult -> () # | |||||
Eq ArchiveResult | |||||
Defined in Codec.Archive.Types.Foreign Methods (==) :: ArchiveResult -> ArchiveResult -> Bool # (/=) :: ArchiveResult -> ArchiveResult -> Bool # | |||||
HFErrorProject ArchiveResult Source # | |||||
Defined in GHCup.Errors | |||||
Pretty ArchiveResult Source # | |||||
Defined in GHCup.Errors Methods pPrintPrec :: PrettyLevel -> Rational -> ArchiveResult -> Doc # pPrint :: ArchiveResult -> Doc # pPrintList :: PrettyLevel -> [ArchiveResult] -> Doc # | |||||
type Rep ArchiveResult | |||||
Defined in Codec.Archive.Types.Foreign type Rep ArchiveResult = D1 ('MetaData "ArchiveResult" "Codec.Archive.Types.Foreign" "libarchive-3.0.4.2-KxMGCIf6otTCV7PVOhd6bX" 'False) ((C1 ('MetaCons "ArchiveFatal" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ArchiveFailed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArchiveWarn" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ArchiveRetry" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ArchiveOk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArchiveEOF" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Orphan instances
NFData Authority Source # | |
NFData Host Source # | |
NFData Port Source # | |
NFData UserInfo Source # | |
Pretty Version Source # | |
Methods pPrintPrec :: PrettyLevel -> Rational -> Version -> Doc # pPrintList :: PrettyLevel -> [Version] -> Doc # | |
Pretty Versioning Source # | |
Methods pPrintPrec :: PrettyLevel -> Rational -> Versioning -> Doc # pPrint :: Versioning -> Doc # pPrintList :: PrettyLevel -> [Versioning] -> Doc # | |
Show (IO ()) Source # | |
NFData (URIRef Absolute) Source # | |
Show (a -> b) Source # | |