Copyright | (c) Julian Ospald 2020 |
---|---|
License | LGPL-3.0 |
Maintainer | hasufell@hasufell.de |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
GHCup.Types
Contents
Description
Synopsis
- data Platform
- data VersionRange
- data Tag
- 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 DownloadInfo = DownloadInfo {}
- data KeyCombination = KeyCombination {}
- data GHCupInfo = GHCupInfo {}
- type ToolRequirements = Map Tool ToolReqVersionSpec
- type GHCupDownloads = Map Tool ToolVersionSpec
- data Tool
- 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
- data LinuxDistro
- data TarDir
- data DownloadMirror = DownloadMirror {}
- newtype DownloadMirrors = DM (Map Text DownloadMirror)
- data URLSource
- data NewURLSource
- data ChannelAlias
- data MetaMode
- 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 KeepDirs
- data Downloader
- data UserKeyBindings = UserKeyBindings {}
- data GPGSetting
- data PlatformRequest = PlatformRequest {}
- data PagerConfig = PagerConfig {}
- 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 KeyBindings = KeyBindings {}
- data AppState = AppState {}
- data LoggerConfig = LoggerConfig {
- lcPrintDebug :: Bool
- consoleOutter :: Text -> IO ()
- fileOutter :: Text -> IO ()
- fancyColors :: Bool
- data LeanAppState = LeanAppState {}
- data MSYS2Env
- data DebugInfo = DebugInfo {
- diDirs :: Dirs
- diArch :: Architecture
- diPlatform :: PlatformResult
- diChannels :: [(ChannelAlias, URI)]
- diShimGenURL :: URI
- data PlatformResult = PlatformResult {}
- data SetGHC
- data SetHLS
- data GitBranch = GitBranch {}
- data VersionCmp
- data LogLevel
- data InstallDir
- data InstallDirResolved
- data ToolVersion
- data BuildSystem
- data VersionPattern
- data GuessMode
- tagToString :: Tag -> String
- archToString :: Architecture -> String
- platformToString :: Platform -> String
- distroToString :: LinuxDistro -> String
- allDistros :: [LinuxDistro]
- channelAliasText :: ChannelAlias -> Text
- fromURLSource :: URLSource -> [NewURLSource]
- convert' :: Either (Either GHCupInfo SetupInfo) URI -> NewURLSource
- defaultUserSettings :: UserSettings
- fromSettings :: Settings -> Maybe KeyBindings -> UserSettings
- defaultKeyBindings :: KeyBindings
- fromAppState :: AppState -> LeanAppState
- defaultPagerConfig :: PagerConfig
- allPagerConfig :: String -> PagerConfig
- defaultMetaCache :: Integer
- defaultSettings :: Settings
- platResToString :: PlatformResult -> String
- pfReqToString :: PlatformRequest -> String
- mkTVer :: Version -> GHCTargetVersion
- tVerToText :: GHCTargetVersion -> Text
- fromInstallDir :: InstallDirResolved -> FilePath
- isSafeDir :: InstallDirResolved -> Bool
- data Key
- data Modifier
- data ArchiveResult
Documentation
Instances
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
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
Constructors
Dirs | |
Instances
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
newtype MapIgnoreUnknownKeys k v Source #
Map with custom FromJSON instance which ignores unknown keys
Constructors
MapIgnoreUnknownKeys | |
Fields
|
Instances
data DownloadInfo Source #
An encapsulation of a download. This can be used to download, extract and install a tool.
Constructors
DownloadInfo | |
Instances
data KeyCombination Source #
Constructors
KeyCombination | |
Instances
Constructors
GHCupInfo | |
Instances
FromJSON GHCupInfo Source # | |
Defined in GHCup.Types.JSON | |
ToJSON GHCupInfo Source # | |
Generic GHCupInfo Source # | |
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.0-inplace" '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.
An installable tool.
Instances
FromJSON Tool Source # | |
Defined in GHCup.Types.JSON | |
FromJSONKey Tool Source # | |
Defined in GHCup.Types.JSON | |
ToJSON Tool Source # | |
ToJSONKey Tool Source # | |
Defined in GHCup.Types.JSON | |
Bounded Tool Source # | |
Enum Tool Source # | |
Generic Tool Source # | |
Show Tool Source # | |
NFData Tool Source # | |
Defined in GHCup.Types | |
Eq Tool Source # | |
Ord Tool Source # | |
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.50.0-inplace" '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 ToolReqVersionSpec = Map (Maybe Version) PlatformReqSpec Source #
data GHCTargetVersion Source #
A GHC identified by the target platform triple and the version.
Constructors
GHCTargetVersion | |
Fields
|
Instances
data VersionInfo Source #
All necessary information of a tool version, including source download and per-architecture downloads.
Constructors
VersionInfo | |
Fields
|
Instances
data Architecture Source #
Instances
type PlatformVersionSpec = Map (Maybe VersionRange) DownloadInfo Source #
data LinuxDistro Source #
Constructors
Debian | |
Ubuntu | |
Mint | |
Fedora | |
CentOS | |
RedHat | |
Alpine | |
AmazonLinux | |
Rocky | |
Void | |
Gentoo | |
Exherbo | |
OpenSUSE | |
UnknownLinux |
Instances
How to descend into a tar archive.
Instances
FromJSON TarDir Source # | |
Defined in GHCup.Types.JSON | |
ToJSON TarDir Source # | |
Generic TarDir Source # | |
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.0-inplace" '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 DownloadMirror Source #
Constructors
DownloadMirror | |
Fields
|
Instances
newtype DownloadMirrors Source #
Constructors
DM (Map Text DownloadMirror) |
Instances
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
data NewURLSource Source #
Constructors
NewGHCupURL | |
NewStackSetupURL | |
NewGHCupInfo GHCupInfo | |
NewSetupInfo SetupInfo | |
NewURI URI | |
NewChannelAlias ChannelAlias |
Instances
data ChannelAlias Source #
Alias for ease of URLSource selection
Instances
data UserSettings Source #
Constructors
UserSettings | |
Fields
|
Instances
Instances
data Downloader Source #
Instances
data UserKeyBindings Source #
Constructors
UserKeyBindings | |
Fields |
Instances
data GPGSetting Source #
Instances
data PlatformRequest Source #
Constructors
PlatformRequest | |
Fields
|
Instances
data PagerConfig Source #
Instances
Constructors
Settings | |
Fields
|
Instances
data KeyBindings Source #
Constructors
KeyBindings | |
Fields |
Instances
Constructors
AppState | |
Fields
|
Instances
Generic AppState Source # | |
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.0-inplace" '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 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 LeanAppState Source #
Constructors
LeanAppState | |
Fields
|
Instances
Instances
Generic MSYS2Env Source # | |
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.0-inplace" '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
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 |
Instances
Show GitBranch Source # | |
Eq GitBranch Source # | |
Ord GitBranch 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
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 # |
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 # |
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 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 # |
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
tagToString :: Tag -> String Source #
archToString :: Architecture -> String Source #
platformToString :: Platform -> String Source #
distroToString :: LinuxDistro -> String Source #
allDistros :: [LinuxDistro] Source #
channelAliasText :: ChannelAlias -> Text Source #
fromURLSource :: URLSource -> [NewURLSource] Source #
fromSettings :: Settings -> Maybe KeyBindings -> UserSettings Source #
fromAppState :: AppState -> LeanAppState Source #
allPagerConfig :: String -> PagerConfig Source #
mkTVer :: Version -> GHCTargetVersion Source #
tVerToText :: GHCTargetVersion -> Text Source #
isSafeDir :: InstallDirResolved -> Bool Source #
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
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 | |
Read Modifier | |
Show Modifier | |
NFData Modifier | |
Defined in Graphics.Vty.Input.Events | |
Eq Modifier | |
Ord Modifier | |
Defined in Graphics.Vty.Input.Events | |
type Rep Modifier | |
Defined in Graphics.Vty.Input.Events type Rep Modifier = D1 ('MetaData "Modifier" "Graphics.Vty.Input.Events" "vty-6.2-b65764e2e4b14b99f3aa92575ea4c829046af9c45daf618b256312d73040c3b2" '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 Source #
Constructors
ArchiveFatal | |
ArchiveFailed | |
ArchiveWarn | |
ArchiveRetry | |
ArchiveOk | |
ArchiveEOF |
Instances
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 # | |