{-# OPTIONS_GHC -Wno-orphans #-}
{-# LANGUAGE CPP               #-}
{-# LANGUAGE BangPatterns      #-}
{-# LANGUAGE DataKinds         #-}
{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TemplateHaskell   #-}
{-# LANGUAGE DuplicateRecordFields #-}

{-|
Module      : GHCup.Types
Description : GHCup types
Copyright   : (c) Julian Ospald, 2020
License     : LGPL-3.0
Maintainer  : hasufell@hasufell.de
Stability   : experimental
Portability : portable
-}
module GHCup.Types
  ( module GHCup.Types
#if defined(BRICK)
  , Key(..)
#endif
  )
  where

import {-# SOURCE #-} GHCup.Utils.Dirs          ( fromGHCupPath, GHCupPath )

import           Control.DeepSeq                ( NFData, rnf )
import           Data.Map.Strict                ( Map )
import           Data.List.NonEmpty             ( NonEmpty (..) )
import           Data.Time.Calendar             ( Day )
import           Data.Text                      ( Text )
import           Data.Versions
import           GHC.IO.Exception               ( ExitCode )
import           Optics                         ( makeLenses )
import           Text.PrettyPrint.HughesPJClass (Pretty, pPrint, text)
import           URI.ByteString
#if defined(BRICK)
import           Graphics.Vty                   ( Key(..) )
#endif

import qualified Data.ByteString.Lazy          as BL
import qualified Data.Text                     as T
import qualified GHC.Generics                  as GHC


#if !defined(BRICK)
data Key = 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
    deriving (Eq,Show,Read,Ord,GHC.Generic)
#endif


    --------------------
    --[ GHCInfo Tree ]--
    --------------------


data GHCupInfo = GHCupInfo
  { GHCupInfo -> ToolRequirements
_toolRequirements :: ToolRequirements
  , GHCupInfo -> GHCupDownloads
_ghcupDownloads   :: GHCupDownloads
  , GHCupInfo -> Map GlobalTool DownloadInfo
_globalTools      :: Map GlobalTool DownloadInfo
  }
  deriving (Int -> GHCupInfo -> ShowS
[GHCupInfo] -> ShowS
GHCupInfo -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [GHCupInfo] -> ShowS
$cshowList :: [GHCupInfo] -> ShowS
show :: GHCupInfo -> FilePath
$cshow :: GHCupInfo -> FilePath
showsPrec :: Int -> GHCupInfo -> ShowS
$cshowsPrec :: Int -> GHCupInfo -> ShowS
Show, forall x. Rep GHCupInfo x -> GHCupInfo
forall x. GHCupInfo -> Rep GHCupInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GHCupInfo x -> GHCupInfo
$cfrom :: forall x. GHCupInfo -> Rep GHCupInfo x
GHC.Generic, GHCupInfo -> GHCupInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GHCupInfo -> GHCupInfo -> Bool
$c/= :: GHCupInfo -> GHCupInfo -> Bool
== :: GHCupInfo -> GHCupInfo -> Bool
$c== :: GHCupInfo -> GHCupInfo -> Bool
Eq)

instance NFData GHCupInfo



    -------------------------
    --[ Requirements Tree ]--
    -------------------------


type ToolRequirements = Map Tool ToolReqVersionSpec
type ToolReqVersionSpec = Map (Maybe Version) PlatformReqSpec
type PlatformReqSpec = Map Platform PlatformReqVersionSpec
type PlatformReqVersionSpec = Map (Maybe VersionRange) Requirements


data Requirements = Requirements
  { Requirements -> [Text]
_distroPKGs :: [Text]
  , Requirements -> Text
_notes      :: Text
  }
  deriving (Int -> Requirements -> ShowS
[Requirements] -> ShowS
Requirements -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Requirements] -> ShowS
$cshowList :: [Requirements] -> ShowS
show :: Requirements -> FilePath
$cshow :: Requirements -> FilePath
showsPrec :: Int -> Requirements -> ShowS
$cshowsPrec :: Int -> Requirements -> ShowS
Show, forall x. Rep Requirements x -> Requirements
forall x. Requirements -> Rep Requirements x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Requirements x -> Requirements
$cfrom :: forall x. Requirements -> Rep Requirements x
GHC.Generic, Requirements -> Requirements -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Requirements -> Requirements -> Bool
$c/= :: Requirements -> Requirements -> Bool
== :: Requirements -> Requirements -> Bool
$c== :: Requirements -> Requirements -> Bool
Eq)

instance NFData Requirements





    ---------------------
    --[ Download Tree ]--
    ---------------------


-- | Description of all binary and source downloads. This is a tree
-- of nested maps.
type GHCupDownloads = Map Tool ToolVersionSpec
type ToolVersionSpec = Map GHCTargetVersion VersionInfo
type ArchitectureSpec = Map Architecture PlatformSpec
type PlatformSpec = Map Platform PlatformVersionSpec
type PlatformVersionSpec = Map (Maybe VersionRange) DownloadInfo


-- | An installable tool.
data Tool = GHC
          | Cabal
          | GHCup
          | HLS
          | Stack
  deriving (Tool -> Tool -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tool -> Tool -> Bool
$c/= :: Tool -> Tool -> Bool
== :: Tool -> Tool -> Bool
$c== :: Tool -> Tool -> Bool
Eq, forall x. Rep Tool x -> Tool
forall x. Tool -> Rep Tool x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tool x -> Tool
$cfrom :: forall x. Tool -> Rep Tool x
GHC.Generic, Eq Tool
Tool -> Tool -> Bool
Tool -> Tool -> Ordering
Tool -> Tool -> Tool
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Tool -> Tool -> Tool
$cmin :: Tool -> Tool -> Tool
max :: Tool -> Tool -> Tool
$cmax :: Tool -> Tool -> Tool
>= :: Tool -> Tool -> Bool
$c>= :: Tool -> Tool -> Bool
> :: Tool -> Tool -> Bool
$c> :: Tool -> Tool -> Bool
<= :: Tool -> Tool -> Bool
$c<= :: Tool -> Tool -> Bool
< :: Tool -> Tool -> Bool
$c< :: Tool -> Tool -> Bool
compare :: Tool -> Tool -> Ordering
$ccompare :: Tool -> Tool -> Ordering
Ord, Int -> Tool -> ShowS
[Tool] -> ShowS
Tool -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Tool] -> ShowS
$cshowList :: [Tool] -> ShowS
show :: Tool -> FilePath
$cshow :: Tool -> FilePath
showsPrec :: Int -> Tool -> ShowS
$cshowsPrec :: Int -> Tool -> ShowS
Show, Int -> Tool
Tool -> Int
Tool -> [Tool]
Tool -> Tool
Tool -> Tool -> [Tool]
Tool -> Tool -> Tool -> [Tool]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Tool -> Tool -> Tool -> [Tool]
$cenumFromThenTo :: Tool -> Tool -> Tool -> [Tool]
enumFromTo :: Tool -> Tool -> [Tool]
$cenumFromTo :: Tool -> Tool -> [Tool]
enumFromThen :: Tool -> Tool -> [Tool]
$cenumFromThen :: Tool -> Tool -> [Tool]
enumFrom :: Tool -> [Tool]
$cenumFrom :: Tool -> [Tool]
fromEnum :: Tool -> Int
$cfromEnum :: Tool -> Int
toEnum :: Int -> Tool
$ctoEnum :: Int -> Tool
pred :: Tool -> Tool
$cpred :: Tool -> Tool
succ :: Tool -> Tool
$csucc :: Tool -> Tool
Enum, Tool
forall a. a -> a -> Bounded a
maxBound :: Tool
$cmaxBound :: Tool
minBound :: Tool
$cminBound :: Tool
Bounded)

instance Pretty Tool where
  pPrint :: Tool -> Doc
pPrint Tool
GHC = FilePath -> Doc
text FilePath
"ghc"
  pPrint Tool
Cabal = FilePath -> Doc
text FilePath
"cabal"
  pPrint Tool
GHCup = FilePath -> Doc
text FilePath
"ghcup"
  pPrint Tool
HLS = FilePath -> Doc
text FilePath
"hls"
  pPrint Tool
Stack = FilePath -> Doc
text FilePath
"stack"

instance NFData Tool

data GlobalTool = ShimGen
  deriving (GlobalTool -> GlobalTool -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GlobalTool -> GlobalTool -> Bool
$c/= :: GlobalTool -> GlobalTool -> Bool
== :: GlobalTool -> GlobalTool -> Bool
$c== :: GlobalTool -> GlobalTool -> Bool
Eq, forall x. Rep GlobalTool x -> GlobalTool
forall x. GlobalTool -> Rep GlobalTool x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GlobalTool x -> GlobalTool
$cfrom :: forall x. GlobalTool -> Rep GlobalTool x
GHC.Generic, Eq GlobalTool
GlobalTool -> GlobalTool -> Bool
GlobalTool -> GlobalTool -> Ordering
GlobalTool -> GlobalTool -> GlobalTool
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GlobalTool -> GlobalTool -> GlobalTool
$cmin :: GlobalTool -> GlobalTool -> GlobalTool
max :: GlobalTool -> GlobalTool -> GlobalTool
$cmax :: GlobalTool -> GlobalTool -> GlobalTool
>= :: GlobalTool -> GlobalTool -> Bool
$c>= :: GlobalTool -> GlobalTool -> Bool
> :: GlobalTool -> GlobalTool -> Bool
$c> :: GlobalTool -> GlobalTool -> Bool
<= :: GlobalTool -> GlobalTool -> Bool
$c<= :: GlobalTool -> GlobalTool -> Bool
< :: GlobalTool -> GlobalTool -> Bool
$c< :: GlobalTool -> GlobalTool -> Bool
compare :: GlobalTool -> GlobalTool -> Ordering
$ccompare :: GlobalTool -> GlobalTool -> Ordering
Ord, Int -> GlobalTool -> ShowS
[GlobalTool] -> ShowS
GlobalTool -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [GlobalTool] -> ShowS
$cshowList :: [GlobalTool] -> ShowS
show :: GlobalTool -> FilePath
$cshow :: GlobalTool -> FilePath
showsPrec :: Int -> GlobalTool -> ShowS
$cshowsPrec :: Int -> GlobalTool -> ShowS
Show, Int -> GlobalTool
GlobalTool -> Int
GlobalTool -> [GlobalTool]
GlobalTool -> GlobalTool
GlobalTool -> GlobalTool -> [GlobalTool]
GlobalTool -> GlobalTool -> GlobalTool -> [GlobalTool]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: GlobalTool -> GlobalTool -> GlobalTool -> [GlobalTool]
$cenumFromThenTo :: GlobalTool -> GlobalTool -> GlobalTool -> [GlobalTool]
enumFromTo :: GlobalTool -> GlobalTool -> [GlobalTool]
$cenumFromTo :: GlobalTool -> GlobalTool -> [GlobalTool]
enumFromThen :: GlobalTool -> GlobalTool -> [GlobalTool]
$cenumFromThen :: GlobalTool -> GlobalTool -> [GlobalTool]
enumFrom :: GlobalTool -> [GlobalTool]
$cenumFrom :: GlobalTool -> [GlobalTool]
fromEnum :: GlobalTool -> Int
$cfromEnum :: GlobalTool -> Int
toEnum :: Int -> GlobalTool
$ctoEnum :: Int -> GlobalTool
pred :: GlobalTool -> GlobalTool
$cpred :: GlobalTool -> GlobalTool
succ :: GlobalTool -> GlobalTool
$csucc :: GlobalTool -> GlobalTool
Enum, GlobalTool
forall a. a -> a -> Bounded a
maxBound :: GlobalTool
$cmaxBound :: GlobalTool
minBound :: GlobalTool
$cminBound :: GlobalTool
Bounded)

instance NFData GlobalTool


-- | All necessary information of a tool version, including
-- source download and per-architecture downloads.
data VersionInfo = VersionInfo
  { VersionInfo -> [Tag]
_viTags        :: [Tag]              -- ^ version specific tag
  , VersionInfo -> Maybe Day
_viReleaseDay  :: Maybe Day
  , VersionInfo -> Maybe URI
_viChangeLog   :: Maybe URI
  , VersionInfo -> Maybe DownloadInfo
_viSourceDL    :: Maybe DownloadInfo -- ^ source tarball
  , VersionInfo -> Maybe DownloadInfo
_viTestDL      :: Maybe DownloadInfo -- ^ test tarball
  , VersionInfo -> ArchitectureSpec
_viArch        :: ArchitectureSpec   -- ^ descend for binary downloads per arch
  -- informative messages
  , VersionInfo -> Maybe Text
_viPostInstall :: Maybe Text
  , VersionInfo -> Maybe Text
_viPostRemove  :: Maybe Text
  , VersionInfo -> Maybe Text
_viPreCompile  :: Maybe Text
  }
  deriving (VersionInfo -> VersionInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionInfo -> VersionInfo -> Bool
$c/= :: VersionInfo -> VersionInfo -> Bool
== :: VersionInfo -> VersionInfo -> Bool
$c== :: VersionInfo -> VersionInfo -> Bool
Eq, forall x. Rep VersionInfo x -> VersionInfo
forall x. VersionInfo -> Rep VersionInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VersionInfo x -> VersionInfo
$cfrom :: forall x. VersionInfo -> Rep VersionInfo x
GHC.Generic, Int -> VersionInfo -> ShowS
[VersionInfo] -> ShowS
VersionInfo -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [VersionInfo] -> ShowS
$cshowList :: [VersionInfo] -> ShowS
show :: VersionInfo -> FilePath
$cshow :: VersionInfo -> FilePath
showsPrec :: Int -> VersionInfo -> ShowS
$cshowsPrec :: Int -> VersionInfo -> ShowS
Show)

instance NFData VersionInfo


-- | A tag. These are currently attached to a version of a tool.
data Tag = Latest
         | Recommended
         | Prerelease
         | LatestPrerelease
         | Nightly
         | LatestNightly
         | Base PVP
         | Old                -- ^ old versions are hidden by default in TUI
         | UnknownTag String  -- ^ used for upwardscompat
         deriving (Eq Tag
Tag -> Tag -> Bool
Tag -> Tag -> Ordering
Tag -> Tag -> Tag
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Tag -> Tag -> Tag
$cmin :: Tag -> Tag -> Tag
max :: Tag -> Tag -> Tag
$cmax :: Tag -> Tag -> Tag
>= :: Tag -> Tag -> Bool
$c>= :: Tag -> Tag -> Bool
> :: Tag -> Tag -> Bool
$c> :: Tag -> Tag -> Bool
<= :: Tag -> Tag -> Bool
$c<= :: Tag -> Tag -> Bool
< :: Tag -> Tag -> Bool
$c< :: Tag -> Tag -> Bool
compare :: Tag -> Tag -> Ordering
$ccompare :: Tag -> Tag -> Ordering
Ord, Tag -> Tag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tag -> Tag -> Bool
$c/= :: Tag -> Tag -> Bool
== :: Tag -> Tag -> Bool
$c== :: Tag -> Tag -> Bool
Eq, forall x. Rep Tag x -> Tag
forall x. Tag -> Rep Tag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tag x -> Tag
$cfrom :: forall x. Tag -> Rep Tag x
GHC.Generic, Int -> Tag -> ShowS
[Tag] -> ShowS
Tag -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Tag] -> ShowS
$cshowList :: [Tag] -> ShowS
show :: Tag -> FilePath
$cshow :: Tag -> FilePath
showsPrec :: Int -> Tag -> ShowS
$cshowsPrec :: Int -> Tag -> ShowS
Show) -- FIXME: manual JSON instance

instance NFData Tag

tagToString :: Tag -> String
tagToString :: Tag -> FilePath
tagToString Tag
Recommended        = FilePath
"recommended"
tagToString Tag
Latest             = FilePath
"latest"
tagToString Tag
Prerelease         = FilePath
"prerelease"
tagToString Tag
Nightly            = FilePath
"nightly"
tagToString (Base       PVP
pvp'') = FilePath
"base-" forall a. [a] -> [a] -> [a]
++ Text -> FilePath
T.unpack (PVP -> Text
prettyPVP PVP
pvp'')
tagToString (UnknownTag FilePath
t    ) = FilePath
t
tagToString Tag
LatestPrerelease   = FilePath
"latest-prerelease"
tagToString Tag
LatestNightly      = FilePath
"latest-nightly"
tagToString Tag
Old                = FilePath
""

instance Pretty Tag where
  pPrint :: Tag -> Doc
pPrint Tag
Recommended        = FilePath -> Doc
text FilePath
"recommended"
  pPrint Tag
Latest             = FilePath -> Doc
text FilePath
"latest"
  pPrint Tag
Prerelease         = FilePath -> Doc
text FilePath
"prerelease"
  pPrint Tag
Nightly            = FilePath -> Doc
text FilePath
"nightly"
  pPrint (Base       PVP
pvp'') = FilePath -> Doc
text (FilePath
"base-" forall a. [a] -> [a] -> [a]
++ Text -> FilePath
T.unpack (PVP -> Text
prettyPVP PVP
pvp''))
  pPrint (UnknownTag FilePath
t    ) = FilePath -> Doc
text FilePath
t
  pPrint Tag
LatestPrerelease   = FilePath -> Doc
text FilePath
"latest-prerelease"
  pPrint Tag
LatestNightly   = FilePath -> Doc
text FilePath
"latest-prerelease"
  pPrint Tag
Old                = forall a. Monoid a => a
mempty

data Architecture = A_64
                  | A_32
                  | A_PowerPC
                  | A_PowerPC64
                  | A_Sparc
                  | A_Sparc64
                  | A_ARM
                  | A_ARM64
  deriving (Architecture -> Architecture -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Architecture -> Architecture -> Bool
$c/= :: Architecture -> Architecture -> Bool
== :: Architecture -> Architecture -> Bool
$c== :: Architecture -> Architecture -> Bool
Eq, forall x. Rep Architecture x -> Architecture
forall x. Architecture -> Rep Architecture x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Architecture x -> Architecture
$cfrom :: forall x. Architecture -> Rep Architecture x
GHC.Generic, Eq Architecture
Architecture -> Architecture -> Bool
Architecture -> Architecture -> Ordering
Architecture -> Architecture -> Architecture
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Architecture -> Architecture -> Architecture
$cmin :: Architecture -> Architecture -> Architecture
max :: Architecture -> Architecture -> Architecture
$cmax :: Architecture -> Architecture -> Architecture
>= :: Architecture -> Architecture -> Bool
$c>= :: Architecture -> Architecture -> Bool
> :: Architecture -> Architecture -> Bool
$c> :: Architecture -> Architecture -> Bool
<= :: Architecture -> Architecture -> Bool
$c<= :: Architecture -> Architecture -> Bool
< :: Architecture -> Architecture -> Bool
$c< :: Architecture -> Architecture -> Bool
compare :: Architecture -> Architecture -> Ordering
$ccompare :: Architecture -> Architecture -> Ordering
Ord, Int -> Architecture -> ShowS
[Architecture] -> ShowS
Architecture -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Architecture] -> ShowS
$cshowList :: [Architecture] -> ShowS
show :: Architecture -> FilePath
$cshow :: Architecture -> FilePath
showsPrec :: Int -> Architecture -> ShowS
$cshowsPrec :: Int -> Architecture -> ShowS
Show)

instance NFData Architecture

archToString :: Architecture -> String
archToString :: Architecture -> FilePath
archToString Architecture
A_64 = FilePath
"x86_64"
archToString Architecture
A_32 = FilePath
"i386"
archToString Architecture
A_PowerPC = FilePath
"powerpc"
archToString Architecture
A_PowerPC64 = FilePath
"powerpc64"
archToString Architecture
A_Sparc = FilePath
"sparc"
archToString Architecture
A_Sparc64 = FilePath
"sparc64"
archToString Architecture
A_ARM = FilePath
"arm"
archToString Architecture
A_ARM64 = FilePath
"aarch64"

instance Pretty Architecture where
  pPrint :: Architecture -> Doc
pPrint = FilePath -> Doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. Architecture -> FilePath
archToString

data Platform = Linux LinuxDistro
              -- ^ must exit
              | Darwin
              -- ^ must exit
              | FreeBSD
              | Windows
              -- ^ must exit
  deriving (Platform -> Platform -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Platform -> Platform -> Bool
$c/= :: Platform -> Platform -> Bool
== :: Platform -> Platform -> Bool
$c== :: Platform -> Platform -> Bool
Eq, forall x. Rep Platform x -> Platform
forall x. Platform -> Rep Platform x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Platform x -> Platform
$cfrom :: forall x. Platform -> Rep Platform x
GHC.Generic, Eq Platform
Platform -> Platform -> Bool
Platform -> Platform -> Ordering
Platform -> Platform -> Platform
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Platform -> Platform -> Platform
$cmin :: Platform -> Platform -> Platform
max :: Platform -> Platform -> Platform
$cmax :: Platform -> Platform -> Platform
>= :: Platform -> Platform -> Bool
$c>= :: Platform -> Platform -> Bool
> :: Platform -> Platform -> Bool
$c> :: Platform -> Platform -> Bool
<= :: Platform -> Platform -> Bool
$c<= :: Platform -> Platform -> Bool
< :: Platform -> Platform -> Bool
$c< :: Platform -> Platform -> Bool
compare :: Platform -> Platform -> Ordering
$ccompare :: Platform -> Platform -> Ordering
Ord, Int -> Platform -> ShowS
[Platform] -> ShowS
Platform -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Platform] -> ShowS
$cshowList :: [Platform] -> ShowS
show :: Platform -> FilePath
$cshow :: Platform -> FilePath
showsPrec :: Int -> Platform -> ShowS
$cshowsPrec :: Int -> Platform -> ShowS
Show)

instance NFData Platform

platformToString :: Platform -> String
platformToString :: Platform -> FilePath
platformToString (Linux LinuxDistro
distro) = FilePath
"linux-" forall a. [a] -> [a] -> [a]
++ LinuxDistro -> FilePath
distroToString LinuxDistro
distro
platformToString Platform
Darwin = FilePath
"darwin"
platformToString Platform
FreeBSD = FilePath
"freebsd"
platformToString Platform
Windows = FilePath
"windows"

instance Pretty Platform where
  pPrint :: Platform -> Doc
pPrint = FilePath -> Doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. Platform -> FilePath
platformToString

data LinuxDistro = Debian
                 | Ubuntu
                 | Mint
                 | Fedora
                 | CentOS
                 | RedHat
                 | Alpine
                 | AmazonLinux
                 -- rolling
                 | Gentoo
                 | Exherbo
                 -- not known
                 | UnknownLinux
                 -- ^ must exit
  deriving (LinuxDistro -> LinuxDistro -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LinuxDistro -> LinuxDistro -> Bool
$c/= :: LinuxDistro -> LinuxDistro -> Bool
== :: LinuxDistro -> LinuxDistro -> Bool
$c== :: LinuxDistro -> LinuxDistro -> Bool
Eq, forall x. Rep LinuxDistro x -> LinuxDistro
forall x. LinuxDistro -> Rep LinuxDistro x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LinuxDistro x -> LinuxDistro
$cfrom :: forall x. LinuxDistro -> Rep LinuxDistro x
GHC.Generic, Eq LinuxDistro
LinuxDistro -> LinuxDistro -> Bool
LinuxDistro -> LinuxDistro -> Ordering
LinuxDistro -> LinuxDistro -> LinuxDistro
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LinuxDistro -> LinuxDistro -> LinuxDistro
$cmin :: LinuxDistro -> LinuxDistro -> LinuxDistro
max :: LinuxDistro -> LinuxDistro -> LinuxDistro
$cmax :: LinuxDistro -> LinuxDistro -> LinuxDistro
>= :: LinuxDistro -> LinuxDistro -> Bool
$c>= :: LinuxDistro -> LinuxDistro -> Bool
> :: LinuxDistro -> LinuxDistro -> Bool
$c> :: LinuxDistro -> LinuxDistro -> Bool
<= :: LinuxDistro -> LinuxDistro -> Bool
$c<= :: LinuxDistro -> LinuxDistro -> Bool
< :: LinuxDistro -> LinuxDistro -> Bool
$c< :: LinuxDistro -> LinuxDistro -> Bool
compare :: LinuxDistro -> LinuxDistro -> Ordering
$ccompare :: LinuxDistro -> LinuxDistro -> Ordering
Ord, Int -> LinuxDistro -> ShowS
[LinuxDistro] -> ShowS
LinuxDistro -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [LinuxDistro] -> ShowS
$cshowList :: [LinuxDistro] -> ShowS
show :: LinuxDistro -> FilePath
$cshow :: LinuxDistro -> FilePath
showsPrec :: Int -> LinuxDistro -> ShowS
$cshowsPrec :: Int -> LinuxDistro -> ShowS
Show)

instance NFData LinuxDistro

distroToString :: LinuxDistro -> String
distroToString :: LinuxDistro -> FilePath
distroToString LinuxDistro
Debian = FilePath
"debian"
distroToString LinuxDistro
Ubuntu = FilePath
"ubuntu"
distroToString LinuxDistro
Mint = FilePath
"mint"
distroToString LinuxDistro
Fedora = FilePath
"fedora"
distroToString LinuxDistro
CentOS = FilePath
"centos"
distroToString LinuxDistro
RedHat = FilePath
"redhat"
distroToString LinuxDistro
Alpine = FilePath
"alpine"
distroToString LinuxDistro
AmazonLinux = FilePath
"amazon"
distroToString LinuxDistro
Gentoo = FilePath
"gentoo"
distroToString LinuxDistro
Exherbo = FilePath
"exherbo"
distroToString LinuxDistro
UnknownLinux = FilePath
"unknown"

instance Pretty LinuxDistro where
  pPrint :: LinuxDistro -> Doc
pPrint = FilePath -> Doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. LinuxDistro -> FilePath
distroToString


-- | An encapsulation of a download. This can be used
-- to download, extract and install a tool.
data DownloadInfo = DownloadInfo
  { DownloadInfo -> URI
_dlUri    :: URI
  , DownloadInfo -> Maybe TarDir
_dlSubdir :: Maybe TarDir
  , DownloadInfo -> Text
_dlHash   :: Text
  , DownloadInfo -> Maybe Integer
_dlCSize  :: Maybe Integer
  , DownloadInfo -> Maybe FilePath
_dlOutput :: Maybe FilePath
  }
  deriving (DownloadInfo -> DownloadInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DownloadInfo -> DownloadInfo -> Bool
$c/= :: DownloadInfo -> DownloadInfo -> Bool
== :: DownloadInfo -> DownloadInfo -> Bool
$c== :: DownloadInfo -> DownloadInfo -> Bool
Eq, Eq DownloadInfo
DownloadInfo -> DownloadInfo -> Bool
DownloadInfo -> DownloadInfo -> Ordering
DownloadInfo -> DownloadInfo -> DownloadInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DownloadInfo -> DownloadInfo -> DownloadInfo
$cmin :: DownloadInfo -> DownloadInfo -> DownloadInfo
max :: DownloadInfo -> DownloadInfo -> DownloadInfo
$cmax :: DownloadInfo -> DownloadInfo -> DownloadInfo
>= :: DownloadInfo -> DownloadInfo -> Bool
$c>= :: DownloadInfo -> DownloadInfo -> Bool
> :: DownloadInfo -> DownloadInfo -> Bool
$c> :: DownloadInfo -> DownloadInfo -> Bool
<= :: DownloadInfo -> DownloadInfo -> Bool
$c<= :: DownloadInfo -> DownloadInfo -> Bool
< :: DownloadInfo -> DownloadInfo -> Bool
$c< :: DownloadInfo -> DownloadInfo -> Bool
compare :: DownloadInfo -> DownloadInfo -> Ordering
$ccompare :: DownloadInfo -> DownloadInfo -> Ordering
Ord, forall x. Rep DownloadInfo x -> DownloadInfo
forall x. DownloadInfo -> Rep DownloadInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DownloadInfo x -> DownloadInfo
$cfrom :: forall x. DownloadInfo -> Rep DownloadInfo x
GHC.Generic, Int -> DownloadInfo -> ShowS
[DownloadInfo] -> ShowS
DownloadInfo -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [DownloadInfo] -> ShowS
$cshowList :: [DownloadInfo] -> ShowS
show :: DownloadInfo -> FilePath
$cshow :: DownloadInfo -> FilePath
showsPrec :: Int -> DownloadInfo -> ShowS
$cshowsPrec :: Int -> DownloadInfo -> ShowS
Show)

instance NFData DownloadInfo



    --------------
    --[ Others ]--
    --------------

data DownloadMirror = DownloadMirror {
     DownloadMirror -> Authority
authority :: Authority
   , DownloadMirror -> Maybe Text
pathPrefix :: Maybe Text
} deriving (DownloadMirror -> DownloadMirror -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DownloadMirror -> DownloadMirror -> Bool
$c/= :: DownloadMirror -> DownloadMirror -> Bool
== :: DownloadMirror -> DownloadMirror -> Bool
$c== :: DownloadMirror -> DownloadMirror -> Bool
Eq, Eq DownloadMirror
DownloadMirror -> DownloadMirror -> Bool
DownloadMirror -> DownloadMirror -> Ordering
DownloadMirror -> DownloadMirror -> DownloadMirror
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DownloadMirror -> DownloadMirror -> DownloadMirror
$cmin :: DownloadMirror -> DownloadMirror -> DownloadMirror
max :: DownloadMirror -> DownloadMirror -> DownloadMirror
$cmax :: DownloadMirror -> DownloadMirror -> DownloadMirror
>= :: DownloadMirror -> DownloadMirror -> Bool
$c>= :: DownloadMirror -> DownloadMirror -> Bool
> :: DownloadMirror -> DownloadMirror -> Bool
$c> :: DownloadMirror -> DownloadMirror -> Bool
<= :: DownloadMirror -> DownloadMirror -> Bool
$c<= :: DownloadMirror -> DownloadMirror -> Bool
< :: DownloadMirror -> DownloadMirror -> Bool
$c< :: DownloadMirror -> DownloadMirror -> Bool
compare :: DownloadMirror -> DownloadMirror -> Ordering
$ccompare :: DownloadMirror -> DownloadMirror -> Ordering
Ord, forall x. Rep DownloadMirror x -> DownloadMirror
forall x. DownloadMirror -> Rep DownloadMirror x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DownloadMirror x -> DownloadMirror
$cfrom :: forall x. DownloadMirror -> Rep DownloadMirror x
GHC.Generic, Int -> DownloadMirror -> ShowS
[DownloadMirror] -> ShowS
DownloadMirror -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [DownloadMirror] -> ShowS
$cshowList :: [DownloadMirror] -> ShowS
show :: DownloadMirror -> FilePath
$cshow :: DownloadMirror -> FilePath
showsPrec :: Int -> DownloadMirror -> ShowS
$cshowsPrec :: Int -> DownloadMirror -> ShowS
Show)

instance NFData DownloadMirror

newtype DownloadMirrors = DM (Map Text DownloadMirror)
  deriving (DownloadMirrors -> DownloadMirrors -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DownloadMirrors -> DownloadMirrors -> Bool
$c/= :: DownloadMirrors -> DownloadMirrors -> Bool
== :: DownloadMirrors -> DownloadMirrors -> Bool
$c== :: DownloadMirrors -> DownloadMirrors -> Bool
Eq, Eq DownloadMirrors
DownloadMirrors -> DownloadMirrors -> Bool
DownloadMirrors -> DownloadMirrors -> Ordering
DownloadMirrors -> DownloadMirrors -> DownloadMirrors
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DownloadMirrors -> DownloadMirrors -> DownloadMirrors
$cmin :: DownloadMirrors -> DownloadMirrors -> DownloadMirrors
max :: DownloadMirrors -> DownloadMirrors -> DownloadMirrors
$cmax :: DownloadMirrors -> DownloadMirrors -> DownloadMirrors
>= :: DownloadMirrors -> DownloadMirrors -> Bool
$c>= :: DownloadMirrors -> DownloadMirrors -> Bool
> :: DownloadMirrors -> DownloadMirrors -> Bool
$c> :: DownloadMirrors -> DownloadMirrors -> Bool
<= :: DownloadMirrors -> DownloadMirrors -> Bool
$c<= :: DownloadMirrors -> DownloadMirrors -> Bool
< :: DownloadMirrors -> DownloadMirrors -> Bool
$c< :: DownloadMirrors -> DownloadMirrors -> Bool
compare :: DownloadMirrors -> DownloadMirrors -> Ordering
$ccompare :: DownloadMirrors -> DownloadMirrors -> Ordering
Ord, forall x. Rep DownloadMirrors x -> DownloadMirrors
forall x. DownloadMirrors -> Rep DownloadMirrors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DownloadMirrors x -> DownloadMirrors
$cfrom :: forall x. DownloadMirrors -> Rep DownloadMirrors x
GHC.Generic, Int -> DownloadMirrors -> ShowS
[DownloadMirrors] -> ShowS
DownloadMirrors -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [DownloadMirrors] -> ShowS
$cshowList :: [DownloadMirrors] -> ShowS
show :: DownloadMirrors -> FilePath
$cshow :: DownloadMirrors -> FilePath
showsPrec :: Int -> DownloadMirrors -> ShowS
$cshowsPrec :: Int -> DownloadMirrors -> ShowS
Show)

instance NFData DownloadMirrors

instance NFData UserInfo
instance NFData Host
instance NFData Port
instance NFData Authority


-- | How to descend into a tar archive.
data TarDir = RealDir FilePath
            | RegexDir String     -- ^ will be compiled to regex, the first match will "win"
            deriving (TarDir -> TarDir -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TarDir -> TarDir -> Bool
$c/= :: TarDir -> TarDir -> Bool
== :: TarDir -> TarDir -> Bool
$c== :: TarDir -> TarDir -> Bool
Eq, Eq TarDir
TarDir -> TarDir -> Bool
TarDir -> TarDir -> Ordering
TarDir -> TarDir -> TarDir
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TarDir -> TarDir -> TarDir
$cmin :: TarDir -> TarDir -> TarDir
max :: TarDir -> TarDir -> TarDir
$cmax :: TarDir -> TarDir -> TarDir
>= :: TarDir -> TarDir -> Bool
$c>= :: TarDir -> TarDir -> Bool
> :: TarDir -> TarDir -> Bool
$c> :: TarDir -> TarDir -> Bool
<= :: TarDir -> TarDir -> Bool
$c<= :: TarDir -> TarDir -> Bool
< :: TarDir -> TarDir -> Bool
$c< :: TarDir -> TarDir -> Bool
compare :: TarDir -> TarDir -> Ordering
$ccompare :: TarDir -> TarDir -> Ordering
Ord, forall x. Rep TarDir x -> TarDir
forall x. TarDir -> Rep TarDir x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TarDir x -> TarDir
$cfrom :: forall x. TarDir -> Rep TarDir x
GHC.Generic, Int -> TarDir -> ShowS
[TarDir] -> ShowS
TarDir -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [TarDir] -> ShowS
$cshowList :: [TarDir] -> ShowS
show :: TarDir -> FilePath
$cshow :: TarDir -> FilePath
showsPrec :: Int -> TarDir -> ShowS
$cshowsPrec :: Int -> TarDir -> ShowS
Show)

instance NFData TarDir

instance Pretty TarDir where
  pPrint :: TarDir -> Doc
pPrint (RealDir FilePath
path) = FilePath -> Doc
text FilePath
path
  pPrint (RegexDir FilePath
regex) = FilePath -> Doc
text FilePath
regex


-- | Where to fetch GHCupDownloads from.
data URLSource = GHCupURL
               | OwnSource [Either GHCupInfo URI] -- ^ complete source list
               | OwnSpec GHCupInfo
               | AddSource [Either GHCupInfo URI] -- ^ merge with GHCupURL
               deriving (forall x. Rep URLSource x -> URLSource
forall x. URLSource -> Rep URLSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep URLSource x -> URLSource
$cfrom :: forall x. URLSource -> Rep URLSource x
GHC.Generic, Int -> URLSource -> ShowS
[URLSource] -> ShowS
URLSource -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [URLSource] -> ShowS
$cshowList :: [URLSource] -> ShowS
show :: URLSource -> FilePath
$cshow :: URLSource -> FilePath
showsPrec :: Int -> URLSource -> ShowS
$cshowsPrec :: Int -> URLSource -> ShowS
Show)

instance NFData URLSource
instance NFData (URIRef Absolute) where
  rnf :: URI -> ()
rnf (URI !Scheme
_ !Maybe Authority
_ !ByteString
_ !Query
_ !Maybe ByteString
_) = ()

data MetaMode = Strict
              | Lax
  deriving (Int -> MetaMode -> ShowS
[MetaMode] -> ShowS
MetaMode -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [MetaMode] -> ShowS
$cshowList :: [MetaMode] -> ShowS
show :: MetaMode -> FilePath
$cshow :: MetaMode -> FilePath
showsPrec :: Int -> MetaMode -> ShowS
$cshowsPrec :: Int -> MetaMode -> ShowS
Show, ReadPrec [MetaMode]
ReadPrec MetaMode
Int -> ReadS MetaMode
ReadS [MetaMode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MetaMode]
$creadListPrec :: ReadPrec [MetaMode]
readPrec :: ReadPrec MetaMode
$creadPrec :: ReadPrec MetaMode
readList :: ReadS [MetaMode]
$creadList :: ReadS [MetaMode]
readsPrec :: Int -> ReadS MetaMode
$creadsPrec :: Int -> ReadS MetaMode
Read, MetaMode -> MetaMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MetaMode -> MetaMode -> Bool
$c/= :: MetaMode -> MetaMode -> Bool
== :: MetaMode -> MetaMode -> Bool
$c== :: MetaMode -> MetaMode -> Bool
Eq, forall x. Rep MetaMode x -> MetaMode
forall x. MetaMode -> Rep MetaMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MetaMode x -> MetaMode
$cfrom :: forall x. MetaMode -> Rep MetaMode x
GHC.Generic)

instance NFData MetaMode

data UserSettings = UserSettings
  { UserSettings -> Maybe Bool
uCache       :: Maybe Bool
  , UserSettings -> Maybe Integer
uMetaCache   :: Maybe Integer
  , UserSettings -> Maybe MetaMode
uMetaMode    :: Maybe MetaMode
  , UserSettings -> Maybe Bool
uNoVerify    :: Maybe Bool
  , UserSettings -> Maybe Bool
uVerbose     :: Maybe Bool
  , UserSettings -> Maybe KeepDirs
uKeepDirs    :: Maybe KeepDirs
  , UserSettings -> Maybe Downloader
uDownloader  :: Maybe Downloader
  , UserSettings -> Maybe UserKeyBindings
uKeyBindings :: Maybe UserKeyBindings
  , UserSettings -> Maybe URLSource
uUrlSource   :: Maybe URLSource
  , UserSettings -> Maybe Bool
uNoNetwork   :: Maybe Bool
  , UserSettings -> Maybe GPGSetting
uGPGSetting  :: Maybe GPGSetting
  , UserSettings -> Maybe PlatformRequest
uPlatformOverride :: Maybe PlatformRequest
  , UserSettings -> Maybe DownloadMirrors
uMirrors     :: Maybe DownloadMirrors
  }
  deriving (Int -> UserSettings -> ShowS
[UserSettings] -> ShowS
UserSettings -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [UserSettings] -> ShowS
$cshowList :: [UserSettings] -> ShowS
show :: UserSettings -> FilePath
$cshow :: UserSettings -> FilePath
showsPrec :: Int -> UserSettings -> ShowS
$cshowsPrec :: Int -> UserSettings -> ShowS
Show, forall x. Rep UserSettings x -> UserSettings
forall x. UserSettings -> Rep UserSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserSettings x -> UserSettings
$cfrom :: forall x. UserSettings -> Rep UserSettings x
GHC.Generic)

defaultUserSettings :: UserSettings
defaultUserSettings :: UserSettings
defaultUserSettings = Maybe Bool
-> Maybe Integer
-> Maybe MetaMode
-> Maybe Bool
-> Maybe Bool
-> Maybe KeepDirs
-> Maybe Downloader
-> Maybe UserKeyBindings
-> Maybe URLSource
-> Maybe Bool
-> Maybe GPGSetting
-> Maybe PlatformRequest
-> Maybe DownloadMirrors
-> UserSettings
UserSettings forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing

fromSettings :: Settings -> Maybe KeyBindings -> UserSettings
fromSettings :: Settings -> Maybe KeyBindings -> UserSettings
fromSettings Settings{Bool
Integer
Maybe PlatformRequest
GPGSetting
Downloader
KeepDirs
MetaMode
URLSource
DownloadMirrors
$sel:mirrors:Settings :: Settings -> DownloadMirrors
$sel:platformOverride:Settings :: Settings -> Maybe PlatformRequest
$sel:noColor:Settings :: Settings -> Bool
$sel:gpgSetting:Settings :: Settings -> GPGSetting
$sel:noNetwork:Settings :: Settings -> Bool
$sel:urlSource:Settings :: Settings -> URLSource
$sel:verbose:Settings :: Settings -> Bool
$sel:downloader:Settings :: Settings -> Downloader
$sel:keepDirs:Settings :: Settings -> KeepDirs
$sel:noVerify:Settings :: Settings -> Bool
$sel:metaMode:Settings :: Settings -> MetaMode
$sel:metaCache:Settings :: Settings -> Integer
$sel:cache:Settings :: Settings -> Bool
mirrors :: DownloadMirrors
platformOverride :: Maybe PlatformRequest
noColor :: Bool
gpgSetting :: GPGSetting
noNetwork :: Bool
urlSource :: URLSource
verbose :: Bool
downloader :: Downloader
keepDirs :: KeepDirs
noVerify :: Bool
metaMode :: MetaMode
metaCache :: Integer
cache :: Bool
..} Maybe KeyBindings
Nothing =
  UserSettings {
      $sel:uCache:UserSettings :: Maybe Bool
uCache = forall a. a -> Maybe a
Just Bool
cache
    , $sel:uMetaCache:UserSettings :: Maybe Integer
uMetaCache = forall a. a -> Maybe a
Just Integer
metaCache
    , $sel:uMetaMode:UserSettings :: Maybe MetaMode
uMetaMode = forall a. a -> Maybe a
Just MetaMode
metaMode
    , $sel:uNoVerify:UserSettings :: Maybe Bool
uNoVerify = forall a. a -> Maybe a
Just Bool
noVerify
    , $sel:uVerbose:UserSettings :: Maybe Bool
uVerbose = forall a. a -> Maybe a
Just Bool
verbose
    , $sel:uKeepDirs:UserSettings :: Maybe KeepDirs
uKeepDirs = forall a. a -> Maybe a
Just KeepDirs
keepDirs
    , $sel:uDownloader:UserSettings :: Maybe Downloader
uDownloader = forall a. a -> Maybe a
Just Downloader
downloader
    , $sel:uNoNetwork:UserSettings :: Maybe Bool
uNoNetwork = forall a. a -> Maybe a
Just Bool
noNetwork
    , $sel:uKeyBindings:UserSettings :: Maybe UserKeyBindings
uKeyBindings = forall a. Maybe a
Nothing
    , $sel:uUrlSource:UserSettings :: Maybe URLSource
uUrlSource = forall a. a -> Maybe a
Just URLSource
urlSource
    , $sel:uGPGSetting:UserSettings :: Maybe GPGSetting
uGPGSetting = forall a. a -> Maybe a
Just GPGSetting
gpgSetting
    , $sel:uPlatformOverride:UserSettings :: Maybe PlatformRequest
uPlatformOverride = Maybe PlatformRequest
platformOverride
    , $sel:uMirrors:UserSettings :: Maybe DownloadMirrors
uMirrors = forall a. a -> Maybe a
Just DownloadMirrors
mirrors
  }
fromSettings Settings{Bool
Integer
Maybe PlatformRequest
GPGSetting
Downloader
KeepDirs
MetaMode
URLSource
DownloadMirrors
mirrors :: DownloadMirrors
platformOverride :: Maybe PlatformRequest
noColor :: Bool
gpgSetting :: GPGSetting
noNetwork :: Bool
urlSource :: URLSource
verbose :: Bool
downloader :: Downloader
keepDirs :: KeepDirs
noVerify :: Bool
metaMode :: MetaMode
metaCache :: Integer
cache :: Bool
$sel:mirrors:Settings :: Settings -> DownloadMirrors
$sel:platformOverride:Settings :: Settings -> Maybe PlatformRequest
$sel:noColor:Settings :: Settings -> Bool
$sel:gpgSetting:Settings :: Settings -> GPGSetting
$sel:noNetwork:Settings :: Settings -> Bool
$sel:urlSource:Settings :: Settings -> URLSource
$sel:verbose:Settings :: Settings -> Bool
$sel:downloader:Settings :: Settings -> Downloader
$sel:keepDirs:Settings :: Settings -> KeepDirs
$sel:noVerify:Settings :: Settings -> Bool
$sel:metaMode:Settings :: Settings -> MetaMode
$sel:metaCache:Settings :: Settings -> Integer
$sel:cache:Settings :: Settings -> Bool
..} (Just KeyBindings{Key
$sel:bShowAllTools:KeyBindings :: KeyBindings -> Key
$sel:bShowAllVersions:KeyBindings :: KeyBindings -> Key
$sel:bChangelog:KeyBindings :: KeyBindings -> Key
$sel:bSet:KeyBindings :: KeyBindings -> Key
$sel:bUninstall:KeyBindings :: KeyBindings -> Key
$sel:bInstall:KeyBindings :: KeyBindings -> Key
$sel:bQuit:KeyBindings :: KeyBindings -> Key
$sel:bDown:KeyBindings :: KeyBindings -> Key
$sel:bUp:KeyBindings :: KeyBindings -> Key
bShowAllTools :: Key
bShowAllVersions :: Key
bChangelog :: Key
bSet :: Key
bUninstall :: Key
bInstall :: Key
bQuit :: Key
bDown :: Key
bUp :: Key
..}) =
  let ukb :: UserKeyBindings
ukb = UserKeyBindings
            { $sel:kUp:UserKeyBindings :: Maybe Key
kUp           = forall a. a -> Maybe a
Just Key
bUp
            , $sel:kDown:UserKeyBindings :: Maybe Key
kDown         = forall a. a -> Maybe a
Just Key
bDown
            , $sel:kQuit:UserKeyBindings :: Maybe Key
kQuit         = forall a. a -> Maybe a
Just Key
bQuit
            , $sel:kInstall:UserKeyBindings :: Maybe Key
kInstall      = forall a. a -> Maybe a
Just Key
bInstall
            , $sel:kUninstall:UserKeyBindings :: Maybe Key
kUninstall    = forall a. a -> Maybe a
Just Key
bUninstall
            , $sel:kSet:UserKeyBindings :: Maybe Key
kSet          = forall a. a -> Maybe a
Just Key
bSet
            , $sel:kChangelog:UserKeyBindings :: Maybe Key
kChangelog    = forall a. a -> Maybe a
Just Key
bChangelog
            , $sel:kShowAll:UserKeyBindings :: Maybe Key
kShowAll      = forall a. a -> Maybe a
Just Key
bShowAllVersions
            , $sel:kShowAllTools:UserKeyBindings :: Maybe Key
kShowAllTools = forall a. a -> Maybe a
Just Key
bShowAllTools
            }
  in UserSettings {
      $sel:uCache:UserSettings :: Maybe Bool
uCache = forall a. a -> Maybe a
Just Bool
cache
    , $sel:uMetaCache:UserSettings :: Maybe Integer
uMetaCache = forall a. a -> Maybe a
Just Integer
metaCache
    , $sel:uMetaMode:UserSettings :: Maybe MetaMode
uMetaMode = forall a. a -> Maybe a
Just MetaMode
metaMode
    , $sel:uNoVerify:UserSettings :: Maybe Bool
uNoVerify = forall a. a -> Maybe a
Just Bool
noVerify
    , $sel:uVerbose:UserSettings :: Maybe Bool
uVerbose = forall a. a -> Maybe a
Just Bool
verbose
    , $sel:uKeepDirs:UserSettings :: Maybe KeepDirs
uKeepDirs = forall a. a -> Maybe a
Just KeepDirs
keepDirs
    , $sel:uDownloader:UserSettings :: Maybe Downloader
uDownloader = forall a. a -> Maybe a
Just Downloader
downloader
    , $sel:uNoNetwork:UserSettings :: Maybe Bool
uNoNetwork = forall a. a -> Maybe a
Just Bool
noNetwork
    , $sel:uKeyBindings:UserSettings :: Maybe UserKeyBindings
uKeyBindings = forall a. a -> Maybe a
Just UserKeyBindings
ukb
    , $sel:uUrlSource:UserSettings :: Maybe URLSource
uUrlSource = forall a. a -> Maybe a
Just URLSource
urlSource
    , $sel:uGPGSetting:UserSettings :: Maybe GPGSetting
uGPGSetting = forall a. a -> Maybe a
Just GPGSetting
gpgSetting
    , $sel:uPlatformOverride:UserSettings :: Maybe PlatformRequest
uPlatformOverride = Maybe PlatformRequest
platformOverride
    , $sel:uMirrors:UserSettings :: Maybe DownloadMirrors
uMirrors = forall a. a -> Maybe a
Just DownloadMirrors
mirrors
  }

data UserKeyBindings = UserKeyBindings
  { UserKeyBindings -> Maybe Key
kUp        :: Maybe Key
  , UserKeyBindings -> Maybe Key
kDown      :: Maybe Key
  , UserKeyBindings -> Maybe Key
kQuit      :: Maybe Key
  , UserKeyBindings -> Maybe Key
kInstall   :: Maybe Key
  , UserKeyBindings -> Maybe Key
kUninstall :: Maybe Key
  , UserKeyBindings -> Maybe Key
kSet       :: Maybe Key
  , UserKeyBindings -> Maybe Key
kChangelog :: Maybe Key
  , UserKeyBindings -> Maybe Key
kShowAll   :: Maybe Key
  , UserKeyBindings -> Maybe Key
kShowAllTools :: Maybe Key
  }
  deriving (Int -> UserKeyBindings -> ShowS
[UserKeyBindings] -> ShowS
UserKeyBindings -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [UserKeyBindings] -> ShowS
$cshowList :: [UserKeyBindings] -> ShowS
show :: UserKeyBindings -> FilePath
$cshow :: UserKeyBindings -> FilePath
showsPrec :: Int -> UserKeyBindings -> ShowS
$cshowsPrec :: Int -> UserKeyBindings -> ShowS
Show, forall x. Rep UserKeyBindings x -> UserKeyBindings
forall x. UserKeyBindings -> Rep UserKeyBindings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserKeyBindings x -> UserKeyBindings
$cfrom :: forall x. UserKeyBindings -> Rep UserKeyBindings x
GHC.Generic)

data KeyBindings = KeyBindings
  { KeyBindings -> Key
bUp        :: Key
  , KeyBindings -> Key
bDown      :: Key
  , KeyBindings -> Key
bQuit      :: Key
  , KeyBindings -> Key
bInstall   :: Key
  , KeyBindings -> Key
bUninstall :: Key
  , KeyBindings -> Key
bSet       :: Key
  , KeyBindings -> Key
bChangelog :: Key
  , KeyBindings -> Key
bShowAllVersions :: Key
  , KeyBindings -> Key
bShowAllTools :: Key
  }
  deriving (Int -> KeyBindings -> ShowS
[KeyBindings] -> ShowS
KeyBindings -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [KeyBindings] -> ShowS
$cshowList :: [KeyBindings] -> ShowS
show :: KeyBindings -> FilePath
$cshow :: KeyBindings -> FilePath
showsPrec :: Int -> KeyBindings -> ShowS
$cshowsPrec :: Int -> KeyBindings -> ShowS
Show, forall x. Rep KeyBindings x -> KeyBindings
forall x. KeyBindings -> Rep KeyBindings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep KeyBindings x -> KeyBindings
$cfrom :: forall x. KeyBindings -> Rep KeyBindings x
GHC.Generic)

instance NFData KeyBindings
#if defined(IS_WINDOWS) || !defined(BRICK)
instance NFData Key
#endif

defaultKeyBindings :: KeyBindings
defaultKeyBindings :: KeyBindings
defaultKeyBindings = KeyBindings
  { $sel:bUp:KeyBindings :: Key
bUp = Key
KUp
  , $sel:bDown:KeyBindings :: Key
bDown = Key
KDown
  , $sel:bQuit:KeyBindings :: Key
bQuit = Char -> Key
KChar Char
'q'
  , $sel:bInstall:KeyBindings :: Key
bInstall = Char -> Key
KChar Char
'i'
  , $sel:bUninstall:KeyBindings :: Key
bUninstall = Char -> Key
KChar Char
'u'
  , $sel:bSet:KeyBindings :: Key
bSet = Char -> Key
KChar Char
's'
  , $sel:bChangelog:KeyBindings :: Key
bChangelog = Char -> Key
KChar Char
'c'
  , $sel:bShowAllVersions:KeyBindings :: Key
bShowAllVersions = Char -> Key
KChar Char
'a'
  , $sel:bShowAllTools:KeyBindings :: Key
bShowAllTools = Char -> Key
KChar Char
't'
  }

data AppState = AppState
  { AppState -> Settings
settings :: Settings
  , AppState -> Dirs
dirs :: Dirs
  , AppState -> KeyBindings
keyBindings :: KeyBindings
  , AppState -> GHCupInfo
ghcupInfo :: GHCupInfo
  , AppState -> PlatformRequest
pfreq :: PlatformRequest
  , AppState -> LoggerConfig
loggerConfig :: LoggerConfig
  } deriving (Int -> AppState -> ShowS
[AppState] -> ShowS
AppState -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [AppState] -> ShowS
$cshowList :: [AppState] -> ShowS
show :: AppState -> FilePath
$cshow :: AppState -> FilePath
showsPrec :: Int -> AppState -> ShowS
$cshowsPrec :: Int -> AppState -> ShowS
Show, forall x. Rep AppState x -> AppState
forall x. AppState -> Rep AppState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AppState x -> AppState
$cfrom :: forall x. AppState -> Rep AppState x
GHC.Generic)

instance NFData AppState

fromAppState :: AppState -> LeanAppState
fromAppState :: AppState -> LeanAppState
fromAppState AppState {LoggerConfig
PlatformRequest
Dirs
Settings
KeyBindings
GHCupInfo
loggerConfig :: LoggerConfig
pfreq :: PlatformRequest
ghcupInfo :: GHCupInfo
keyBindings :: KeyBindings
dirs :: Dirs
settings :: Settings
$sel:loggerConfig:AppState :: AppState -> LoggerConfig
$sel:pfreq:AppState :: AppState -> PlatformRequest
$sel:ghcupInfo:AppState :: AppState -> GHCupInfo
$sel:keyBindings:AppState :: AppState -> KeyBindings
$sel:dirs:AppState :: AppState -> Dirs
$sel:settings:AppState :: AppState -> Settings
..} = LeanAppState {LoggerConfig
Dirs
Settings
KeyBindings
$sel:loggerConfig:LeanAppState :: LoggerConfig
$sel:keyBindings:LeanAppState :: KeyBindings
$sel:dirs:LeanAppState :: Dirs
$sel:settings:LeanAppState :: Settings
loggerConfig :: LoggerConfig
keyBindings :: KeyBindings
dirs :: Dirs
settings :: Settings
..}

data LeanAppState = LeanAppState
  { LeanAppState -> Settings
settings :: Settings
  , LeanAppState -> Dirs
dirs :: Dirs
  , LeanAppState -> KeyBindings
keyBindings :: KeyBindings
  , LeanAppState -> LoggerConfig
loggerConfig :: LoggerConfig
  } deriving (Int -> LeanAppState -> ShowS
[LeanAppState] -> ShowS
LeanAppState -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [LeanAppState] -> ShowS
$cshowList :: [LeanAppState] -> ShowS
show :: LeanAppState -> FilePath
$cshow :: LeanAppState -> FilePath
showsPrec :: Int -> LeanAppState -> ShowS
$cshowsPrec :: Int -> LeanAppState -> ShowS
Show, forall x. Rep LeanAppState x -> LeanAppState
forall x. LeanAppState -> Rep LeanAppState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LeanAppState x -> LeanAppState
$cfrom :: forall x. LeanAppState -> Rep LeanAppState x
GHC.Generic)

instance NFData LeanAppState


data Settings = Settings
  { Settings -> Bool
cache            :: Bool
  , Settings -> Integer
metaCache        :: Integer
  , Settings -> MetaMode
metaMode         :: MetaMode
  , Settings -> Bool
noVerify         :: Bool
  , Settings -> KeepDirs
keepDirs         :: KeepDirs
  , Settings -> Downloader
downloader       :: Downloader
  , Settings -> Bool
verbose          :: Bool
  , Settings -> URLSource
urlSource        :: URLSource
  , Settings -> Bool
noNetwork        :: Bool
  , Settings -> GPGSetting
gpgSetting       :: GPGSetting
  , Settings -> Bool
noColor          :: Bool -- this also exists in LoggerConfig
  , Settings -> Maybe PlatformRequest
platformOverride :: Maybe PlatformRequest
  , Settings -> DownloadMirrors
mirrors          :: DownloadMirrors
  }
  deriving (Int -> Settings -> ShowS
[Settings] -> ShowS
Settings -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Settings] -> ShowS
$cshowList :: [Settings] -> ShowS
show :: Settings -> FilePath
$cshow :: Settings -> FilePath
showsPrec :: Int -> Settings -> ShowS
$cshowsPrec :: Int -> Settings -> ShowS
Show, forall x. Rep Settings x -> Settings
forall x. Settings -> Rep Settings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Settings x -> Settings
$cfrom :: forall x. Settings -> Rep Settings x
GHC.Generic)

defaultMetaCache :: Integer
defaultMetaCache :: Integer
defaultMetaCache = Integer
300 -- 5 minutes

defaultSettings :: Settings
defaultSettings :: Settings
defaultSettings = Bool
-> Integer
-> MetaMode
-> Bool
-> KeepDirs
-> Downloader
-> Bool
-> URLSource
-> Bool
-> GPGSetting
-> Bool
-> Maybe PlatformRequest
-> DownloadMirrors
-> Settings
Settings Bool
False Integer
defaultMetaCache MetaMode
Lax Bool
False KeepDirs
Never Downloader
Curl Bool
False URLSource
GHCupURL Bool
False GPGSetting
GPGNone Bool
False forall a. Maybe a
Nothing (Map Text DownloadMirror -> DownloadMirrors
DM forall a. Monoid a => a
mempty)

instance NFData Settings

data Dirs = Dirs
  { Dirs -> GHCupPath
baseDir    :: GHCupPath
  , Dirs -> FilePath
binDir     :: FilePath
  , Dirs -> GHCupPath
cacheDir   :: GHCupPath
  , Dirs -> GHCupPath
logsDir    :: GHCupPath
  , Dirs -> GHCupPath
confDir    :: GHCupPath
  , Dirs -> GHCupPath
dbDir      :: GHCupPath
  , Dirs -> GHCupPath
recycleDir :: GHCupPath -- mainly used on windows
  , Dirs -> GHCupPath
tmpDir     :: GHCupPath
  }
  deriving (Int -> Dirs -> ShowS
[Dirs] -> ShowS
Dirs -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Dirs] -> ShowS
$cshowList :: [Dirs] -> ShowS
show :: Dirs -> FilePath
$cshow :: Dirs -> FilePath
showsPrec :: Int -> Dirs -> ShowS
$cshowsPrec :: Int -> Dirs -> ShowS
Show, forall x. Rep Dirs x -> Dirs
forall x. Dirs -> Rep Dirs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Dirs x -> Dirs
$cfrom :: forall x. Dirs -> Rep Dirs x
GHC.Generic)

