2021-03-01 23:15:03 +00:00
{- # OPTIONS_GHC - Wno - orphans # -}
{- # LANGUAGE CPP # -}
2021-03-11 16:03:51 +00:00
{- # LANGUAGE DataKinds # -}
2020-01-11 20:15:05 +00:00
{- # LANGUAGE ExistentialQuantification # -}
{- # LANGUAGE FlexibleContexts # -}
{- # LANGUAGE StandaloneDeriving # -}
2021-03-01 23:15:03 +00:00
{- # LANGUAGE TypeOperators # -}
{- # LANGUAGE FlexibleInstances # -}
2022-12-19 16:10:19 +00:00
{- # LANGUAGE RankNTypes # -}
2020-01-11 20:15:05 +00:00
2020-07-21 23:08:58 +00:00
{- |
Module : GHCup . Errors
Description : GHCup error types
Copyright : ( c ) Julian Ospald , 2020
2020-07-30 18:04:02 +00:00
License : LGPL - 3.0
2020-07-21 23:08:58 +00:00
Maintainer : hasufell @ hasufell . de
Stability : experimental
2021-05-14 21:09:45 +00:00
Portability : portable
2020-07-21 23:08:58 +00:00
- }
2020-01-11 20:15:05 +00:00
module GHCup.Errors where
import GHCup.Types
2021-03-01 23:15:03 +00:00
import Codec.Archive
2020-01-11 20:15:05 +00:00
import Control.Exception.Safe
2021-07-24 14:36:31 +00:00
import Data.ByteString ( ByteString )
import Data.CaseInsensitive ( CI )
2020-01-11 20:15:05 +00:00
import Data.Text ( Text )
import Data.Versions
2021-03-01 23:15:03 +00:00
import Haskus.Utils.Variant
2022-05-02 17:54:37 +00:00
import System.FilePath
2021-07-20 19:45:24 +00:00
import Text.PrettyPrint hiding ( ( <> ) )
import Text.PrettyPrint.HughesPJClass hiding ( ( <> ) )
2021-03-01 23:15:03 +00:00
import URI.ByteString
2020-01-11 20:15:05 +00:00
2021-07-24 14:36:31 +00:00
import qualified Data.Map.Strict as M
2021-08-25 16:54:58 +00:00
import qualified Data.Text as T
2023-02-12 11:58:08 +00:00
import qualified Data.Text.Encoding as E
import qualified Data.Text.Encoding.Error as E
2022-12-19 16:10:19 +00:00
import Data.Data ( Proxy ( .. ) )
2023-05-01 09:46:27 +00:00
import Data.Time ( Day )
2022-12-19 16:10:19 +00:00
allHFError :: String
allHFError = unlines allErrors
where
format p = " GHCup- " <> show ( eBase p ) <> " " <> eDesc p
format'' e p = " GHCup- " <> show ( eNum e ) <> " " <> eDesc p
format' e _ = " GHCup- " <> show ( eNum e ) <> " " <> prettyShow e
format''' e _ str' = " GHCup- " <> show ( eNum e ) <> " " <> str'
allErrors =
[ " # low level errors (1 to 500) "
, let proxy = Proxy :: Proxy NoCompatiblePlatform in format proxy
, let proxy = Proxy :: Proxy NoDownload in format proxy
, let proxy = Proxy :: Proxy NoUpdate in format proxy
, let proxy = Proxy :: Proxy DistroNotFound in format proxy
, let proxy = Proxy :: Proxy UnknownArchive in format proxy
, let proxy = Proxy :: Proxy UnsupportedScheme in format proxy
, let proxy = Proxy :: Proxy CopyError in format proxy
, let proxy = Proxy :: Proxy MergeFileTreeError in format proxy
, let proxy = Proxy :: Proxy TagNotFound in format proxy
2023-05-01 09:46:27 +00:00
, let proxy = Proxy :: Proxy DayNotFound in format proxy
2022-12-19 16:10:19 +00:00
, let proxy = Proxy :: Proxy NextVerNotFound in format proxy
, let proxy = Proxy :: Proxy AlreadyInstalled in format proxy
, let proxy = Proxy :: Proxy DirNotEmpty in format proxy
, let proxy = Proxy :: Proxy NotInstalled in format proxy
, let proxy = Proxy :: Proxy UninstallFailed in format proxy
, let proxy = Proxy :: Proxy NotFoundInPATH in format proxy
, let proxy = Proxy :: Proxy JSONError in format proxy
, let proxy = Proxy :: Proxy FileDoesNotExistError in format proxy
, let proxy = Proxy :: Proxy FileAlreadyExistsError in format proxy
, let proxy = Proxy :: Proxy TarDirDoesNotExist in format proxy
, let proxy = Proxy :: Proxy DigestError in format proxy
, let proxy = Proxy :: Proxy GPGError in format proxy
, let proxy = Proxy :: Proxy HTTPStatusError in format proxy
, let proxy = Proxy :: Proxy MalformedHeaders in format proxy
, let proxy = Proxy :: Proxy HTTPNotModified in format proxy
, let proxy = Proxy :: Proxy NoLocationHeader in format proxy
, let proxy = Proxy :: Proxy TooManyRedirs in format proxy
, let proxy = Proxy :: Proxy PatchFailed in format proxy
, let proxy = Proxy :: Proxy NoToolRequirements in format proxy
, let proxy = Proxy :: Proxy InvalidBuildConfig in format proxy
, let proxy = Proxy :: Proxy NoToolVersionSet in format proxy
, let proxy = Proxy :: Proxy NoNetwork in format proxy
, let proxy = Proxy :: Proxy HadrianNotFound in format proxy
, let proxy = Proxy :: Proxy ToolShadowed in format proxy
, let proxy = Proxy :: Proxy ContentLengthError in format proxy
2023-02-12 11:58:08 +00:00
, let proxy = Proxy :: Proxy DuplicateReleaseChannel in format proxy
2022-12-19 16:10:19 +00:00
, " "
2023-01-08 11:29:35 +00:00
, " # high level errors (4000+) "
2022-12-19 16:10:19 +00:00
, let proxy = Proxy :: Proxy DownloadFailed in format proxy
, let proxy = Proxy :: Proxy InstallSetError in format proxy
2023-01-08 11:29:35 +00:00
, let proxy = Proxy :: Proxy TestFailed in format proxy
2022-12-19 16:10:19 +00:00
, let proxy = Proxy :: Proxy BuildFailed in format proxy
, let proxy = Proxy :: Proxy GHCupSetError in format proxy
, " "
, " # true exceptions (500+) "
, let proxy = Proxy :: Proxy ParseError in format proxy
, let proxy = Proxy :: Proxy UnexpectedListLength in format proxy
, let proxy = Proxy :: Proxy NoUrlBase in format proxy
, " "
, " # orphans (800+) "
, let proxy = Proxy :: Proxy URIParseError in format proxy
, let proxy = Proxy :: Proxy URIParseError
e = MalformedScheme MissingColon
in format' e proxy
, let proxy = Proxy :: Proxy URIParseError
e = MalformedUserInfo
in format' e proxy
, let proxy = Proxy :: Proxy URIParseError
e = MalformedQuery
in format' e proxy
, let proxy = Proxy :: Proxy URIParseError
e = MalformedFragment
in format' e proxy
, let proxy = Proxy :: Proxy URIParseError
e = MalformedHost
in format' e proxy
, let proxy = Proxy :: Proxy URIParseError
e = MalformedPort
in format' e proxy
, let proxy = Proxy :: Proxy URIParseError
e = MalformedPath
in format' e proxy
, let proxy = Proxy :: Proxy URIParseError
e = OtherError " "
in format'' e proxy
, let proxy = Proxy :: Proxy ArchiveResult in format proxy
, let proxy = Proxy :: Proxy ArchiveResult
e = ArchiveFatal
in format' e proxy
, let proxy = Proxy :: Proxy ArchiveResult
e = ArchiveFailed
in format' e proxy
, let proxy = Proxy :: Proxy ArchiveResult
e = ArchiveWarn
in format' e proxy
, let proxy = Proxy :: Proxy ArchiveResult
e = ArchiveRetry
in format' e proxy
, let proxy = Proxy :: Proxy ArchiveResult
e = ArchiveOk
in format' e proxy
, let proxy = Proxy :: Proxy ArchiveResult
e = ArchiveEOF
in format' e proxy
, let proxy = Proxy :: Proxy ProcessError in format proxy
, let proxy = Proxy :: Proxy ProcessError
e = NonZeroExit 0 " " []
in format''' e proxy " A process returned a non-zero exit code. "
, let proxy = Proxy :: Proxy ProcessError
e = PTerminated " " []
in format''' e proxy " A process terminated prematurely. "
, let proxy = Proxy :: Proxy ProcessError
e = PStopped " " []
in format''' e proxy " A process stopped prematurely. "
, let proxy = Proxy :: Proxy ProcessError
e = NoSuchPid " " []
in format''' e proxy " Could not find PID for this process. "
]
prettyHFError :: ( Pretty e , HFErrorProject e ) => e -> String
2023-01-02 11:37:31 +00:00
prettyHFError e =
let errorCode = " GHCup- " <> padIntAndShow ( eNum e )
in ( " [ " <> linkEscapeCode errorCode ( hfErrorLink errorCode ) <> " ] " ) <> prettyShow e
where
hfErrorLink errorCode = " https://errors.haskell.org/messages/ " <> errorCode
padIntAndShow i
| i < 10 = " 0000 " <> show i
| i < 100 = " 000 " <> show i
| i < 1000 = " 00 " <> show i
| i < 10000 = " 0 " <> show i
| otherwise = show i
2022-12-19 16:10:19 +00:00
class HFErrorProject a where
eNum :: a -> Int
eNum _ = eBase ( Proxy :: Proxy a )
eBase :: Proxy a -> Int
eDesc :: Proxy a -> String
2020-01-11 20:15:05 +00:00
2023-01-08 11:29:35 +00:00
linkEscapeCode :: String -> String -> String
linkEscapeCode linkText link = " \ ESC ]8;; " <> link <> " \ ESC \ \ " <> linkText <> " \ ESC ]8;; \ ESC \ \ "
2020-01-11 20:15:05 +00:00
------------------------
--[ Low-level errors ]--
------------------------
-- | A compatible platform could not be found.
data NoCompatiblePlatform = NoCompatiblePlatform String -- the platform we got
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty NoCompatiblePlatform where
pPrint ( NoCompatiblePlatform str' ) =
text ( " Could not find a compatible platform. Got: " ++ str' )
2022-12-19 16:10:19 +00:00
instance HFErrorProject NoCompatiblePlatform where
eBase _ = 1
eDesc _ = " No compatible platform could be found "
2021-08-29 12:50:49 +00:00
-- | Unable to find a download for the requested version/distro.
2020-01-11 20:15:05 +00:00
data NoDownload = NoDownload
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty NoDownload where
pPrint NoDownload =
2022-12-19 16:10:19 +00:00
text ( eDesc ( Proxy :: Proxy NoDownload ) )
instance HFErrorProject NoDownload where
eBase _ = 10
eDesc _ = " Unable to find a download for the requested version/distro. "
2021-03-01 23:15:03 +00:00
2020-04-15 11:57:44 +00:00
-- | No update available or necessary.
data NoUpdate = NoUpdate
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty NoUpdate where
2022-12-19 16:10:19 +00:00
pPrint NoUpdate = text ( eDesc ( Proxy :: Proxy NoUpdate ) )
instance HFErrorProject NoUpdate where
eBase _ = 20
eDesc _ = " No update available or necessary. "
2021-03-01 23:15:03 +00:00
2020-01-11 20:15:05 +00:00
-- | The Architecture is unknown and unsupported.
data NoCompatibleArch = NoCompatibleArch String
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty NoCompatibleArch where
pPrint ( NoCompatibleArch arch ) =
text ( " The Architecture is unknown or unsupported. Got: " ++ arch )
2022-12-19 16:10:19 +00:00
instance HFErrorProject NoCompatibleArch where
eBase _ = 30
eDesc _ = " The Architecture is unknown and unsupported "
2020-01-11 20:15:05 +00:00
-- | Unable to figure out the distribution of the host.
data DistroNotFound = DistroNotFound
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty DistroNotFound where
pPrint DistroNotFound =
2022-12-19 16:10:19 +00:00
text ( eDesc ( Proxy :: Proxy DistroNotFound ) )
instance HFErrorProject DistroNotFound where
eBase _ = 40
eDesc _ = " Unable to figure out the distribution of the host "
2021-03-01 23:15:03 +00:00
2020-01-11 20:15:05 +00:00
-- | The archive format is unknown. We don't know how to extract it.
2021-05-14 21:09:45 +00:00
data UnknownArchive = UnknownArchive FilePath
2020-01-11 20:15:05 +00:00
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty UnknownArchive where
pPrint ( UnknownArchive file ) =
2021-08-25 16:54:58 +00:00
text $ " The archive format is unknown. We don't know how to extract the file " <> file
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject UnknownArchive where
eBase _ = 50
eDesc _ = " The archive format is unknown. We don't know how to extract it. "
2020-01-11 20:15:05 +00:00
-- | The scheme is not supported (such as ftp).
data UnsupportedScheme = UnsupportedScheme
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty UnsupportedScheme where
2022-12-19 16:10:19 +00:00
pPrint UnsupportedScheme =
text ( eDesc ( Proxy :: Proxy UnsupportedScheme ) )
instance HFErrorProject UnsupportedScheme where
eBase _ = 60
eDesc _ = " The scheme is not supported (such as ftp). "
2021-03-01 23:15:03 +00:00
2020-01-11 20:15:05 +00:00
-- | Unable to copy a file.
data CopyError = CopyError String
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty CopyError where
pPrint ( CopyError reason ) =
text ( " Unable to copy a file. Reason was: " ++ reason )
2022-12-19 16:10:19 +00:00
instance HFErrorProject CopyError where
eBase _ = 70
eDesc _ = " Unable to copy a file. "
2022-05-19 21:17:58 +00:00
-- | Unable to merge file trees.
data MergeFileTreeError = MergeFileTreeError IOException FilePath FilePath
deriving Show
instance Pretty MergeFileTreeError where
pPrint ( MergeFileTreeError e from to ) =
text " Failed to merge file tree from " <+> text from <+> text " to " <+> text to <+> text " \ n exception was: " <+> text ( displayException e )
2022-05-28 14:44:08 +00:00
<+> text " \ n ...you may need to delete " <+> text to <+> text " manually. Make sure it's gone. "
2022-05-19 21:17:58 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject MergeFileTreeError where
eBase _ = 80
eDesc _ = " Unable to merge file trees during installation "
2020-01-11 20:15:05 +00:00
-- | Unable to find a tag of a tool.
data TagNotFound = TagNotFound Tag Tool
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty TagNotFound where
pPrint ( TagNotFound tag tool ) =
2021-08-25 16:54:58 +00:00
text " Unable to find tag " <+> pPrint tag <+> text " of tool " <+> pPrint tool
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject TagNotFound where
eBase _ = 90
eDesc _ = " Unable to find a tag of a tool "
2023-05-01 09:46:27 +00:00
-- | Unable to find a release day of a tool
2023-05-14 13:34:50 +00:00
data DayNotFound = DayNotFound Day Tool ( Maybe Day )
2023-05-01 09:46:27 +00:00
deriving Show
instance Pretty DayNotFound where
2023-05-14 13:34:50 +00:00
pPrint ( DayNotFound day tool Nothing ) =
2023-05-01 09:46:27 +00:00
text " Unable to find release date " <+> text ( show day ) <+> text " of tool " <+> pPrint tool
2023-05-14 13:34:50 +00:00
pPrint ( DayNotFound day tool ( Just alternateDay ) ) =
text " Unable to find release date " <+> text ( show day ) <+> text " of tool " <+> pPrint tool <+>
text " but found an alternative date " <+> text ( show alternateDay )
2023-05-01 09:46:27 +00:00
instance HFErrorProject DayNotFound where
eBase _ = 95
eDesc _ = " Unable to find a release date of a tool "
2021-02-25 17:21:25 +00:00
-- | Unable to find the next version of a tool (the one after the currently
-- set one).
data NextVerNotFound = NextVerNotFound Tool
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty NextVerNotFound where
pPrint ( NextVerNotFound tool ) =
2021-08-25 16:54:58 +00:00
text " Unable to find next (the one after the currently set one) version of tool " <+> pPrint tool
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject NextVerNotFound where
eBase _ = 100
eDesc _ = " Unable to find the next version of a tool (the one after the currently set one) "
2020-01-11 20:15:05 +00:00
-- | The tool (such as GHC) is already installed with that version.
data AlreadyInstalled = AlreadyInstalled Tool Version
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty AlreadyInstalled where
pPrint ( AlreadyInstalled tool ver' ) =
2022-07-11 14:01:40 +00:00
( pPrint tool <> text " - " <> pPrint ver' ) <+> text " is already installed; "
2022-08-23 11:59:08 +00:00
<+> text " if you really want to reinstall it, you may want to run 'ghcup install " <+> pPrint tool <+> text " --force " <+> ( pPrint ver' <> text " ' " )
2022-05-23 21:49:43 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject AlreadyInstalled where
eBase _ = 110
eDesc _ = " The tool (such as GHC) is already installed with that version "
2021-03-01 23:15:03 +00:00
2021-08-11 10:24:51 +00:00
-- | The Directory is supposed to be empty, but wasn't.
data DirNotEmpty = DirNotEmpty { path :: FilePath }
2022-05-23 21:32:58 +00:00
deriving Show
2021-08-10 14:41:32 +00:00
2021-08-11 10:24:51 +00:00
instance Pretty DirNotEmpty where
pPrint ( DirNotEmpty path ) = do
2021-08-25 16:54:58 +00:00
text $ " The directory was expected to be empty, but isn't: " <> path
2021-08-10 14:41:32 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject DirNotEmpty where
eBase _ = 120
eDesc _ = " The Directory is supposed to be empty, but wasn't "
2020-01-11 20:15:05 +00:00
-- | The tool is not installed. Some operations rely on a tool
-- to be installed (such as setting the current GHC version).
2021-03-01 23:15:03 +00:00
data NotInstalled = NotInstalled Tool GHCTargetVersion
2020-01-11 20:15:05 +00:00
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty NotInstalled where
pPrint ( NotInstalled tool ver ) =
2021-08-25 16:54:58 +00:00
text " The version " <+> pPrint ver <+> text " of the tool " <+> pPrint tool <+> text " is not installed. "
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject NotInstalled where
eBase _ = 130
eDesc _ = " The required tool is not installed "
2022-05-12 15:58:40 +00:00
data UninstallFailed = UninstallFailed FilePath [ FilePath ]
deriving Show
instance Pretty UninstallFailed where
pPrint ( UninstallFailed dir files ) =
text " The following files survived uninstallation: " <+> pPrint files <+> text " ...consider removing " <+> pPrint dir <+> text " manually. "
2022-12-19 16:10:19 +00:00
instance HFErrorProject UninstallFailed where
eBase _ = 140
eDesc _ = " Uninstallation failed with leftover files "
2020-04-10 20:44:43 +00:00
-- | An executable was expected to be in PATH, but was not found.
2021-05-14 21:09:45 +00:00
data NotFoundInPATH = NotFoundInPATH FilePath
2020-04-10 20:44:43 +00:00
deriving Show
2021-10-03 09:38:53 +00:00
instance Exception NotFoundInPATH
2021-03-01 23:15:03 +00:00
instance Pretty NotFoundInPATH where
pPrint ( NotFoundInPATH exe ) =
2021-08-25 16:54:58 +00:00
text $ " The exe " <> exe <> " was not found in PATH. "
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject NotFoundInPATH where
eBase _ = 150
eDesc _ = " An executable was expected to be in PATH, but was not found "
2020-01-11 20:15:05 +00:00
-- | JSON decoding failed.
data JSONError = JSONDecodeError String
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty JSONError where
pPrint ( JSONDecodeError err ) =
2021-08-25 16:54:58 +00:00
text $ " JSON decoding failed with: " <> err
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject JSONError where
eBase _ = 160
eDesc _ = " JSON decoding failed "
2020-01-11 20:15:05 +00:00
-- | A file that is supposed to exist does not exist
-- (e.g. when we use file scheme to "download" something).
2021-05-14 21:09:45 +00:00
data FileDoesNotExistError = FileDoesNotExistError FilePath
2020-01-11 20:15:05 +00:00
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty FileDoesNotExistError where
pPrint ( FileDoesNotExistError file ) =
2021-08-25 16:54:58 +00:00
text $ " File " <> file <> " does not exist. "
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject FileDoesNotExistError where
eBase _ = 170
eDesc _ = " A file that is supposed to exist does not exist (oops) "
2021-08-11 04:58:30 +00:00
-- | 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 FileAlreadyExistsError = FileAlreadyExistsError FilePath
deriving Show
instance Pretty FileAlreadyExistsError where
pPrint ( FileAlreadyExistsError file ) =
2021-08-25 16:54:58 +00:00
text $ " File " <> file <> " Already exists. "
2021-08-11 04:58:30 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject FileAlreadyExistsError where
eBase _ = 180
eDesc _ = " A file already exists that wasn't expected to exist "
2020-08-06 11:28:20 +00:00
data TarDirDoesNotExist = TarDirDoesNotExist TarDir
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty TarDirDoesNotExist where
pPrint ( TarDirDoesNotExist dir ) =
text " Tar directory does not exist: " <+> pPrint dir
2022-12-19 16:10:19 +00:00
instance HFErrorProject TarDirDoesNotExist where
eBase _ = 190
eDesc _ = " The tar directory (e.g. inside an archive) does not exist "
2020-01-11 20:15:05 +00:00
-- | File digest verification failed.
2021-09-19 19:24:21 +00:00
data DigestError = DigestError FilePath Text Text
2020-01-11 20:15:05 +00:00
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty DigestError where
2021-09-19 19:24:21 +00:00
pPrint ( DigestError fp currentDigest expectedDigest ) =
text " Digest error for " <+> text ( fp <> " : expected " )
<+> text ( T . unpack expectedDigest ) <+> text " but got " <+> pPrint currentDigest <+> text
" \ n Consider removing the file in case it's cached and try again. "
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject DigestError where
eBase _ = 200
eDesc _ = " File digest verification failed "
2022-12-21 16:31:41 +00:00
2022-12-19 16:10:19 +00:00
-- | File PGP verification failed.
2021-09-18 17:45:32 +00:00
data GPGError = forall xs . ( ToVariantMaybe DownloadFailed xs , PopVariant DownloadFailed xs , Show ( V xs ) , Pretty ( V xs ) ) => GPGError ( V xs )
deriving instance Show GPGError
instance Pretty GPGError where
pPrint ( GPGError reason ) = text " GPG verify failed: " <+> pPrint reason
2022-12-19 16:10:19 +00:00
instance HFErrorProject GPGError where
eBase _ = 210
eDesc _ = " File PGP verification failed "
2020-01-11 20:15:05 +00:00
-- | Unexpected HTTP status.
2021-07-24 14:36:31 +00:00
data HTTPStatusError = HTTPStatusError Int ( M . Map ( CI ByteString ) ByteString )
2020-01-11 20:15:05 +00:00
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty HTTPStatusError where
2021-07-24 14:36:31 +00:00
pPrint ( HTTPStatusError status _ ) =
2021-08-25 16:54:58 +00:00
text " Unexpected HTTP status: " <+> pPrint status
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject HTTPStatusError where
eBase _ = 220
eDesc _ = " Unexpected HTTP status error (e.g. during downloads) "
2021-07-24 14:36:31 +00:00
-- | Malformed headers.
data MalformedHeaders = MalformedHeaders Text
deriving Show
instance Pretty MalformedHeaders where
pPrint ( MalformedHeaders h ) =
2021-08-25 16:54:58 +00:00
text " Headers are malformed: " <+> pPrint h
2021-07-24 14:36:31 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject MalformedHeaders where
eBase _ = 230
eDesc _ = " Malformed headers during download "
2021-07-24 14:36:31 +00:00
-- | Unexpected HTTP status.
data HTTPNotModified = HTTPNotModified Text
deriving Show
instance Pretty HTTPNotModified where
pPrint ( HTTPNotModified etag ) =
2021-08-25 16:54:58 +00:00
text " Remote resource not modifed, etag was: " <+> pPrint etag
2021-07-24 14:36:31 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject HTTPNotModified where
eBase _ = 240
eDesc _ = " Not modified HTTP status error (e.g. during downloads). "
2020-01-11 20:15:05 +00:00
-- | The 'Location' header was expected during a 3xx redirect, but not found.
data NoLocationHeader = NoLocationHeader
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty NoLocationHeader where
pPrint NoLocationHeader =
2022-12-19 16:10:19 +00:00
text ( eDesc ( Proxy :: Proxy NoLocationHeader ) )
instance HFErrorProject NoLocationHeader where
eBase _ = 250
eDesc _ = " The 'Location' header was expected during a 3xx redirect, but not found. "
2021-03-01 23:15:03 +00:00
2020-01-11 20:15:05 +00:00
-- | Too many redirects.
data TooManyRedirs = TooManyRedirs
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty TooManyRedirs where
pPrint TooManyRedirs =
2022-12-19 16:10:19 +00:00
text ( eDesc ( Proxy :: Proxy TooManyRedirs ) )
instance HFErrorProject TooManyRedirs where
eBase _ = 260
eDesc _ = " Too many redirections. "
2021-03-01 23:15:03 +00:00
2020-04-08 20:57:57 +00:00
-- | A patch could not be applied.
data PatchFailed = PatchFailed
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty PatchFailed where
pPrint PatchFailed =
2022-12-19 16:10:19 +00:00
text ( eDesc ( Proxy :: Proxy PatchFailed ) )
instance HFErrorProject PatchFailed where
eBase _ = 270
eDesc _ = " A patch could not be applied. "
2021-03-01 23:15:03 +00:00
2020-04-10 15:36:27 +00:00
-- | The tool requirements could not be found.
data NoToolRequirements = NoToolRequirements
deriving Show
2020-01-11 20:15:05 +00:00
2021-03-01 23:15:03 +00:00
instance Pretty NoToolRequirements where
pPrint NoToolRequirements =
2022-12-19 16:10:19 +00:00
text ( eDesc ( Proxy :: Proxy NoToolRequirements ) )
instance HFErrorProject NoToolRequirements where
eBase _ = 280
eDesc _ = " The Tool requirements could not be found. "
2021-03-01 23:15:03 +00:00
2020-04-25 10:06:41 +00:00
data InvalidBuildConfig = InvalidBuildConfig Text
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty InvalidBuildConfig where
pPrint ( InvalidBuildConfig reason ) =
2021-08-25 16:54:58 +00:00
text " The build config is invalid. Reason was: " <+> pPrint reason
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject InvalidBuildConfig where
eBase _ = 290
eDesc _ = " The build config is invalid. "
2021-02-25 17:21:25 +00:00
data NoToolVersionSet = NoToolVersionSet Tool
deriving Show
2020-04-25 10:06:41 +00:00
2021-03-01 23:15:03 +00:00
instance Pretty NoToolVersionSet where
pPrint ( NoToolVersionSet tool ) =
2021-08-25 16:54:58 +00:00
text " No version is set for tool " <+> pPrint tool <+> text " . "
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject NoToolVersionSet where
eBase _ = 300
eDesc _ = " No version is set for tool (but was expected). "
2021-07-18 21:29:09 +00:00
data NoNetwork = NoNetwork
deriving Show
instance Pretty NoNetwork where
pPrint NoNetwork =
2022-12-19 16:10:19 +00:00
text ( eDesc ( Proxy :: Proxy NoNetwork ) )
instance HFErrorProject NoNetwork where
eBase _ = 310
eDesc _ = " A download was required or requested, but '--offline' was specified. "
2021-07-18 21:29:09 +00:00
2021-07-20 19:45:24 +00:00
data HadrianNotFound = HadrianNotFound
deriving Show
instance Pretty HadrianNotFound where
pPrint HadrianNotFound =
2022-12-19 16:10:19 +00:00
text ( eDesc ( Proxy :: Proxy HadrianNotFound ) )
instance HFErrorProject HadrianNotFound where
eBase _ = 320
eDesc _ = " Could not find Hadrian build files. Does this GHC version support Hadrian builds? "
2021-07-20 19:45:24 +00:00
2022-05-23 14:48:29 +00:00
data ToolShadowed = ToolShadowed
Tool
2022-05-02 17:54:37 +00:00
FilePath -- shadow binary
FilePath -- upgraded binary
Version -- upgraded version
deriving Show
2022-05-23 14:48:29 +00:00
instance Pretty ToolShadowed where
pPrint ( ToolShadowed tool sh up _ ) =
text ( prettyShow tool
<> " is shadowed by "
2022-05-02 17:54:37 +00:00
<> sh
2022-05-23 14:48:29 +00:00
<> " . \ n The upgrade will not be in effect, unless you remove "
2022-05-02 17:54:37 +00:00
<> sh
2022-05-23 14:48:29 +00:00
<> " \ n or make sure "
2022-05-02 17:54:37 +00:00
<> takeDirectory up
<> " comes before "
<> takeDirectory sh
<> " in PATH. "
)
2020-01-11 20:15:05 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject ToolShadowed where
eBase _ = 330
eDesc _ = " A tool is shadowed in PATH. "
-- | File content length verification failed.
data ContentLengthError = ContentLengthError ( Maybe FilePath ) ( Maybe Integer ) Integer
deriving Show
instance Pretty ContentLengthError where
pPrint ( ContentLengthError Nothing Nothing expectedSize ) =
text " Content length exceeded expected size: "
<+> text ( show expectedSize )
<+> text " \ n Consider removing the file in case it's cached and try again. "
pPrint ( ContentLengthError Nothing ( Just currentSize ) expectedSize ) =
text " Content length error. Expected "
<+> text ( show expectedSize ) <+> text " but got " <+> pPrint currentSize <+> text
" \ n Consider removing the file in case it's cached and try again. "
pPrint ( ContentLengthError ( Just fp ) ( Just currentSize ) expectedSize ) =
text " Content length error for " <+> text ( fp <> " : expected " )
<+> text ( show expectedSize ) <+> text " but got " <+> pPrint currentSize <+> text
" \ n Consider removing the file in case it's cached and try again. "
pPrint ( ContentLengthError ( Just fp ) Nothing expectedSize ) =
text " Content length error for " <+> text ( fp <> " : expected " )
<+> text ( show expectedSize ) <+> text " \ n Consider removing the file in case it's cached and try again. "
instance Exception ContentLengthError
instance HFErrorProject ContentLengthError where
eBase _ = 340
eDesc _ = " File content length verification failed "
2023-02-12 11:58:08 +00:00
data DuplicateReleaseChannel = DuplicateReleaseChannel URI
deriving Show
instance HFErrorProject DuplicateReleaseChannel where
eBase _ = 350
eDesc _ = " Duplicate release channel detected when adding URI. \ n Giving up. You can use '--force' to remove and append the duplicate URI (this may change order/semantics). "
instance Pretty DuplicateReleaseChannel where
pPrint ( DuplicateReleaseChannel uri ) =
text $ " Duplicate release channel detected when adding: \ n "
<> ( T . unpack . E . decodeUtf8With E . lenientDecode . serializeURIRef' ) uri
<> " \ n Giving up. You can use '--force' to remove and append the duplicate URI (this may change order/semantics). "
2020-01-11 20:15:05 +00:00
-------------------------
--[ High-level errors ]--
-------------------------
-- | A download failed. The underlying error is encapsulated.
2022-12-19 16:10:19 +00:00
data DownloadFailed = forall xs . ( HFErrorProject ( V xs ) , ToVariantMaybe DownloadFailed xs , PopVariant DownloadFailed xs , Show ( V xs ) , Pretty ( V xs ) ) => DownloadFailed ( V xs )
2021-03-01 23:15:03 +00:00
instance Pretty DownloadFailed where
pPrint ( DownloadFailed reason ) =
2021-09-06 20:31:07 +00:00
case reason of
VMaybe ( _ :: DownloadFailed ) -> pPrint reason
_ -> text " Download failed: " <+> pPrint reason
2020-01-11 20:15:05 +00:00
deriving instance Show DownloadFailed
2022-12-19 16:10:19 +00:00
instance HFErrorProject DownloadFailed where
eBase _ = 5000
eNum ( DownloadFailed xs ) = 5000 + eNum xs
eDesc _ = " A download failed. "
data InstallSetError = 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 )
2022-05-23 21:32:58 +00:00
instance Pretty InstallSetError where
pPrint ( InstallSetError reason1 reason2 ) =
text " Both installation and setting the tool failed. Install error was: "
<+> pPrint reason1
<+> text " \ n Set error was: "
<+> pPrint reason2
deriving instance Show InstallSetError
2022-12-19 16:10:19 +00:00
instance HFErrorProject InstallSetError where
eBase _ = 7000
-- will there be collisions?
eNum ( InstallSetError xs1 xs2 ) = 7000 + eNum xs1 + eNum xs2
eDesc _ = " Installation or setting the tool failed. "
2020-01-11 20:15:05 +00:00
2023-01-08 11:29:35 +00:00
-- | A test failed.
data TestFailed = forall es . ( ToVariantMaybe TestFailed es , PopVariant TestFailed es , Pretty ( V es ) , Show ( V es ) , HFErrorProject ( V es ) ) => TestFailed FilePath ( V es )
instance Pretty TestFailed where
pPrint ( TestFailed path reason ) =
case reason of
VMaybe ( _ :: TestFailed ) -> pPrint reason
_ -> text ( " The test failed. GHC test suite is fragile and non-portable. Please also check out the " <> linkEscapeCode " issue tracker " " https://gitlab.haskell.org/ghc/ghc/-/issues/?sort=updated_desc&state=opened&label_name%5B%5D=testsuite&label_name%5B%5D=packaging&first_page_size=20 " <> " . \ n Build dir was: " ) <+> text path <+> text " \ n Reason was: " <+> pPrint reason
deriving instance Show TestFailed
instance HFErrorProject TestFailed where
eBase _ = 4000
eNum ( TestFailed _ xs2 ) = 4000 + eNum xs2
eDesc _ = " The test failed. "
2020-01-11 20:15:05 +00:00
-- | A build failed.
2022-12-19 16:10:19 +00:00
data BuildFailed = forall es . ( ToVariantMaybe BuildFailed es , PopVariant BuildFailed es , Pretty ( V es ) , Show ( V es ) , HFErrorProject ( V es ) ) => BuildFailed FilePath ( V es )
2020-01-11 20:15:05 +00:00
2021-03-01 23:15:03 +00:00
instance Pretty BuildFailed where
pPrint ( BuildFailed path reason ) =
2021-09-06 20:31:07 +00:00
case reason of
VMaybe ( _ :: BuildFailed ) -> pPrint reason
_ -> text " BuildFailed failed in dir " <+> text ( path <> " : " ) <+> pPrint reason
2021-03-01 23:15:03 +00:00
2020-01-11 20:15:05 +00:00
deriving instance Show BuildFailed
2022-12-19 16:10:19 +00:00
instance HFErrorProject BuildFailed where
eBase _ = 8000
eNum ( BuildFailed _ xs2 ) = 8000 + eNum xs2
eDesc _ = " The build failed. "
2020-01-11 20:15:05 +00:00
-- | Setting the current GHC version failed.
2022-12-19 16:10:19 +00:00
data GHCupSetError = forall es . ( ToVariantMaybe GHCupSetError es , PopVariant GHCupSetError es , Show ( V es ) , Pretty ( V es ) , HFErrorProject ( V es ) ) => GHCupSetError ( V es )
2020-01-11 20:15:05 +00:00
2021-03-01 23:15:03 +00:00
instance Pretty GHCupSetError where
pPrint ( GHCupSetError reason ) =
2021-09-06 20:31:07 +00:00
case reason of
VMaybe ( _ :: GHCupSetError ) -> pPrint reason
2022-12-19 16:10:19 +00:00
_ -> text " Setting the current version failed: " <+> pPrint reason
2021-03-01 23:15:03 +00:00
2020-01-11 20:15:05 +00:00
deriving instance Show GHCupSetError
2022-12-19 16:10:19 +00:00
instance HFErrorProject GHCupSetError where
eBase _ = 9000
eNum ( GHCupSetError xs ) = 9000 + eNum xs
eDesc _ = " Setting the current version failed. "
2020-01-11 20:15:05 +00:00
---------------------------------------------
--[ True Exceptions (e.g. for MonadThrow) ]--
---------------------------------------------
-- | Parsing failed.
data ParseError = ParseError String
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty ParseError where
pPrint ( ParseError reason ) =
2021-08-25 16:54:58 +00:00
text " Parsing failed: " <+> pPrint reason
2021-03-01 23:15:03 +00:00
2020-01-11 20:15:05 +00:00
instance Exception ParseError
2020-09-20 15:57:16 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject ParseError where
eBase _ = 500
eDesc _ = " A parse error occured. "
2020-09-20 15:57:16 +00:00
data UnexpectedListLength = UnexpectedListLength String
deriving Show
2021-03-01 23:15:03 +00:00
instance Pretty UnexpectedListLength where
pPrint ( UnexpectedListLength reason ) =
2021-08-25 16:54:58 +00:00
text " List length unexpected: " <+> pPrint reason
2021-03-01 23:15:03 +00:00
2020-09-20 15:57:16 +00:00
instance Exception UnexpectedListLength
2022-12-19 16:10:19 +00:00
instance HFErrorProject UnexpectedListLength where
eBase _ = 510
eDesc _ = " A list had an unexpected length. "
2021-08-06 17:40:22 +00:00
data NoUrlBase = NoUrlBase Text
deriving Show
instance Pretty NoUrlBase where
pPrint ( NoUrlBase url ) =
2021-08-25 16:54:58 +00:00
text " Couldn't get a base filename from url " <+> pPrint url
2021-08-06 17:40:22 +00:00
instance Exception NoUrlBase
2022-12-19 16:10:19 +00:00
instance HFErrorProject NoUrlBase where
eBase _ = 520
eDesc _ = " URL does not have a base filename. "
2021-03-01 23:15:03 +00:00
------------------------
--[ orphan instances ]--
------------------------
instance Pretty ( V '[] ) where
{- # INLINABLE pPrint # -}
pPrint _ = undefined
instance
( Pretty x
, Pretty ( V xs )
) => Pretty ( V ( x ': xs ) )
where
pPrint v = case popVariantHead v of
Right x -> pPrint x
Left xs -> pPrint xs
2022-12-19 16:10:19 +00:00
instance HFErrorProject ( V '[] ) where
{- # INLINABLE eBase # -}
eBase _ = undefined
{- # INLINABLE eDesc # -}
eDesc _ = undefined
instance
( HFErrorProject x
, HFErrorProject ( V xs )
) => HFErrorProject ( V ( x ': xs ) )
where
eNum v = case popVariantHead v of
Right x -> eNum x
Left xs -> eNum xs
eDesc _ = undefined
eBase _ = undefined
2021-03-01 23:15:03 +00:00
instance Pretty URIParseError where
pPrint ( MalformedScheme reason ) =
2021-08-25 16:54:58 +00:00
text " Failed to parse URI. Malformed scheme: " <+> text ( show reason )
2021-03-01 23:15:03 +00:00
pPrint MalformedUserInfo =
2021-08-25 16:54:58 +00:00
text " Failed to parse URI. Malformed user info. "
2021-03-01 23:15:03 +00:00
pPrint MalformedQuery =
2021-08-25 16:54:58 +00:00
text " Failed to parse URI. Malformed query. "
2021-03-01 23:15:03 +00:00
pPrint MalformedFragment =
2021-08-25 16:54:58 +00:00
text " Failed to parse URI. Malformed fragment. "
2021-03-01 23:15:03 +00:00
pPrint MalformedHost =
2021-08-25 16:54:58 +00:00
text " Failed to parse URI. Malformed host. "
2021-03-01 23:15:03 +00:00
pPrint MalformedPort =
2021-08-25 16:54:58 +00:00
text " Failed to parse URI. Malformed port. "
2021-03-01 23:15:03 +00:00
pPrint MalformedPath =
2021-08-25 16:54:58 +00:00
text " Failed to parse URI. Malformed path. "
2021-03-01 23:15:03 +00:00
pPrint ( OtherError err ) =
2021-08-25 16:54:58 +00:00
text " Failed to parse URI: " <+> pPrint err
2021-03-01 23:15:03 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject URIParseError where
eBase _ = 800
eNum ( MalformedScheme NonAlphaLeading ) = 801
eNum ( MalformedScheme InvalidChars ) = 802
eNum ( MalformedScheme MissingColon ) = 803
eNum MalformedUserInfo = 804
eNum MalformedQuery = 805
eNum MalformedFragment = 806
eNum MalformedHost = 807
eNum MalformedPort = 808
eNum MalformedPath = 809
eNum ( OtherError _ ) = 810
eDesc _ = " Failed to parse URI. "
2021-03-01 23:15:03 +00:00
instance Pretty ArchiveResult where
pPrint ArchiveFatal = text " Archive result: fatal "
pPrint ArchiveFailed = text " Archive result: failed "
pPrint ArchiveWarn = text " Archive result: warning "
pPrint ArchiveRetry = text " Archive result: retry "
pPrint ArchiveOk = text " Archive result: Ok "
pPrint ArchiveEOF = text " Archive result: EOF "
2021-08-25 16:54:58 +00:00
2022-12-19 16:10:19 +00:00
instance HFErrorProject ArchiveResult where
eBase _ = 820
eNum ArchiveFatal = 821
eNum ArchiveFailed = 822
eNum ArchiveWarn = 823
eNum ArchiveRetry = 824
eNum ArchiveOk = 825
eNum ArchiveEOF = 826
eDesc _ = " Archive extraction result. "
2021-08-25 16:54:58 +00:00
instance Pretty T . Text where
pPrint = text . T . unpack
2022-12-19 16:10:19 +00:00
instance Pretty ProcessError where
pPrint ( NonZeroExit e exe args ) =
text " Process " <+> pPrint exe <+> text " with arguments " <+> pPrint args <+> text " failed with exit code " <+> text ( show e <> " . " )
pPrint ( PTerminated exe args ) =
text " Process " <+> pPrint exe <+> text " with arguments " <+> pPrint args <+> text " terminated. "
pPrint ( PStopped exe args ) =
text " Process " <+> pPrint exe <+> text " with arguments " <+> pPrint args <+> text " stopped. "
pPrint ( NoSuchPid exe args ) =
text " Could not find PID for process running " <+> pPrint exe <+> text " with arguments " <+> text ( show args ) <+> text " . "
instance HFErrorProject ProcessError where
eBase _ = 840
eNum NonZeroExit { } = 841
eNum ( PTerminated _ _ ) = 842
eNum ( PStopped _ _ ) = 843
eNum ( NoSuchPid _ _ ) = 844
eDesc _ = " A process exited prematurely. "