ghcup-hs/lib/GHCup/Errors.hs

125 lines
3.2 KiB
Haskell
Raw Permalink Normal View History

2020-03-08 17:30:08 +00:00
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DataKinds #-}
2020-03-03 00:59:19 +00:00
module GHCup.Errors where
import GHCup.Types
import Control.Exception.Safe
import Data.ByteString ( ByteString )
import Data.Text ( Text )
2020-03-08 17:30:08 +00:00
import Data.Versions
import Haskus.Utils.Variant
2020-03-03 00:59:19 +00:00
import HPath
2020-03-08 17:30:08 +00:00
------------------------
--[ Low-level errors ]--
------------------------
2020-03-03 00:59:19 +00:00
-- | A compatible platform could not be found.
2020-03-08 17:30:08 +00:00
data NoCompatiblePlatform = NoCompatiblePlatform String -- the platform we got
2020-03-03 00:59:19 +00:00
deriving Show
2020-03-08 17:30:08 +00:00
-- | Unable to find a download for the requested versio/distro.
2020-03-03 00:59:19 +00:00
data NoDownload = NoDownload
deriving Show
2020-03-08 17:30:08 +00:00
-- | The Architecture is unknown and unsupported.
2020-03-03 00:59:19 +00:00
data NoCompatibleArch = NoCompatibleArch String
deriving Show
2020-03-08 17:30:08 +00:00
-- | Unable to figure out the distribution of the host.
2020-03-03 00:59:19 +00:00
data DistroNotFound = DistroNotFound
deriving Show
2020-03-08 17:30:08 +00:00
-- | The archive format is unknown. We don't know how to extract it.
data UnknownArchive = UnknownArchive ByteString
2020-03-03 00:59:19 +00:00
deriving Show
2020-03-08 17:30:08 +00:00
-- | The scheme is not supported (such as ftp).
data UnsupportedScheme = UnsupportedScheme
2020-03-03 00:59:19 +00:00
deriving Show
2020-03-08 17:30:08 +00:00
-- | Unable to copy a file.
data CopyError = CopyError String
2020-03-03 00:59:19 +00:00
deriving Show
2020-03-08 17:30:08 +00:00
-- | Unable to find a tag of a tool.
2020-03-03 00:59:19 +00:00
data TagNotFound = TagNotFound Tag Tool
deriving Show
2020-03-08 17:30:08 +00:00
-- | The tool (such as GHC) is already installed with that version.
data AlreadyInstalled = AlreadyInstalled Tool Version
2020-03-03 00:59:19 +00:00
deriving Show
2020-03-08 17:30:08 +00:00
-- | The tool is not installed. Some operations rely on a tool
-- to be installed (such as setting the current GHC version).
data NotInstalled = NotInstalled Tool Version
2020-03-03 00:59:19 +00:00
deriving Show
2020-03-08 17:30:08 +00:00
-- | JSON decoding failed.
2020-03-03 00:59:19 +00:00
data JSONError = JSONDecodeError String
deriving Show
2020-03-08 17:30:08 +00:00
-- | A file that is supposed to exist does not exist
-- (e.g. when we use file scheme to "download" something).
data FileDoesNotExistError = FileDoesNotExistError ByteString
2020-03-03 00:59:19 +00:00
deriving Show
2020-03-08 17:30:08 +00:00
-- | File digest verification failed.
data DigestError = DigestError Text Text
deriving Show
2020-03-03 00:59:19 +00:00
2020-03-08 17:30:08 +00:00
-- | Unexpected HTTP status.
data HTTPStatusError = HTTPStatusError Int
2020-03-03 00:59:19 +00:00
deriving Show
2020-03-08 17:30:08 +00:00
-- | The 'Location' header was expected during a 3xx redirect, but not found.
data NoLocationHeader = NoLocationHeader
2020-03-03 00:59:19 +00:00
deriving Show
2020-03-08 17:30:08 +00:00
-- | Too many redirects.
data TooManyRedirs = TooManyRedirs
2020-03-03 00:59:19 +00:00
deriving Show
2020-03-08 17:30:08 +00:00
-------------------------
--[ High-level errors ]--
-------------------------
-- | A download failed. The underlying error is encapsulated.
data DownloadFailed = forall es . Show (V es) => DownloadFailed (V es)
deriving instance Show DownloadFailed
-- | A build failed.
data BuildFailed = forall es . Show (V es) => BuildFailed (Path Abs) (V es)
deriving instance Show BuildFailed
-- | Setting the current GHC version failed.
data GHCupSetError = forall es . Show (V es) => GHCupSetError (V es)
deriving instance Show GHCupSetError
---------------------------------------------
--[ True Exceptions (e.g. for MonadThrow) ]--
---------------------------------------------
-- | Parsing failed.
data ParseError = ParseError String
2020-03-03 00:59:19 +00:00
deriving Show
2020-03-08 17:30:08 +00:00
instance Exception ParseError