ghcup-0.1.22.0: ghc toolchain installer
Copyright(c) Julian Ospald 2020
LicenseLGPL-3.0
Maintainerhasufell@hasufell.de
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHCup.Errors

Description

 
Synopsis

Documentation

class HFErrorProject a where Source #

Minimal complete definition

eBase, eDesc

Methods

eNum :: a -> Int Source #

eBase :: Proxy a -> Int Source #

eDesc :: Proxy a -> String Source #

Instances

Instances details
HFErrorProject AlreadyInstalled Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject BuildFailed Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject ContentLengthError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject CopyError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject DayNotFound Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject DigestError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject DigestMissing Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject DirNotEmpty Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject DistroNotFound Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject DownloadFailed Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject DuplicateReleaseChannel Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject FileAlreadyExistsError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject FileDoesNotExistError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject GHCupSetError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject GPGError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject HTTPNotModified Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject HTTPStatusError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject HadrianNotFound Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject InstallSetError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject InvalidBuildConfig Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject JSONError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject MalformedHeaders Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject MergeFileTreeError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NextVerNotFound Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoCompatibleArch Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoCompatiblePlatform Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoDownload Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoLocationHeader Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoNetwork Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoToolRequirements Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoToolVersionSet Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoUpdate Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoUrlBase Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NotFoundInPATH Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NotInstalled Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject ParseError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject PatchFailed Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject StackPlatformDetectError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject TagNotFound Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject TarDirDoesNotExist Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject TestFailed Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject TooManyRedirs Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject ToolShadowed Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject UnexpectedListLength Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject UninstallFailed Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject UnknownArchive Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject UnsupportedScheme Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject UnsupportedSetupCombo Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject ProcessError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject ArchiveResult Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject URIParseError Source # 
Instance details

Defined in GHCup.Errors