instance NFData Dirs

data KeepDirs = Always
              | Errors
              | Never
  deriving (KeepDirs -> KeepDirs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeepDirs -> KeepDirs -> Bool
$c/= :: KeepDirs -> KeepDirs -> Bool
== :: KeepDirs -> KeepDirs -> Bool
$c== :: KeepDirs -> KeepDirs -> Bool
Eq, Int -> KeepDirs -> ShowS
[KeepDirs] -> ShowS
KeepDirs -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [KeepDirs] -> ShowS
$cshowList :: [KeepDirs] -> ShowS
show :: KeepDirs -> FilePath
$cshow :: KeepDirs -> FilePath
showsPrec :: Int -> KeepDirs -> ShowS
$cshowsPrec :: Int -> KeepDirs -> ShowS
Show, Eq KeepDirs
KeepDirs -> KeepDirs -> Bool
KeepDirs -> KeepDirs -> Ordering
KeepDirs -> KeepDirs -> KeepDirs
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: KeepDirs -> KeepDirs -> KeepDirs
$cmin :: KeepDirs -> KeepDirs -> KeepDirs
max :: KeepDirs -> KeepDirs -> KeepDirs
$cmax :: KeepDirs -> KeepDirs -> KeepDirs
>= :: KeepDirs -> KeepDirs -> Bool
$c>= :: KeepDirs -> KeepDirs -> Bool
> :: KeepDirs -> KeepDirs -> Bool
$c> :: KeepDirs -> KeepDirs -> Bool
<= :: KeepDirs -> KeepDirs -> Bool
$c<= :: KeepDirs -> KeepDirs -> Bool
< :: KeepDirs -> KeepDirs -> Bool
$c< :: KeepDirs -> KeepDirs -> Bool
compare :: KeepDirs -> KeepDirs -> Ordering
$ccompare :: KeepDirs -> KeepDirs -> Ordering
Ord, forall x. Rep KeepDirs x -> KeepDirs
forall x. KeepDirs -> Rep KeepDirs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep KeepDirs x -> KeepDirs
$cfrom :: forall x. KeepDirs -> Rep KeepDirs x
GHC.Generic)

instance NFData KeepDirs

data Downloader = Curl
                | Wget
#if defined(INTERNAL_DOWNLOADER)
                | Internal
#endif
  deriving (Downloader -> Downloader -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Downloader -> Downloader -> Bool
$c/= :: Downloader -> Downloader -> Bool
== :: Downloader -> Downloader -> Bool
$c== :: Downloader -> Downloader -> Bool
Eq, Int -> Downloader -> ShowS
[Downloader] -> ShowS
Downloader -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Downloader] -> ShowS
$cshowList :: [Downloader] -> ShowS
show :: Downloader -> FilePath
$cshow :: Downloader -> FilePath
showsPrec :: Int -> Downloader -> ShowS
$cshowsPrec :: Int -> Downloader -> ShowS
Show, Eq Downloader
Downloader -> Downloader -> Bool
Downloader -> Downloader -> Ordering
Downloader -> Downloader -> Downloader
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Downloader -> Downloader -> Downloader
$cmin :: Downloader -> Downloader -> Downloader
max :: Downloader -> Downloader -> Downloader
$cmax :: Downloader -> Downloader -> Downloader
>= :: Downloader -> Downloader -> Bool
$c>= :: Downloader -> Downloader -> Bool
> :: Downloader -> Downloader -> Bool
$c> :: Downloader -> Downloader -> Bool
<= :: Downloader -> Downloader -> Bool
$c<= :: Downloader -> Downloader -> Bool
< :: Downloader -> Downloader -> Bool
$c< :: Downloader -> Downloader -> Bool
compare :: Downloader -> Downloader -> Ordering
$ccompare :: Downloader -> Downloader -> Ordering
Ord, forall x. Rep Downloader x -> Downloader
forall x. Downloader -> Rep Downloader x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Downloader x -> Downloader
$cfrom :: forall x. Downloader -> Rep Downloader x
GHC.Generic)