(HFErrorProject x, HFErrorProject (V xs)) => HFErrorProject (V (x ': xs)) Source # 
Instance details

Defined in GHCup.Errors

Methods

eNum :: V (x ': xs) -> Int Source #

eBase :: Proxy (V (x ': xs)) -> Int Source #

eDesc :: Proxy (V (x ': xs)) -> String Source #

HFErrorProject (V ('[] :: [Type])) Source # 
Instance details

Defined in GHCup.Errors

Methods

eNum :: V '[] -> Int Source #

eBase :: Proxy (V '[]) -> Int Source #

eDesc :: Proxy (V '[]) -> String Source #

data NoDownload Source #

Unable to find a download for the requested version/distro.

Instances

Instances details
Show NoDownload Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoDownload Source # 
Instance details

Defined in GHCup.Errors

Pretty NoDownload Source # 
Instance details

Defined in GHCup.Errors

data NoUpdate Source #

No update available or necessary.

Constructors

NoUpdate 

Instances

Instances details
Show NoUpdate Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoUpdate Source # 
Instance details

Defined in GHCup.Errors

Pretty NoUpdate Source # 
Instance details

Defined in GHCup.Errors

data DistroNotFound Source #

Unable to figure out the distribution of the host.

Constructors

DistroNotFound 

data UnknownArchive Source #

The archive format is unknown. We don't know how to extract it.

Constructors

UnknownArchive FilePath 

data CopyError Source #

Unable to copy a file.

Constructors

CopyError String 

Instances

Instances details
Show CopyError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject CopyError Source # 
Instance details

Defined in GHCup.Errors

Pretty CopyError Source # 
Instance details

Defined in GHCup.Errors

data TagNotFound Source #

Unable to find a tag of a tool.

Constructors

TagNotFound Tag Tool 

Instances

Instances details
Show TagNotFound Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject TagNotFound Source # 
Instance details

Defined in GHCup.Errors

Pretty TagNotFound Source # 
Instance details

Defined in GHCup.Errors

data DayNotFound Source #

Unable to find a release day of a tool

Constructors

DayNotFound Day Tool (Maybe Day) 

Instances

Instances details
Show DayNotFound Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject DayNotFound Source # 
Instance details

Defined in GHCup.Errors

Pretty DayNotFound Source # 
Instance details

Defined in GHCup.Errors

data NextVerNotFound Source #

Unable to find the next version of a tool (the one after the currently set one).

Constructors

NextVerNotFound Tool 

data AlreadyInstalled Source #

The tool (such as GHC) is already installed with that version.

data DirNotEmpty Source #

The Directory is supposed to be empty, but wasn't.

Constructors

DirNotEmpty 

Fields

Instances

Instances details
Show DirNotEmpty Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject DirNotEmpty Source # 
Instance details

Defined in GHCup.Errors

Pretty DirNotEmpty Source # 
Instance details

Defined in GHCup.Errors

data NotInstalled Source #

The tool is not installed. Some operations rely on a tool to be installed (such as setting the current GHC version).

data JSONError Source #

JSON decoding failed.

Constructors

JSONDecodeError String 

Instances

Instances details
Show JSONError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject JSONError Source # 
Instance details

Defined in GHCup.Errors

Pretty JSONError Source # 
Instance details

Defined in GHCup.Errors

data FileDoesNotExistError Source #

A file that is supposed to exist does not exist (e.g. when we use file scheme to "download" something).

data FileAlreadyExistsError Source #

The file already exists (e.g. when we use isolated installs with the same path). (e.g. This is done to prevent any overwriting)

data DigestError Source #

File digest verification failed.

Instances

Instances details
Show DigestError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject DigestError Source # 
Instance details

Defined in GHCup.Errors

Pretty DigestError Source # 
Instance details

Defined in GHCup.Errors

data GPGError Source #

File PGP verification failed.

Constructors

forall xs.(ToVariantMaybe DownloadFailed xs, PopVariant DownloadFailed xs, Show (V xs), Pretty (V xs)) => GPGError (V xs) 

Instances

Instances details
Show GPGError Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject GPGError Source # 
Instance details

Defined in GHCup.Errors

Pretty GPGError Source # 
Instance details

Defined in GHCup.Errors

data NoLocationHeader Source #

The Location header was expected during a 3xx redirect, but not found.

Constructors

NoLocationHeader 

data TooManyRedirs Source #

Too many redirects.

Constructors

TooManyRedirs 

data PatchFailed Source #

A patch could not be applied.

Constructors

PatchFailed 

Instances

Instances details
Show PatchFailed Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject PatchFailed Source # 
Instance details

Defined in GHCup.Errors

Pretty PatchFailed Source # 
Instance details

Defined in GHCup.Errors

data NoNetwork Source #

Constructors

NoNetwork 

Instances

Instances details
Show NoNetwork Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject NoNetwork Source # 
Instance details

Defined in GHCup.Errors

Pretty NoNetwork Source # 
Instance details

Defined in GHCup.Errors

data DownloadFailed Source #

A download failed. The underlying error is encapsulated.

Constructors

forall xs.(HFErrorProject (V xs), ToVariantMaybe DownloadFailed xs, PopVariant DownloadFailed xs, Show (V xs), Pretty (V xs)) => DownloadFailed (V xs) 

data InstallSetError Source #

Constructors

forall xs1 xs2.(Show (V xs1), Pretty (V xs1), HFErrorProject (V xs1), Show (V xs2), Pretty (V xs2), HFErrorProject (V xs2)) => InstallSetError (V xs1) (V xs2) 

data TestFailed Source #

A test failed.

Constructors

forall es.(ToVariantMaybe TestFailed es, PopVariant TestFailed es, Pretty (V es), Show (V es), HFErrorProject (V es)) => TestFailed FilePath (V es) 

Instances

Instances details
Show TestFailed Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject TestFailed Source # 
Instance details

Defined in GHCup.Errors

Pretty TestFailed Source # 
Instance details

Defined in GHCup.Errors

data BuildFailed Source #

A build failed.

Constructors

forall es.(ToVariantMaybe BuildFailed es, PopVariant BuildFailed es, Pretty (V es), Show (V es), HFErrorProject (V es)) => BuildFailed FilePath (V es) 

Instances

Instances details
Show BuildFailed Source # 
Instance details

Defined in GHCup.Errors

HFErrorProject BuildFailed Source # 
Instance details

Defined in GHCup.Errors

Pretty BuildFailed Source # 
Instance details

Defined in GHCup.Errors

data GHCupSetError Source #

Setting the current GHC version failed.

Constructors

forall es.(ToVariantMaybe GHCupSetError es, PopVariant GHCupSetError es, Show (V es), Pretty (V es), HFErrorProject (V es)) => GHCupSetError (V es) 

Orphan instances

Pretty ProcessError Source # 
Instance details

Pretty ArchiveResult Source # 
Instance details

Pretty Text Source # 
Instance details

Pretty URIParseError Source # 
Instance details

(Pretty x, Pretty (V xs)) => Pretty (V (x ': xs)) Source # 
Instance details

Methods

pPrintPrec :: PrettyLevel -> Rational -> V (x ': xs) -> Doc #

pPrint :: V (x ': xs) -> Doc #

pPrintList :: PrettyLevel -> [V (x ': xs)] -> Doc #

Pretty (V ('[] :: [Type])) Source # 
Instance details

Methods

pPrintPrec :: PrettyLevel -> Rational -> V '[] -> Doc #

pPrint :: V '[] -> Doc #

pPrintList :: PrettyLevel -> [V '[]] -> Doc #