instance NFData Downloader

data GPGSetting = GPGStrict
                | GPGLax
                | GPGNone
  deriving (GPGSetting -> GPGSetting -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GPGSetting -> GPGSetting -> Bool
$c/= :: GPGSetting -> GPGSetting -> Bool
== :: GPGSetting -> GPGSetting -> Bool
$c== :: GPGSetting -> GPGSetting -> Bool
Eq, Int -> GPGSetting -> ShowS
[GPGSetting] -> ShowS
GPGSetting -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [GPGSetting] -> ShowS
$cshowList :: [GPGSetting] -> ShowS
show :: GPGSetting -> FilePath
$cshow :: GPGSetting -> FilePath
showsPrec :: Int -> GPGSetting -> ShowS
$cshowsPrec :: Int -> GPGSetting -> ShowS
Show, Eq GPGSetting
GPGSetting -> GPGSetting -> Bool
GPGSetting -> GPGSetting -> Ordering
GPGSetting -> GPGSetting -> GPGSetting
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GPGSetting -> GPGSetting -> GPGSetting
$cmin :: GPGSetting -> GPGSetting -> GPGSetting
max :: GPGSetting -> GPGSetting -> GPGSetting
$cmax :: GPGSetting -> GPGSetting -> GPGSetting
>= :: GPGSetting -> GPGSetting -> Bool
$c>= :: GPGSetting -> GPGSetting -> Bool
> :: GPGSetting -> GPGSetting -> Bool
$c> :: GPGSetting -> GPGSetting -> Bool
<= :: GPGSetting -> GPGSetting -> Bool
$c<= :: GPGSetting -> GPGSetting -> Bool
< :: GPGSetting -> GPGSetting -> Bool
$c< :: GPGSetting -> GPGSetting -> Bool
compare :: GPGSetting -> GPGSetting -> Ordering
$ccompare :: GPGSetting -> GPGSetting -> Ordering
Ord, forall x. Rep GPGSetting x -> GPGSetting
forall x. GPGSetting -> Rep GPGSetting x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GPGSetting x -> GPGSetting
$cfrom :: forall x. GPGSetting -> Rep GPGSetting x
GHC.Generic)

instance NFData GPGSetting

data DebugInfo = DebugInfo
  { DebugInfo -> FilePath
diBaseDir  :: FilePath
  , DebugInfo -> FilePath
diBinDir   :: FilePath
  , DebugInfo -> FilePath
diGHCDir   :: FilePath
  , DebugInfo -> FilePath
diCacheDir :: FilePath
  , DebugInfo -> Architecture
diArch     :: Architecture
  , DebugInfo -> PlatformResult
diPlatform :: PlatformResult
  }
  deriving Int -> DebugInfo -> ShowS
[DebugInfo] -> ShowS
DebugInfo -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [DebugInfo] -> ShowS
$cshowList :: [DebugInfo] -> ShowS
show :: DebugInfo -> FilePath
$cshow :: DebugInfo -> FilePath
showsPrec :: Int -> DebugInfo -> ShowS
$cshowsPrec :: Int -> DebugInfo -> ShowS
Show


data SetGHC = SetGHCOnly  -- ^ unversioned 'ghc'
            | SetGHC_XY   -- ^ ghc-x.y
            | SetGHC_XYZ  -- ^ ghc-x.y.z
            deriving (SetGHC -> SetGHC -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetGHC -> SetGHC -> Bool
$c/= :: SetGHC -> SetGHC -> Bool
== :: SetGHC -> SetGHC -> Bool
$c== :: SetGHC -> SetGHC -> Bool
Eq, Int -> SetGHC -> ShowS
[SetGHC] -> ShowS
SetGHC -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [SetGHC] -> ShowS
$cshowList :: [SetGHC] -> ShowS
show :: SetGHC -> FilePath
$cshow :: SetGHC -> FilePath
showsPrec :: Int -> SetGHC -> ShowS
$cshowsPrec :: Int -> SetGHC -> ShowS
Show)

data SetHLS = SetHLSOnly  -- ^ unversioned 'hls'
            | 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
            deriving (SetHLS -> SetHLS -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetHLS -> SetHLS -> Bool
$c/= :: SetHLS -> SetHLS -> Bool
== :: SetHLS -> SetHLS -> Bool
$c== :: SetHLS -> SetHLS -> Bool
Eq, Int -> SetHLS -> ShowS
[SetHLS] -> ShowS
SetHLS -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [SetHLS] -> ShowS
$cshowList :: [SetHLS] -> ShowS
show :: SetHLS -> FilePath
$cshow :: SetHLS -> FilePath
showsPrec :: Int -> SetHLS -> ShowS
$cshowsPrec :: Int -> SetHLS -> ShowS
Show)


data PlatformResult = PlatformResult
  { PlatformResult -> Platform
_platform      :: Platform
  , PlatformResult -> Maybe Versioning
_distroVersion :: Maybe Versioning
  }
  deriving (PlatformResult -> PlatformResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PlatformResult -> PlatformResult -> Bool
$c/= :: PlatformResult -> PlatformResult -> Bool
== :: PlatformResult -> PlatformResult -> Bool
$c== :: PlatformResult -> PlatformResult -> Bool
Eq, Int -> PlatformResult -> ShowS
[PlatformResult] -> ShowS
PlatformResult -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [PlatformResult] -> ShowS
$cshowList :: [PlatformResult] -> ShowS
show :: PlatformResult -> FilePath
$cshow :: PlatformResult -> FilePath
showsPrec :: Int -> PlatformResult -> ShowS
$cshowsPrec :: Int -> PlatformResult -> ShowS
Show, forall x. Rep PlatformResult x -> PlatformResult
forall x. PlatformResult -> Rep PlatformResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PlatformResult x -> PlatformResult
$cfrom :: forall x. PlatformResult -> Rep PlatformResult x
GHC.Generic)

instance NFData PlatformResult

platResToString :: PlatformResult -> String
platResToString :: PlatformResult -> FilePath
platResToString PlatformResult { $sel:_platform:PlatformResult :: PlatformResult -> Platform
_platform = Platform
plat, $sel:_distroVersion:PlatformResult :: PlatformResult -> Maybe Versioning
_distroVersion = Just Versioning
v' }
  = forall a. Show a => a -> FilePath
show Platform
plat forall a. Semigroup a => a -> a -> a
<> FilePath
", " forall a. Semigroup a => a -> a -> a
<> Text -> FilePath
T.unpack (Versioning -> Text
prettyV Versioning
v')
platResToString PlatformResult { $sel:_platform:PlatformResult :: PlatformResult -> Platform
_platform = Platform
plat, $sel:_distroVersion:PlatformResult :: PlatformResult -> Maybe Versioning
_distroVersion = Maybe Versioning
Nothing }
  = forall a. Show a => a -> FilePath
show Platform
plat

instance Pretty PlatformResult where
  pPrint :: PlatformResult -> Doc
pPrint = FilePath -> Doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlatformResult -> FilePath
platResToString

data PlatformRequest = PlatformRequest
  { PlatformRequest -> Architecture
_rArch     :: Architecture
  , PlatformRequest -> Platform
_rPlatform :: Platform
  , PlatformRequest -> Maybe Versioning
_rVersion  :: Maybe Versioning
  }
  deriving (PlatformRequest -> PlatformRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PlatformRequest -> PlatformRequest -> Bool
$c/= :: PlatformRequest -> PlatformRequest -> Bool
== :: PlatformRequest -> PlatformRequest -> Bool
$c== :: PlatformRequest -> PlatformRequest -> Bool
Eq, Int -> PlatformRequest -> ShowS
[PlatformRequest] -> ShowS
PlatformRequest -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [PlatformRequest] -> ShowS
$cshowList :: [PlatformRequest] -> ShowS
show :: PlatformRequest -> FilePath
$cshow :: PlatformRequest -> FilePath
showsPrec :: Int -> PlatformRequest -> ShowS
$cshowsPrec :: Int -> PlatformRequest -> ShowS
Show, forall x. Rep PlatformRequest x -> PlatformRequest
forall x. PlatformRequest -> Rep PlatformRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PlatformRequest x -> PlatformRequest
$cfrom :: forall x. PlatformRequest -> Rep PlatformRequest x
GHC.Generic)

instance NFData PlatformRequest

pfReqToString :: PlatformRequest -> String
pfReqToString :: PlatformRequest -> FilePath
pfReqToString (PlatformRequest Architecture
arch Platform
plat Maybe Versioning
ver) =
  Architecture -> FilePath
archToString Architecture
arch forall a. [a] -> [a] -> [a]
++ FilePath
"-" forall a. [a] -> [a] -> [a]
++ Platform -> FilePath
platformToString Platform
plat forall a. [a] -> [a] -> [a]
++ FilePath
pver
 where
  pver :: FilePath
pver = case Maybe Versioning
ver of
           Just Versioning
v' -> FilePath
"-" forall a. [a] -> [a] -> [a]
++ Text -> FilePath
T.unpack (Versioning -> Text
prettyV Versioning
v')
           Maybe Versioning
Nothing -> FilePath
""

instance Pretty PlatformRequest where
  pPrint :: PlatformRequest -> Doc
pPrint = FilePath -> Doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlatformRequest -> FilePath
pfReqToString

-- | A GHC identified by the target platform triple
-- and the version.
data GHCTargetVersion = GHCTargetVersion
  { GHCTargetVersion -> Maybe Text
_tvTarget  :: Maybe Text
  , GHCTargetVersion -> Version
_tvVersion :: Version
  }
  deriving (Eq GHCTargetVersion
GHCTargetVersion -> GHCTargetVersion -> Bool
GHCTargetVersion -> GHCTargetVersion -> Ordering
GHCTargetVersion -> GHCTargetVersion -> GHCTargetVersion
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GHCTargetVersion -> GHCTargetVersion -> GHCTargetVersion
$cmin :: GHCTargetVersion -> GHCTargetVersion -> GHCTargetVersion
max :: GHCTargetVersion -> GHCTargetVersion -> GHCTargetVersion
$cmax :: GHCTargetVersion -> GHCTargetVersion -> GHCTargetVersion
>= :: GHCTargetVersion -> GHCTargetVersion -> Bool
$c>= :: GHCTargetVersion -> GHCTargetVersion -> Bool
> :: GHCTargetVersion -> GHCTargetVersion -> Bool
$c> :: GHCTargetVersion -> GHCTargetVersion -> Bool
<= :: GHCTargetVersion -> GHCTargetVersion -> Bool
$c<= :: GHCTargetVersion -> GHCTargetVersion -> Bool
< :: GHCTargetVersion -> GHCTargetVersion -> Bool
$c< :: GHCTargetVersion -> GHCTargetVersion -> Bool
compare :: GHCTargetVersion -> GHCTargetVersion -> Ordering
$ccompare :: GHCTargetVersion -> GHCTargetVersion -> Ordering
Ord, GHCTargetVersion -> GHCTargetVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GHCTargetVersion -> GHCTargetVersion -> Bool
$c/= :: GHCTargetVersion -> GHCTargetVersion -> Bool
== :: GHCTargetVersion -> GHCTargetVersion -> Bool
$c== :: GHCTargetVersion -> GHCTargetVersion -> Bool
Eq, Int -> GHCTargetVersion -> ShowS
[GHCTargetVersion] -> ShowS
GHCTargetVersion -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [GHCTargetVersion] -> ShowS
$cshowList :: [GHCTargetVersion] -> ShowS
show :: GHCTargetVersion -> FilePath
$cshow :: GHCTargetVersion -> FilePath
showsPrec :: Int -> GHCTargetVersion -> ShowS
$cshowsPrec :: Int -> GHCTargetVersion -> ShowS
Show, forall x. Rep GHCTargetVersion x -> GHCTargetVersion
forall x. GHCTargetVersion -> Rep GHCTargetVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GHCTargetVersion x -> GHCTargetVersion
$cfrom :: forall x. GHCTargetVersion -> Rep GHCTargetVersion x
GHC.Generic)

instance NFData GHCTargetVersion

data GitBranch = GitBranch
  { GitBranch -> FilePath
ref  :: String
  , GitBranch -> Maybe FilePath
repo :: Maybe String
  }
  deriving (Eq GitBranch
GitBranch -> GitBranch -> Bool
GitBranch -> GitBranch -> Ordering
GitBranch -> GitBranch -> GitBranch
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GitBranch -> GitBranch -> GitBranch
$cmin :: GitBranch -> GitBranch -> GitBranch
max :: GitBranch -> GitBranch -> GitBranch
$cmax :: GitBranch -> GitBranch -> GitBranch
>= :: GitBranch -> GitBranch -> Bool
$c>= :: GitBranch -> GitBranch -> Bool
> :: GitBranch -> GitBranch -> Bool
$c> :: GitBranch -> GitBranch -> Bool
<= :: GitBranch -> GitBranch -> Bool
$c<= :: GitBranch -> GitBranch -> Bool
< :: GitBranch -> GitBranch -> Bool
$c< :: GitBranch -> GitBranch -> Bool
compare :: GitBranch -> GitBranch -> Ordering
$ccompare :: GitBranch -> GitBranch -> Ordering
Ord, GitBranch -> GitBranch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GitBranch -> GitBranch -> Bool
$c/= :: GitBranch -> GitBranch -> Bool
== :: GitBranch -> GitBranch -> Bool
$c== :: GitBranch -> GitBranch -> Bool
Eq, Int -> GitBranch -> ShowS
[GitBranch] -> ShowS
GitBranch -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [GitBranch] -> ShowS
$cshowList :: [GitBranch] -> ShowS
show :: GitBranch -> FilePath
$cshow :: GitBranch -> FilePath
showsPrec :: Int -> GitBranch -> ShowS
$cshowsPrec :: Int -> GitBranch -> ShowS
Show)

mkTVer :: Version -> GHCTargetVersion
mkTVer :: Version -> GHCTargetVersion
mkTVer = Maybe Text -> Version -> GHCTargetVersion
GHCTargetVersion forall a. Maybe a
Nothing

tVerToText :: GHCTargetVersion -> Text
tVerToText :: GHCTargetVersion -> Text
tVerToText (GHCTargetVersion (Just Text
t) Version
v') = Text
t forall a. Semigroup a => a -> a -> a
<> Text
"-" forall a. Semigroup a => a -> a -> a
<> Version -> Text
prettyVer Version
v'
tVerToText (GHCTargetVersion Maybe Text
Nothing  Version
v') = Version -> Text
prettyVer Version
v'

-- | Assembles a path of the form: <target-triple>-<version>
instance Pretty GHCTargetVersion where
  pPrint :: GHCTargetVersion -> Doc
pPrint = FilePath -> Doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. GHCTargetVersion -> Text
tVerToText


-- | A comparator and a version.
data VersionCmp = VR_gt Versioning
                | VR_gteq Versioning
                | VR_lt Versioning
                | VR_lteq Versioning
                | VR_eq Versioning
  deriving (VersionCmp -> VersionCmp -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionCmp -> VersionCmp -> Bool
$c/= :: VersionCmp -> VersionCmp -> Bool
== :: VersionCmp -> VersionCmp -> Bool
$c== :: VersionCmp -> VersionCmp -> Bool
Eq, forall x. Rep VersionCmp x -> VersionCmp
forall x. VersionCmp -> Rep VersionCmp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VersionCmp x -> VersionCmp
$cfrom :: forall x. VersionCmp -> Rep VersionCmp x
GHC.Generic, Eq VersionCmp
VersionCmp -> VersionCmp -> Bool
VersionCmp -> VersionCmp -> Ordering
VersionCmp -> VersionCmp -> VersionCmp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VersionCmp -> VersionCmp -> VersionCmp
$cmin :: VersionCmp -> VersionCmp -> VersionCmp
max :: VersionCmp -> VersionCmp -> VersionCmp
$cmax :: VersionCmp -> VersionCmp -> VersionCmp
>= :: VersionCmp -> VersionCmp -> Bool
$c>= :: VersionCmp -> VersionCmp -> Bool
> :: VersionCmp -> VersionCmp -> Bool
$c> :: VersionCmp -> VersionCmp -> Bool
<= :: VersionCmp -> VersionCmp -> Bool
$c<= :: VersionCmp -> VersionCmp -> Bool
< :: VersionCmp -> VersionCmp -> Bool
$c< :: VersionCmp -> VersionCmp -> Bool
compare :: VersionCmp -> VersionCmp -> Ordering
$ccompare :: VersionCmp -> VersionCmp -> Ordering
Ord, Int -> VersionCmp -> ShowS
[VersionCmp] -> ShowS
VersionCmp -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [VersionCmp] -> ShowS
$cshowList :: [VersionCmp] -> ShowS
show :: VersionCmp -> FilePath
$cshow :: VersionCmp -> FilePath
showsPrec :: Int -> VersionCmp -> ShowS
$cshowsPrec :: Int -> VersionCmp -> ShowS
Show)

instance NFData VersionCmp


-- | A version range. Supports && and ||, but not  arbitrary
-- combinations. This is a little simplified.
data VersionRange = SimpleRange (NonEmpty VersionCmp) -- And
                  | OrRange (NonEmpty VersionCmp) VersionRange
  deriving (VersionRange -> VersionRange -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionRange -> VersionRange -> Bool
$c/= :: VersionRange -> VersionRange -> Bool
== :: VersionRange -> VersionRange -> Bool
$c== :: VersionRange -> VersionRange -> Bool
Eq, forall x. Rep VersionRange x -> VersionRange
forall x. VersionRange -> Rep VersionRange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VersionRange x -> VersionRange
$cfrom :: forall x. VersionRange -> Rep VersionRange x
GHC.Generic, Eq VersionRange
VersionRange -> VersionRange -> Bool
VersionRange -> VersionRange -> Ordering
VersionRange -> VersionRange -> VersionRange
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VersionRange -> VersionRange -> VersionRange
$cmin :: VersionRange -> VersionRange -> VersionRange
max :: VersionRange -> VersionRange -> VersionRange
$cmax :: VersionRange -> VersionRange -> VersionRange
>= :: VersionRange -> VersionRange -> Bool
$c>= :: VersionRange -> VersionRange -> Bool
> :: VersionRange -> VersionRange -> Bool
$c> :: VersionRange -> VersionRange -> Bool
<= :: VersionRange -> VersionRange -> Bool
$c<= :: VersionRange -> VersionRange -> Bool
< :: VersionRange -> VersionRange -> Bool
$c< :: VersionRange -> VersionRange -> Bool
compare :: VersionRange -> VersionRange -> Ordering
$ccompare :: VersionRange -> VersionRange -> Ordering
Ord, Int -> VersionRange -> ShowS
[VersionRange] -> ShowS
VersionRange -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [VersionRange] -> ShowS
$cshowList :: [VersionRange] -> ShowS
show :: VersionRange -> FilePath
$cshow :: VersionRange -> FilePath
showsPrec :: Int -> VersionRange -> ShowS
$cshowsPrec :: Int -> VersionRange -> ShowS
Show)

instance NFData VersionRange

instance Pretty Versioning where
  pPrint :: Versioning -> Doc
pPrint = FilePath -> Doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Versioning -> Text
prettyV

instance Pretty Version where
  pPrint :: Version -> Doc
pPrint = FilePath -> Doc
text forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> Text
prettyVer

instance Show (a -> b) where
  show :: (a -> b) -> FilePath
show a -> b
_ = FilePath
"<function>"

instance Show (IO ()) where
  show :: IO () -> FilePath
show IO ()
_ = FilePath
"<io>"


data LogLevel = Warn
              | Info
              | Debug
              | Error
  deriving (LogLevel -> LogLevel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogLevel -> LogLevel -> Bool
$c/= :: LogLevel -> LogLevel -> Bool
== :: LogLevel -> LogLevel -> Bool
$c== :: LogLevel -> LogLevel -> Bool
Eq, Eq LogLevel
LogLevel -> LogLevel -> Bool
LogLevel -> LogLevel -> Ordering
LogLevel -> LogLevel -> LogLevel
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LogLevel -> LogLevel -> LogLevel
$cmin :: LogLevel -> LogLevel -> LogLevel
max :: LogLevel -> LogLevel -> LogLevel
$cmax :: LogLevel -> LogLevel -> LogLevel
>= :: LogLevel -> LogLevel -> Bool
$c>= :: LogLevel -> LogLevel -> Bool
> :: LogLevel -> LogLevel -> Bool
$c> :: LogLevel -> LogLevel -> Bool
<= :: LogLevel -> LogLevel -> Bool
$c<= :: LogLevel -> LogLevel -> Bool
< :: LogLevel -> LogLevel -> Bool
$c< :: LogLevel -> LogLevel -> Bool
compare :: LogLevel -> LogLevel -> Ordering
$ccompare :: LogLevel -> LogLevel -> Ordering
Ord, Int -> LogLevel -> ShowS
[LogLevel] -> ShowS
LogLevel -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [LogLevel] -> ShowS
$cshowList :: [LogLevel] -> ShowS
show :: LogLevel -> FilePath
$cshow :: LogLevel -> FilePath
showsPrec :: Int -> LogLevel -> ShowS
$cshowsPrec :: Int -> LogLevel -> ShowS
Show)

data LoggerConfig = LoggerConfig
  { LoggerConfig -> Bool
lcPrintDebug   :: Bool            -- ^ whether to print debug in colorOutter
  , LoggerConfig -> Text -> IO ()
consoleOutter  :: T.Text -> IO () -- ^ how to write the console output
  , LoggerConfig -> Text -> IO ()
fileOutter     :: T.Text -> IO () -- ^ how to write the file output
  , LoggerConfig -> Bool
fancyColors    :: Bool
  }
  deriving Int -> LoggerConfig -> ShowS
[LoggerConfig] -> ShowS
LoggerConfig -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [LoggerConfig] -> ShowS
$cshowList :: [LoggerConfig] -> ShowS
show :: LoggerConfig -> FilePath
$cshow :: LoggerConfig -> FilePath
showsPrec :: Int -> LoggerConfig -> ShowS
$cshowsPrec :: Int -> LoggerConfig -> ShowS
Show

instance NFData LoggerConfig where
  rnf :: LoggerConfig -> ()
rnf (LoggerConfig !Bool
lcPrintDebug !Text -> IO ()
_ !Text -> IO ()
_ !Bool
fancyColors) = forall a. NFData a => a -> ()
rnf (Bool
lcPrintDebug, Bool
fancyColors)

data ProcessError = NonZeroExit Int FilePath [String]
                  | PTerminated FilePath [String]
                  | PStopped FilePath [String]
                  | NoSuchPid FilePath [String]
                  deriving Int -> ProcessError -> ShowS
[ProcessError] -> ShowS
ProcessError -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ProcessError] -> ShowS
$cshowList :: [ProcessError] -> ShowS
show :: ProcessError -> FilePath
$cshow :: ProcessError -> FilePath
showsPrec :: Int -> ProcessError -> ShowS
$cshowsPrec :: Int -> ProcessError -> ShowS
Show


data CapturedProcess = CapturedProcess
  { CapturedProcess -> ExitCode
_exitCode :: ExitCode
  , CapturedProcess -> ByteString
_stdOut   :: BL.ByteString
  , CapturedProcess -> ByteString
_stdErr   :: BL.ByteString
  }
  deriving (CapturedProcess -> CapturedProcess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CapturedProcess -> CapturedProcess -> Bool
$c/= :: CapturedProcess -> CapturedProcess -> Bool
== :: CapturedProcess -> CapturedProcess -> Bool
$c== :: CapturedProcess -> CapturedProcess -> Bool
Eq, Int -> CapturedProcess -> ShowS
[CapturedProcess] -> ShowS
CapturedProcess -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [CapturedProcess] -> ShowS
$cshowList :: [CapturedProcess] -> ShowS
show :: CapturedProcess -> FilePath
$cshow :: CapturedProcess -> FilePath
showsPrec :: Int -> CapturedProcess -> ShowS
$cshowsPrec :: Int -> CapturedProcess -> ShowS
Show)

makeLenses ''CapturedProcess


data InstallDir = IsolateDir FilePath
                | GHCupInternal
  deriving (InstallDir -> InstallDir -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstallDir -> InstallDir -> Bool
$c/= :: InstallDir -> InstallDir -> Bool
== :: InstallDir -> InstallDir -> Bool
$c== :: InstallDir -> InstallDir -> Bool
Eq, Int -> InstallDir -> ShowS
[InstallDir] -> ShowS
InstallDir -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [InstallDir] -> ShowS
$cshowList :: [InstallDir] -> ShowS
show :: InstallDir -> FilePath
$cshow :: InstallDir -> FilePath
showsPrec :: Int -> InstallDir -> ShowS
$cshowsPrec :: Int -> InstallDir -> ShowS
Show)

data InstallDirResolved = IsolateDirResolved FilePath
                        | GHCupDir GHCupPath
                        | GHCupBinDir FilePath
  deriving (InstallDirResolved -> InstallDirResolved -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstallDirResolved -> InstallDirResolved -> Bool
$c/= :: InstallDirResolved -> InstallDirResolved -> Bool
== :: InstallDirResolved -> InstallDirResolved -> Bool
$c== :: InstallDirResolved -> InstallDirResolved -> Bool
Eq, Int -> InstallDirResolved -> ShowS
[InstallDirResolved] -> ShowS
InstallDirResolved -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [InstallDirResolved] -> ShowS
$cshowList :: [InstallDirResolved] -> ShowS
show :: InstallDirResolved -> FilePath
$cshow :: InstallDirResolved -> FilePath
showsPrec :: Int -> InstallDirResolved -> ShowS
$cshowsPrec :: Int -> InstallDirResolved -> ShowS
Show)

fromInstallDir :: InstallDirResolved -> FilePath
fromInstallDir :: InstallDirResolved -> FilePath
fromInstallDir (IsolateDirResolved FilePath
fp) = FilePath
fp
fromInstallDir (GHCupDir GHCupPath
fp) = GHCupPath -> FilePath
fromGHCupPath GHCupPath
fp
fromInstallDir (GHCupBinDir FilePath
fp) = FilePath
fp


isSafeDir :: InstallDirResolved -> Bool
isSafeDir :: InstallDirResolved -> Bool
isSafeDir (IsolateDirResolved FilePath
_) = Bool
False
isSafeDir (GHCupDir GHCupPath
_)           = Bool
True
isSafeDir (GHCupBinDir FilePath
_)        = Bool
False

type PromptQuestion = Text

data PromptResponse = PromptYes | PromptNo
  deriving (Int -> PromptResponse -> ShowS
[PromptResponse] -> ShowS
PromptResponse -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [PromptResponse] -> ShowS
$cshowList :: [PromptResponse] -> ShowS
show :: PromptResponse -> FilePath
$cshow :: PromptResponse -> FilePath
showsPrec :: Int -> PromptResponse -> ShowS
$cshowsPrec :: Int -> PromptResponse -> ShowS
Show, PromptResponse -> PromptResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PromptResponse -> PromptResponse -> Bool
$c/= :: PromptResponse -> PromptResponse -> Bool
== :: PromptResponse -> PromptResponse -> Bool
$c== :: PromptResponse -> PromptResponse -> Bool
Eq)

data ToolVersion = GHCVersion GHCTargetVersion
                 | ToolVersion Version
                 | ToolTag Tag
                 | ToolDay Day

instance Pretty ToolVersion where
  pPrint :: ToolVersion -> Doc
pPrint (GHCVersion GHCTargetVersion
v) = forall a. Pretty a => a -> Doc
pPrint GHCTargetVersion
v
  pPrint (ToolVersion Version
v) = forall a. Pretty a => a -> Doc
pPrint Version
v
  pPrint (ToolTag Tag
t) = forall a. Pretty a => a -> Doc
pPrint Tag
t
  pPrint (ToolDay Day
d) = FilePath -> Doc
text (forall a. Show a => a -> FilePath
show Day
d)