{-# 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           Control.DeepSeq                ( NFData, rnf )
import           Data.Map.Strict                ( Map )
import           Data.List.NonEmpty             ( NonEmpty (..) )
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 (Key -> Key -> Bool
(Key -> Key -> Bool) -> (Key -> Key -> Bool) -> Eq Key
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c== :: Key -> Key -> Bool
Eq,Int -> Key -> ShowS
[Key] -> ShowS
Key -> String
(Int -> Key -> ShowS)
-> (Key -> String) -> ([Key] -> ShowS) -> Show Key
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Key] -> ShowS
$cshowList :: [Key] -> ShowS
show :: Key -> String
$cshow :: Key -> String
showsPrec :: Int -> Key -> ShowS
$cshowsPrec :: Int -> Key -> ShowS
Show,ReadPrec [Key]
ReadPrec Key
Int -> ReadS Key
ReadS [Key]
(Int -> ReadS Key)
-> ReadS [Key] -> ReadPrec Key -> ReadPrec [Key] -> Read Key
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Key]
$creadListPrec :: ReadPrec [Key]
readPrec :: ReadPrec Key
$creadPrec :: ReadPrec Key
readList :: ReadS [Key]
$creadList :: ReadS [Key]
readsPrec :: Int -> ReadS Key
$creadsPrec :: Int -> ReadS Key
Read,Eq Key
Eq Key
-> (Key -> Key -> Ordering)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Key)
-> (Key -> Key -> Key)
-> Ord Key
Key -> Key -> Bool
Key -> Key -> Ordering
Key -> Key -> Key
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 :: Key -> Key -> Key
$cmin :: Key -> Key -> Key
max :: Key -> Key -> Key
$cmax :: Key -> Key -> Key
>= :: Key -> Key -> Bool
$c>= :: Key -> Key -> Bool
> :: Key -> Key -> Bool
$c> :: Key -> Key -> Bool
<= :: Key -> Key -> Bool
$c<= :: Key -> Key -> Bool
< :: Key -> Key -> Bool
$c< :: Key -> Key -> Bool
compare :: Key -> Key -> Ordering
$ccompare :: Key -> Key -> Ordering
$cp1Ord :: Eq Key
Ord,(forall x. Key -> Rep Key x)
-> (forall x. Rep Key x -> Key) -> Generic Key
forall x. Rep Key x -> Key
forall x. Key -> Rep Key x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Key x -> Key
$cfrom :: forall x. Key -> Rep Key x
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 -> String
(Int -> GHCupInfo -> ShowS)
-> (GHCupInfo -> String)
-> ([GHCupInfo] -> ShowS)
-> Show GHCupInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GHCupInfo] -> ShowS
$cshowList :: [GHCupInfo] -> ShowS
show :: GHCupInfo -> String
$cshow :: GHCupInfo -> String
showsPrec :: Int -> GHCupInfo -> ShowS
$cshowsPrec :: Int -> GHCupInfo -> ShowS
Show, (forall x. GHCupInfo -> Rep GHCupInfo x)
-> (forall x. Rep GHCupInfo x -> GHCupInfo) -> Generic GHCupInfo
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)

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 -> String
(Int -> Requirements -> ShowS)
-> (Requirements -> String)
-> ([Requirements] -> ShowS)
-> Show Requirements
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Requirements] -> ShowS
$cshowList :: [Requirements] -> ShowS
show :: Requirements -> String
$cshow :: Requirements -> String
showsPrec :: Int -> Requirements -> ShowS
$cshowsPrec :: Int -> Requirements -> ShowS
Show, (forall x. Requirements -> Rep Requirements x)
-> (forall x. Rep Requirements x -> Requirements)
-> Generic Requirements
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)

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 Version 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
(Tool -> Tool -> Bool) -> (Tool -> Tool -> Bool) -> Eq Tool
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. Tool -> Rep Tool x)
-> (forall x. Rep Tool x -> Tool) -> Generic Tool
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
Eq Tool
-> (Tool -> Tool -> Ordering)
-> (Tool -> Tool -> Bool)
-> (Tool -> Tool -> Bool)
-> (Tool -> Tool -> Bool)
-> (Tool -> Tool -> Bool)
-> (Tool -> Tool -> Tool)
-> (Tool -> Tool -> Tool)
-> Ord 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
$cp1Ord :: Eq Tool
Ord, Int -> Tool -> ShowS
[Tool] -> ShowS
Tool -> String
(Int -> Tool -> ShowS)
-> (Tool -> String) -> ([Tool] -> ShowS) -> Show Tool
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tool] -> ShowS
$cshowList :: [Tool] -> ShowS
show :: Tool -> String
$cshow :: Tool -> String
showsPrec :: Int -> Tool -> ShowS
$cshowsPrec :: Int -> Tool -> ShowS
Show, Int -> Tool
Tool -> Int
Tool -> [Tool]
Tool -> Tool
Tool -> Tool -> [Tool]
Tool -> Tool -> Tool -> [Tool]
(Tool -> Tool)
-> (Tool -> Tool)
-> (Int -> Tool)
-> (Tool -> Int)
-> (Tool -> [Tool])
-> (Tool -> Tool -> [Tool])
-> (Tool -> Tool -> [Tool])
-> (Tool -> Tool -> Tool -> [Tool])
-> Enum 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
Tool -> Tool -> Bounded 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 = String -> Doc
text String
"ghc"
  pPrint Tool
Cabal = String -> Doc
text String
"cabal"
  pPrint Tool
GHCup = String -> Doc
text String
"ghcup"
  pPrint Tool
HLS = String -> Doc
text String
"hls"
  pPrint Tool
Stack = String -> Doc
text String
"stack"

instance NFData Tool

data GlobalTool = ShimGen
  deriving (GlobalTool -> GlobalTool -> Bool
(GlobalTool -> GlobalTool -> Bool)
-> (GlobalTool -> GlobalTool -> Bool) -> Eq GlobalTool
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. GlobalTool -> Rep GlobalTool x)
-> (forall x. Rep GlobalTool x -> GlobalTool) -> Generic GlobalTool
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
Eq GlobalTool
-> (GlobalTool -> GlobalTool -> Ordering)
-> (GlobalTool -> GlobalTool -> Bool)
-> (GlobalTool -> GlobalTool -> Bool)
-> (GlobalTool -> GlobalTool -> Bool)
-> (GlobalTool -> GlobalTool -> Bool)
-> (GlobalTool -> GlobalTool -> GlobalTool)
-> (GlobalTool -> GlobalTool -> GlobalTool)
-> Ord 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
$cp1Ord :: Eq GlobalTool
Ord, Int -> GlobalTool -> ShowS
[GlobalTool] -> ShowS
GlobalTool -> String
(Int -> GlobalTool -> ShowS)
-> (GlobalTool -> String)
-> ([GlobalTool] -> ShowS)
-> Show GlobalTool
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GlobalTool] -> ShowS
$cshowList :: [GlobalTool] -> ShowS
show :: GlobalTool -> String
$cshow :: GlobalTool -> String
showsPrec :: Int -> GlobalTool -> ShowS
$cshowsPrec :: Int -> GlobalTool -> ShowS
Show, Int -> GlobalTool
GlobalTool -> Int
GlobalTool -> [GlobalTool]
GlobalTool -> GlobalTool
GlobalTool -> GlobalTool -> [GlobalTool]
GlobalTool -> GlobalTool -> GlobalTool -> [GlobalTool]
(GlobalTool -> GlobalTool)
-> (GlobalTool -> GlobalTool)
-> (Int -> GlobalTool)
-> (GlobalTool -> Int)
-> (GlobalTool -> [GlobalTool])
-> (GlobalTool -> GlobalTool -> [GlobalTool])
-> (GlobalTool -> GlobalTool -> [GlobalTool])
-> (GlobalTool -> GlobalTool -> GlobalTool -> [GlobalTool])
-> Enum 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
GlobalTool -> GlobalTool -> Bounded 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 URI
_viChangeLog   :: Maybe URI
  , VersionInfo -> Maybe DownloadInfo
_viSourceDL    :: Maybe DownloadInfo -- ^ source 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
(VersionInfo -> VersionInfo -> Bool)
-> (VersionInfo -> VersionInfo -> Bool) -> Eq VersionInfo
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. VersionInfo -> Rep VersionInfo x)
-> (forall x. Rep VersionInfo x -> VersionInfo)
-> Generic VersionInfo
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 -> String
(Int -> VersionInfo -> ShowS)
-> (VersionInfo -> String)
-> ([VersionInfo] -> ShowS)
-> Show VersionInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VersionInfo] -> ShowS
$cshowList :: [VersionInfo] -> ShowS
show :: VersionInfo -> String
$cshow :: VersionInfo -> String
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
         | Base PVP
         | Old                -- ^ old versions are hidden by default in TUI
         | UnknownTag String  -- ^ used for upwardscompat
         deriving (Eq Tag
Eq Tag
-> (Tag -> Tag -> Ordering)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Bool)
-> (Tag -> Tag -> Tag)
-> (Tag -> Tag -> Tag)
-> Ord 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
$cp1Ord :: Eq Tag
Ord, Tag -> Tag -> Bool
(Tag -> Tag -> Bool) -> (Tag -> Tag -> Bool) -> Eq Tag
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. Tag -> Rep Tag x)
-> (forall x. Rep Tag x -> Tag) -> Generic Tag
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 -> String
(Int -> Tag -> ShowS)
-> (Tag -> String) -> ([Tag] -> ShowS) -> Show Tag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tag] -> ShowS
$cshowList :: [Tag] -> ShowS
show :: Tag -> String
$cshow :: Tag -> String
showsPrec :: Int -> Tag -> ShowS
$cshowsPrec :: Int -> Tag -> ShowS
Show) -- FIXME: manual JSON instance

instance NFData Tag

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

instance Pretty Tag where
  pPrint :: Tag -> Doc
pPrint Tag
Recommended        = String -> Doc
text String
"recommended"
  pPrint Tag
Latest             = String -> Doc
text String
"latest"
  pPrint Tag
Prerelease         = String -> Doc
text String
"prerelease"
  pPrint (Base       PVP
pvp'') = String -> Doc
text (String
"base-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack (PVP -> Text
prettyPVP PVP
pvp''))
  pPrint (UnknownTag String
t    ) = String -> Doc
text String
t
  pPrint Tag
Old                = Doc
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
(Architecture -> Architecture -> Bool)
-> (Architecture -> Architecture -> Bool) -> Eq Architecture
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. Architecture -> Rep Architecture x)
-> (forall x. Rep Architecture x -> Architecture)
-> Generic Architecture
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
Eq Architecture
-> (Architecture -> Architecture -> Ordering)
-> (Architecture -> Architecture -> Bool)
-> (Architecture -> Architecture -> Bool)
-> (Architecture -> Architecture -> Bool)
-> (Architecture -> Architecture -> Bool)
-> (Architecture -> Architecture -> Architecture)
-> (Architecture -> Architecture -> Architecture)
-> Ord 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
$cp1Ord :: Eq Architecture
Ord, Int -> Architecture -> ShowS
[Architecture] -> ShowS
Architecture -> String
(Int -> Architecture -> ShowS)
-> (Architecture -> String)
-> ([Architecture] -> ShowS)
-> Show Architecture
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Architecture] -> ShowS
$cshowList :: [Architecture] -> ShowS
show :: Architecture -> String
$cshow :: Architecture -> String
showsPrec :: Int -> Architecture -> ShowS
$cshowsPrec :: Int -> Architecture -> ShowS
Show)

instance NFData Architecture

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

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

data Platform = Linux LinuxDistro
              -- ^ must exit
              | Darwin
              -- ^ must exit
              | FreeBSD
              | Windows
              -- ^ must exit
  deriving (Platform -> Platform -> Bool
(Platform -> Platform -> Bool)
-> (Platform -> Platform -> Bool) -> Eq Platform
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. Platform -> Rep Platform x)
-> (forall x. Rep Platform x -> Platform) -> Generic Platform
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
Eq Platform
-> (Platform -> Platform -> Ordering)
-> (Platform -> Platform -> Bool)
-> (Platform -> Platform -> Bool)
-> (Platform -> Platform -> Bool)
-> (Platform -> Platform -> Bool)
-> (Platform -> Platform -> Platform)
-> (Platform -> Platform -> Platform)
-> Ord 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
$cp1Ord :: Eq Platform
Ord, Int -> Platform -> ShowS
[Platform] -> ShowS
Platform -> String
(Int -> Platform -> ShowS)
-> (Platform -> String) -> ([Platform] -> ShowS) -> Show Platform
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Platform] -> ShowS
$cshowList :: [Platform] -> ShowS
show :: Platform -> String
$cshow :: Platform -> String
showsPrec :: Int -> Platform -> ShowS
$cshowsPrec :: Int -> Platform -> ShowS
Show)

instance NFData Platform

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

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

data LinuxDistro = Debian
                 | Ubuntu
                 | Mint
                 | Fedora
                 | CentOS
                 | RedHat
                 | Alpine
                 | AmazonLinux
                 -- rolling
                 | Gentoo
                 | Exherbo
                 -- not known
                 | UnknownLinux
                 -- ^ must exit
  deriving (LinuxDistro -> LinuxDistro -> Bool
(LinuxDistro -> LinuxDistro -> Bool)
-> (LinuxDistro -> LinuxDistro -> Bool) -> Eq LinuxDistro
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. LinuxDistro -> Rep LinuxDistro x)
-> (forall x. Rep LinuxDistro x -> LinuxDistro)
-> Generic LinuxDistro
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
Eq LinuxDistro
-> (LinuxDistro -> LinuxDistro -> Ordering)
-> (LinuxDistro -> LinuxDistro -> Bool)
-> (LinuxDistro -> LinuxDistro -> Bool)
-> (LinuxDistro -> LinuxDistro -> Bool)
-> (LinuxDistro -> LinuxDistro -> Bool)
-> (LinuxDistro -> LinuxDistro -> LinuxDistro)
-> (LinuxDistro -> LinuxDistro -> LinuxDistro)
-> Ord 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
$cp1Ord :: Eq LinuxDistro
Ord, Int -> LinuxDistro -> ShowS
[LinuxDistro] -> ShowS
LinuxDistro -> String
(Int -> LinuxDistro -> ShowS)
-> (LinuxDistro -> String)
-> ([LinuxDistro] -> ShowS)
-> Show LinuxDistro
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LinuxDistro] -> ShowS
$cshowList :: [LinuxDistro] -> ShowS
show :: LinuxDistro -> String
$cshow :: LinuxDistro -> String
showsPrec :: Int -> LinuxDistro -> ShowS
$cshowsPrec :: Int -> LinuxDistro -> ShowS
Show)

instance NFData LinuxDistro

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

instance Pretty LinuxDistro where
  pPrint :: LinuxDistro -> Doc
pPrint = String -> Doc
text (String -> Doc) -> (LinuxDistro -> String) -> LinuxDistro -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LinuxDistro -> String
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
  }
  deriving (DownloadInfo -> DownloadInfo -> Bool
(DownloadInfo -> DownloadInfo -> Bool)
-> (DownloadInfo -> DownloadInfo -> Bool) -> Eq DownloadInfo
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
Eq DownloadInfo
-> (DownloadInfo -> DownloadInfo -> Ordering)
-> (DownloadInfo -> DownloadInfo -> Bool)
-> (DownloadInfo -> DownloadInfo -> Bool)
-> (DownloadInfo -> DownloadInfo -> Bool)
-> (DownloadInfo -> DownloadInfo -> Bool)
-> (DownloadInfo -> DownloadInfo -> DownloadInfo)
-> (DownloadInfo -> DownloadInfo -> DownloadInfo)
-> Ord 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
$cp1Ord :: Eq DownloadInfo
Ord, (forall x. DownloadInfo -> Rep DownloadInfo x)
-> (forall x. Rep DownloadInfo x -> DownloadInfo)
-> Generic DownloadInfo
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 -> String
(Int -> DownloadInfo -> ShowS)
-> (DownloadInfo -> String)
-> ([DownloadInfo] -> ShowS)
-> Show DownloadInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DownloadInfo] -> ShowS
$cshowList :: [DownloadInfo] -> ShowS
show :: DownloadInfo -> String
$cshow :: DownloadInfo -> String
showsPrec :: Int -> DownloadInfo -> ShowS
$cshowsPrec :: Int -> DownloadInfo -> ShowS
Show)

instance NFData DownloadInfo



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


-- | 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
(TarDir -> TarDir -> Bool)
-> (TarDir -> TarDir -> Bool) -> Eq TarDir
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
Eq TarDir
-> (TarDir -> TarDir -> Ordering)
-> (TarDir -> TarDir -> Bool)
-> (TarDir -> TarDir -> Bool)
-> (TarDir -> TarDir -> Bool)
-> (TarDir -> TarDir -> Bool)
-> (TarDir -> TarDir -> TarDir)
-> (TarDir -> TarDir -> TarDir)
-> Ord 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
$cp1Ord :: Eq TarDir
Ord, (forall x. TarDir -> Rep TarDir x)
-> (forall x. Rep TarDir x -> TarDir) -> Generic TarDir
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 -> String
(Int -> TarDir -> ShowS)
-> (TarDir -> String) -> ([TarDir] -> ShowS) -> Show TarDir
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TarDir] -> ShowS
$cshowList :: [TarDir] -> ShowS
show :: TarDir -> String
$cshow :: TarDir -> String
showsPrec :: Int -> TarDir -> ShowS
$cshowsPrec :: Int -> TarDir -> ShowS
Show)

instance NFData TarDir

instance Pretty TarDir where
  pPrint :: TarDir -> Doc
pPrint (RealDir String
path) = String -> Doc
text String
path
  pPrint (RegexDir String
regex) = String -> Doc
text String
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. URLSource -> Rep URLSource x)
-> (forall x. Rep URLSource x -> URLSource) -> Generic URLSource
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 -> String
(Int -> URLSource -> ShowS)
-> (URLSource -> String)
-> ([URLSource] -> ShowS)
-> Show URLSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [URLSource] -> ShowS
$cshowList :: [URLSource] -> ShowS
show :: URLSource -> String
$cshow :: URLSource -> String
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 UserSettings = UserSettings
  { UserSettings -> Maybe Bool
uCache       :: Maybe Bool
  , UserSettings -> Maybe Integer
uMetaCache   :: Maybe Integer
  , 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
  }
  deriving (Int -> UserSettings -> ShowS
[UserSettings] -> ShowS
UserSettings -> String
(Int -> UserSettings -> ShowS)
-> (UserSettings -> String)
-> ([UserSettings] -> ShowS)
-> Show UserSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserSettings] -> ShowS
$cshowList :: [UserSettings] -> ShowS
show :: UserSettings -> String
$cshow :: UserSettings -> String
showsPrec :: Int -> UserSettings -> ShowS
$cshowsPrec :: Int -> UserSettings -> ShowS
Show, (forall x. UserSettings -> Rep UserSettings x)
-> (forall x. Rep UserSettings x -> UserSettings)
-> Generic UserSettings
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 Bool
-> Maybe Bool
-> Maybe KeepDirs
-> Maybe Downloader
-> Maybe UserKeyBindings
-> Maybe URLSource
-> Maybe Bool
-> Maybe GPGSetting
-> UserSettings
UserSettings Maybe Bool
forall a. Maybe a
Nothing Maybe Integer
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe KeepDirs
forall a. Maybe a
Nothing Maybe Downloader
forall a. Maybe a
Nothing Maybe UserKeyBindings
forall a. Maybe a
Nothing Maybe URLSource
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe GPGSetting
forall a. Maybe a
Nothing

fromSettings :: Settings -> Maybe KeyBindings -> UserSettings
fromSettings :: Settings -> Maybe KeyBindings -> UserSettings
fromSettings Settings{Bool
Integer
GPGSetting
Downloader
KeepDirs
URLSource
$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:metaCache:Settings :: Settings -> Integer
$sel:cache:Settings :: Settings -> Bool
noColor :: Bool
gpgSetting :: GPGSetting
noNetwork :: Bool
urlSource :: URLSource
verbose :: Bool
downloader :: Downloader
keepDirs :: KeepDirs
noVerify :: Bool
metaCache :: Integer
cache :: Bool
..} Maybe KeyBindings
Nothing =
  UserSettings :: Maybe Bool
-> Maybe Integer
-> Maybe Bool
-> Maybe Bool
-> Maybe KeepDirs
-> Maybe Downloader
-> Maybe UserKeyBindings
-> Maybe URLSource
-> Maybe Bool
-> Maybe GPGSetting
-> UserSettings
UserSettings {
      $sel:uCache:UserSettings :: Maybe Bool
uCache = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
cache
    , $sel:uMetaCache:UserSettings :: Maybe Integer
uMetaCache = Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
metaCache
    , $sel:uNoVerify:UserSettings :: Maybe Bool
uNoVerify = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
noVerify
    , $sel:uVerbose:UserSettings :: Maybe Bool
uVerbose = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
verbose
    , $sel:uKeepDirs:UserSettings :: Maybe KeepDirs
uKeepDirs = KeepDirs -> Maybe KeepDirs
forall a. a -> Maybe a
Just KeepDirs
keepDirs
    , $sel:uDownloader:UserSettings :: Maybe Downloader
uDownloader = Downloader -> Maybe Downloader
forall a. a -> Maybe a
Just Downloader
downloader
    , $sel:uNoNetwork:UserSettings :: Maybe Bool
uNoNetwork = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
noNetwork
    , $sel:uKeyBindings:UserSettings :: Maybe UserKeyBindings
uKeyBindings = Maybe UserKeyBindings
forall a. Maybe a
Nothing
    , $sel:uUrlSource:UserSettings :: Maybe URLSource
uUrlSource = URLSource -> Maybe URLSource
forall a. a -> Maybe a
Just URLSource
urlSource
    , $sel:uGPGSetting:UserSettings :: Maybe GPGSetting
uGPGSetting = GPGSetting -> Maybe GPGSetting
forall a. a -> Maybe a
Just GPGSetting
gpgSetting
  }
fromSettings Settings{Bool
Integer
GPGSetting
Downloader
KeepDirs
URLSource
noColor :: Bool
gpgSetting :: GPGSetting
noNetwork :: Bool
urlSource :: URLSource
verbose :: Bool
downloader :: Downloader
keepDirs :: KeepDirs
noVerify :: Bool
metaCache :: Integer
cache :: Bool
$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: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 :: Maybe Key
-> Maybe Key
-> Maybe Key
-> Maybe Key
-> Maybe Key
-> Maybe Key
-> Maybe Key
-> Maybe Key
-> Maybe Key
-> UserKeyBindings
UserKeyBindings
            { $sel:kUp:UserKeyBindings :: Maybe Key
kUp           = Key -> Maybe Key
forall a. a -> Maybe a
Just Key
bUp        
            , $sel:kDown:UserKeyBindings :: Maybe Key
kDown         = Key -> Maybe Key
forall a. a -> Maybe a
Just Key
bDown      
            , $sel:kQuit:UserKeyBindings :: Maybe Key
kQuit         = Key -> Maybe Key
forall a. a -> Maybe a
Just Key
bQuit      
            , $sel:kInstall:UserKeyBindings :: Maybe Key
kInstall      = Key -> Maybe Key
forall a. a -> Maybe a
Just Key
bInstall   
            , $sel:kUninstall:UserKeyBindings :: Maybe Key
kUninstall    = Key -> Maybe Key
forall a. a -> Maybe a
Just Key
bUninstall 
            , $sel:kSet:UserKeyBindings :: Maybe Key
kSet          = Key -> Maybe Key
forall a. a -> Maybe a
Just Key
bSet       
            , $sel:kChangelog:UserKeyBindings :: Maybe Key
kChangelog    = Key -> Maybe Key
forall a. a -> Maybe a
Just Key
bChangelog 
            , $sel:kShowAll:UserKeyBindings :: Maybe Key
kShowAll      = Key -> Maybe Key
forall a. a -> Maybe a
Just Key
bShowAllVersions
            , $sel:kShowAllTools:UserKeyBindings :: Maybe Key
kShowAllTools = Key -> Maybe Key
forall a. a -> Maybe a
Just Key
bShowAllTools
            }
  in UserSettings :: Maybe Bool
-> Maybe Integer
-> Maybe Bool
-> Maybe Bool
-> Maybe KeepDirs
-> Maybe Downloader
-> Maybe UserKeyBindings
-> Maybe URLSource
-> Maybe Bool
-> Maybe GPGSetting
-> UserSettings
UserSettings {
      $sel:uCache:UserSettings :: Maybe Bool
uCache = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
cache
    , $sel:uMetaCache:UserSettings :: Maybe Integer
uMetaCache = Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
metaCache
    , $sel:uNoVerify:UserSettings :: Maybe Bool
uNoVerify = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
noVerify
    , $sel:uVerbose:UserSettings :: Maybe Bool
uVerbose = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
verbose
    , $sel:uKeepDirs:UserSettings :: Maybe KeepDirs
uKeepDirs = KeepDirs -> Maybe KeepDirs
forall a. a -> Maybe a
Just KeepDirs
keepDirs
    , $sel:uDownloader:UserSettings :: Maybe Downloader
uDownloader = Downloader -> Maybe Downloader
forall a. a -> Maybe a
Just Downloader
downloader
    , $sel:uNoNetwork:UserSettings :: Maybe Bool
uNoNetwork = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
noNetwork
    , $sel:uKeyBindings:UserSettings :: Maybe UserKeyBindings
uKeyBindings = UserKeyBindings -> Maybe UserKeyBindings
forall a. a -> Maybe a
Just UserKeyBindings
ukb
    , $sel:uUrlSource:UserSettings :: Maybe URLSource
uUrlSource = URLSource -> Maybe URLSource
forall a. a -> Maybe a
Just URLSource
urlSource
    , $sel:uGPGSetting:UserSettings :: Maybe GPGSetting
uGPGSetting = GPGSetting -> Maybe GPGSetting
forall a. a -> Maybe a
Just GPGSetting
gpgSetting
  }

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 -> String
(Int -> UserKeyBindings -> ShowS)
-> (UserKeyBindings -> String)
-> ([UserKeyBindings] -> ShowS)
-> Show UserKeyBindings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserKeyBindings] -> ShowS
$cshowList :: [UserKeyBindings] -> ShowS
show :: UserKeyBindings -> String
$cshow :: UserKeyBindings -> String
showsPrec :: Int -> UserKeyBindings -> ShowS
$cshowsPrec :: Int -> UserKeyBindings -> ShowS
Show, (forall x. UserKeyBindings -> Rep UserKeyBindings x)
-> (forall x. Rep UserKeyBindings x -> UserKeyBindings)
-> Generic UserKeyBindings
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 -> String
(Int -> KeyBindings -> ShowS)
-> (KeyBindings -> String)
-> ([KeyBindings] -> ShowS)
-> Show KeyBindings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyBindings] -> ShowS
$cshowList :: [KeyBindings] -> ShowS
show :: KeyBindings -> String
$cshow :: KeyBindings -> String
showsPrec :: Int -> KeyBindings -> ShowS
$cshowsPrec :: Int -> KeyBindings -> ShowS
Show, (forall x. KeyBindings -> Rep KeyBindings x)
-> (forall x. Rep KeyBindings x -> KeyBindings)
-> Generic KeyBindings
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
instance NFData Key

defaultKeyBindings :: KeyBindings
defaultKeyBindings :: KeyBindings
defaultKeyBindings = KeyBindings :: Key
-> Key
-> Key
-> Key
-> Key
-> Key
-> Key
-> Key
-> Key
-> KeyBindings
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 -> String
(Int -> AppState -> ShowS)
-> (AppState -> String) -> ([AppState] -> ShowS) -> Show AppState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AppState] -> ShowS
$cshowList :: [AppState] -> ShowS
show :: AppState -> String
$cshow :: AppState -> String
showsPrec :: Int -> AppState -> ShowS
$cshowsPrec :: Int -> AppState -> ShowS
Show, (forall x. AppState -> Rep AppState x)
-> (forall x. Rep AppState x -> AppState) -> Generic AppState
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

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 -> String
(Int -> LeanAppState -> ShowS)
-> (LeanAppState -> String)
-> ([LeanAppState] -> ShowS)
-> Show LeanAppState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LeanAppState] -> ShowS
$cshowList :: [LeanAppState] -> ShowS
show :: LeanAppState -> String
$cshow :: LeanAppState -> String
showsPrec :: Int -> LeanAppState -> ShowS
$cshowsPrec :: Int -> LeanAppState -> ShowS
Show, (forall x. LeanAppState -> Rep LeanAppState x)
-> (forall x. Rep LeanAppState x -> LeanAppState)
-> Generic LeanAppState
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 -> 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
  }
  deriving (Int -> Settings -> ShowS
[Settings] -> ShowS
Settings -> String
(Int -> Settings -> ShowS)
-> (Settings -> String) -> ([Settings] -> ShowS) -> Show Settings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Settings] -> ShowS
$cshowList :: [Settings] -> ShowS
show :: Settings -> String
$cshow :: Settings -> String
showsPrec :: Int -> Settings -> ShowS
$cshowsPrec :: Int -> Settings -> ShowS
Show, (forall x. Settings -> Rep Settings x)
-> (forall x. Rep Settings x -> Settings) -> Generic Settings
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
-> Bool
-> KeepDirs
-> Downloader
-> Bool
-> URLSource
-> Bool
-> GPGSetting
-> Bool
-> Settings
Settings Bool
False Integer
defaultMetaCache Bool
False KeepDirs
Never Downloader
Curl Bool
False URLSource
GHCupURL Bool
False GPGSetting
GPGNone Bool
False

instance NFData Settings

data Dirs = Dirs
  { Dirs -> String
baseDir  :: FilePath
  , Dirs -> String
binDir   :: FilePath
  , Dirs -> String
cacheDir :: FilePath
  , Dirs -> String
logsDir  :: FilePath
  , Dirs -> String
confDir  :: FilePath
  , Dirs -> String
recycleDir :: FilePath -- mainly used on windows
  }
  deriving (Int -> Dirs -> ShowS
[Dirs] -> ShowS
Dirs -> String
(Int -> Dirs -> ShowS)
-> (Dirs -> String) -> ([Dirs] -> ShowS) -> Show Dirs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Dirs] -> ShowS
$cshowList :: [Dirs] -> ShowS
show :: Dirs -> String
$cshow :: Dirs -> String
showsPrec :: Int -> Dirs -> ShowS
$cshowsPrec :: Int -> Dirs -> ShowS
Show, (forall x. Dirs -> Rep Dirs x)
-> (forall x. Rep Dirs x -> Dirs) -> Generic Dirs
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
(KeepDirs -> KeepDirs -> Bool)
-> (KeepDirs -> KeepDirs -> Bool) -> Eq KeepDirs
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 -> String
(Int -> KeepDirs -> ShowS)
-> (KeepDirs -> String) -> ([KeepDirs] -> ShowS) -> Show KeepDirs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeepDirs] -> ShowS
$cshowList :: [KeepDirs] -> ShowS
show :: KeepDirs -> String
$cshow :: KeepDirs -> String
showsPrec :: Int -> KeepDirs -> ShowS
$cshowsPrec :: Int -> KeepDirs -> ShowS
Show, Eq KeepDirs
Eq KeepDirs
-> (KeepDirs -> KeepDirs -> Ordering)
-> (KeepDirs -> KeepDirs -> Bool)
-> (KeepDirs -> KeepDirs -> Bool)
-> (KeepDirs -> KeepDirs -> Bool)
-> (KeepDirs -> KeepDirs -> Bool)
-> (KeepDirs -> KeepDirs -> KeepDirs)
-> (KeepDirs -> KeepDirs -> KeepDirs)
-> Ord 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
$cp1Ord :: Eq KeepDirs
Ord, (forall x. KeepDirs -> Rep KeepDirs x)
-> (forall x. Rep KeepDirs x -> KeepDirs) -> Generic KeepDirs
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
(Downloader -> Downloader -> Bool)
-> (Downloader -> Downloader -> Bool) -> Eq Downloader
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 -> String
(Int -> Downloader -> ShowS)
-> (Downloader -> String)
-> ([Downloader] -> ShowS)
-> Show Downloader
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Downloader] -> ShowS
$cshowList :: [Downloader] -> ShowS
show :: Downloader -> String
$cshow :: Downloader -> String
showsPrec :: Int -> Downloader -> ShowS
$cshowsPrec :: Int -> Downloader -> ShowS
Show, Eq Downloader
Eq Downloader
-> (Downloader -> Downloader -> Ordering)
-> (Downloader -> Downloader -> Bool)
-> (Downloader -> Downloader -> Bool)
-> (Downloader -> Downloader -> Bool)
-> (Downloader -> Downloader -> Bool)
-> (Downloader -> Downloader -> Downloader)
-> (Downloader -> Downloader -> Downloader)
-> Ord 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
$cp1Ord :: Eq Downloader
Ord, (forall x. Downloader -> Rep Downloader x)
-> (forall x. Rep Downloader x -> Downloader) -> Generic Downloader
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
(GPGSetting -> GPGSetting -> Bool)
-> (GPGSetting -> GPGSetting -> Bool) -> Eq GPGSetting
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 -> String
(Int -> GPGSetting -> ShowS)
-> (GPGSetting -> String)
-> ([GPGSetting] -> ShowS)
-> Show GPGSetting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GPGSetting] -> ShowS
$cshowList :: [GPGSetting] -> ShowS
show :: GPGSetting -> String
$cshow :: GPGSetting -> String
showsPrec :: Int -> GPGSetting -> ShowS
$cshowsPrec :: Int -> GPGSetting -> ShowS
Show, Eq GPGSetting
Eq GPGSetting
-> (GPGSetting -> GPGSetting -> Ordering)
-> (GPGSetting -> GPGSetting -> Bool)
-> (GPGSetting -> GPGSetting -> Bool)
-> (GPGSetting -> GPGSetting -> Bool)
-> (GPGSetting -> GPGSetting -> Bool)
-> (GPGSetting -> GPGSetting -> GPGSetting)
-> (GPGSetting -> GPGSetting -> GPGSetting)
-> Ord 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
$cp1Ord :: Eq GPGSetting
Ord, (forall x. GPGSetting -> Rep GPGSetting x)
-> (forall x. Rep GPGSetting x -> GPGSetting) -> Generic GPGSetting
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 -> String
diBaseDir  :: FilePath
  , DebugInfo -> String
diBinDir   :: FilePath
  , DebugInfo -> String
diGHCDir   :: FilePath
  , DebugInfo -> String
diCacheDir :: FilePath
  , DebugInfo -> Architecture
diArch     :: Architecture
  , DebugInfo -> PlatformResult
diPlatform :: PlatformResult
  }
  deriving Int -> DebugInfo -> ShowS
[DebugInfo] -> ShowS
DebugInfo -> String
(Int -> DebugInfo -> ShowS)
-> (DebugInfo -> String)
-> ([DebugInfo] -> ShowS)
-> Show DebugInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DebugInfo] -> ShowS
$cshowList :: [DebugInfo] -> ShowS
show :: DebugInfo -> String
$cshow :: DebugInfo -> String
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
(SetGHC -> SetGHC -> Bool)
-> (SetGHC -> SetGHC -> Bool) -> Eq SetGHC
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 -> String
(Int -> SetGHC -> ShowS)
-> (SetGHC -> String) -> ([SetGHC] -> ShowS) -> Show SetGHC
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetGHC] -> ShowS
$cshowList :: [SetGHC] -> ShowS
show :: SetGHC -> String
$cshow :: SetGHC -> String
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
(SetHLS -> SetHLS -> Bool)
-> (SetHLS -> SetHLS -> Bool) -> Eq SetHLS
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 -> String
(Int -> SetHLS -> ShowS)
-> (SetHLS -> String) -> ([SetHLS] -> ShowS) -> Show SetHLS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetHLS] -> ShowS
$cshowList :: [SetHLS] -> ShowS
show :: SetHLS -> String
$cshow :: SetHLS -> String
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
(PlatformResult -> PlatformResult -> Bool)
-> (PlatformResult -> PlatformResult -> Bool) -> Eq PlatformResult
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 -> String
(Int -> PlatformResult -> ShowS)
-> (PlatformResult -> String)
-> ([PlatformResult] -> ShowS)
-> Show PlatformResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PlatformResult] -> ShowS
$cshowList :: [PlatformResult] -> ShowS
show :: PlatformResult -> String
$cshow :: PlatformResult -> String
showsPrec :: Int -> PlatformResult -> ShowS
$cshowsPrec :: Int -> PlatformResult -> ShowS
Show, (forall x. PlatformResult -> Rep PlatformResult x)
-> (forall x. Rep PlatformResult x -> PlatformResult)
-> Generic PlatformResult
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 -> String
platResToString PlatformResult { $sel:_platform:PlatformResult :: PlatformResult -> Platform
_platform = Platform
plat, $sel:_distroVersion:PlatformResult :: PlatformResult -> Maybe Versioning
_distroVersion = Just Versioning
v' }
  = Platform -> String
forall a. Show a => a -> String
show Platform
plat String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
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 }
  = Platform -> String
forall a. Show a => a -> String
show Platform
plat

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

data PlatformRequest = PlatformRequest
  { PlatformRequest -> Architecture
_rArch     :: Architecture
  , PlatformRequest -> Platform
_rPlatform :: Platform
  , PlatformRequest -> Maybe Versioning
_rVersion  :: Maybe Versioning
  }
  deriving (PlatformRequest -> PlatformRequest -> Bool
(PlatformRequest -> PlatformRequest -> Bool)
-> (PlatformRequest -> PlatformRequest -> Bool)
-> Eq PlatformRequest
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 -> String
(Int -> PlatformRequest -> ShowS)
-> (PlatformRequest -> String)
-> ([PlatformRequest] -> ShowS)
-> Show PlatformRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PlatformRequest] -> ShowS
$cshowList :: [PlatformRequest] -> ShowS
show :: PlatformRequest -> String
$cshow :: PlatformRequest -> String
showsPrec :: Int -> PlatformRequest -> ShowS
$cshowsPrec :: Int -> PlatformRequest -> ShowS
Show, (forall x. PlatformRequest -> Rep PlatformRequest x)
-> (forall x. Rep PlatformRequest x -> PlatformRequest)
-> Generic PlatformRequest
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 -> String
pfReqToString (PlatformRequest Architecture
arch Platform
plat Maybe Versioning
ver) =
  Architecture -> String
archToString Architecture
arch String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Platform -> String
platformToString Platform
plat String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
pver
 where
  pver :: String
pver = case Maybe Versioning
ver of
           Just Versioning
v' -> String
"-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack (Versioning -> Text
prettyV Versioning
v')
           Maybe Versioning
Nothing -> String
""

instance Pretty PlatformRequest where
  pPrint :: PlatformRequest -> Doc
pPrint = String -> Doc
text (String -> Doc)
-> (PlatformRequest -> String) -> PlatformRequest -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlatformRequest -> String
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
Eq GHCTargetVersion
-> (GHCTargetVersion -> GHCTargetVersion -> Ordering)
-> (GHCTargetVersion -> GHCTargetVersion -> Bool)
-> (GHCTargetVersion -> GHCTargetVersion -> Bool)
-> (GHCTargetVersion -> GHCTargetVersion -> Bool)
-> (GHCTargetVersion -> GHCTargetVersion -> Bool)
-> (GHCTargetVersion -> GHCTargetVersion -> GHCTargetVersion)
-> (GHCTargetVersion -> GHCTargetVersion -> GHCTargetVersion)
-> Ord 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
$cp1Ord :: Eq GHCTargetVersion
Ord, GHCTargetVersion -> GHCTargetVersion -> Bool
(GHCTargetVersion -> GHCTargetVersion -> Bool)
-> (GHCTargetVersion -> GHCTargetVersion -> Bool)
-> Eq GHCTargetVersion
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 -> String
(Int -> GHCTargetVersion -> ShowS)
-> (GHCTargetVersion -> String)
-> ([GHCTargetVersion] -> ShowS)
-> Show GHCTargetVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GHCTargetVersion] -> ShowS
$cshowList :: [GHCTargetVersion] -> ShowS
show :: GHCTargetVersion -> String
$cshow :: GHCTargetVersion -> String
showsPrec :: Int -> GHCTargetVersion -> ShowS
$cshowsPrec :: Int -> GHCTargetVersion -> ShowS
Show)

data GitBranch = GitBranch
  { GitBranch -> String
ref  :: String
  , GitBranch -> Maybe String
repo :: Maybe String
  }
  deriving (Eq GitBranch
Eq GitBranch
-> (GitBranch -> GitBranch -> Ordering)
-> (GitBranch -> GitBranch -> Bool)
-> (GitBranch -> GitBranch -> Bool)
-> (GitBranch -> GitBranch -> Bool)
-> (GitBranch -> GitBranch -> Bool)
-> (GitBranch -> GitBranch -> GitBranch)
-> (GitBranch -> GitBranch -> GitBranch)
-> Ord 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
$cp1Ord :: Eq GitBranch
Ord, GitBranch -> GitBranch -> Bool
(GitBranch -> GitBranch -> Bool)
-> (GitBranch -> GitBranch -> Bool) -> Eq GitBranch
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 -> String
(Int -> GitBranch -> ShowS)
-> (GitBranch -> String)
-> ([GitBranch] -> ShowS)
-> Show GitBranch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GitBranch] -> ShowS
$cshowList :: [GitBranch] -> ShowS
show :: GitBranch -> String
$cshow :: GitBranch -> String
showsPrec :: Int -> GitBranch -> ShowS
$cshowsPrec :: Int -> GitBranch -> ShowS
Show)

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

tVerToText :: GHCTargetVersion -> Text
tVerToText :: GHCTargetVersion -> Text
tVerToText (GHCTargetVersion (Just Text
t) Version
v') = Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-" Text -> Text -> 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 = String -> Doc
text (String -> Doc)
-> (GHCTargetVersion -> String) -> GHCTargetVersion -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack (Text -> String)
-> (GHCTargetVersion -> Text) -> GHCTargetVersion -> String
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
(VersionCmp -> VersionCmp -> Bool)
-> (VersionCmp -> VersionCmp -> Bool) -> Eq VersionCmp
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. VersionCmp -> Rep VersionCmp x)
-> (forall x. Rep VersionCmp x -> VersionCmp) -> Generic VersionCmp
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
Eq VersionCmp
-> (VersionCmp -> VersionCmp -> Ordering)
-> (VersionCmp -> VersionCmp -> Bool)
-> (VersionCmp -> VersionCmp -> Bool)
-> (VersionCmp -> VersionCmp -> Bool)
-> (VersionCmp -> VersionCmp -> Bool)
-> (VersionCmp -> VersionCmp -> VersionCmp)
-> (VersionCmp -> VersionCmp -> VersionCmp)
-> Ord 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
$cp1Ord :: Eq VersionCmp
Ord, Int -> VersionCmp -> ShowS
[VersionCmp] -> ShowS
VersionCmp -> String
(Int -> VersionCmp -> ShowS)
-> (VersionCmp -> String)
-> ([VersionCmp] -> ShowS)
-> Show VersionCmp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VersionCmp] -> ShowS
$cshowList :: [VersionCmp] -> ShowS
show :: VersionCmp -> String
$cshow :: VersionCmp -> String
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
(VersionRange -> VersionRange -> Bool)
-> (VersionRange -> VersionRange -> Bool) -> Eq VersionRange
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. VersionRange -> Rep VersionRange x)
-> (forall x. Rep VersionRange x -> VersionRange)
-> Generic VersionRange
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
Eq VersionRange
-> (VersionRange -> VersionRange -> Ordering)
-> (VersionRange -> VersionRange -> Bool)
-> (VersionRange -> VersionRange -> Bool)
-> (VersionRange -> VersionRange -> Bool)
-> (VersionRange -> VersionRange -> Bool)
-> (VersionRange -> VersionRange -> VersionRange)
-> (VersionRange -> VersionRange -> VersionRange)
-> Ord 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
$cp1Ord :: Eq VersionRange
Ord, Int -> VersionRange -> ShowS
[VersionRange] -> ShowS
VersionRange -> String
(Int -> VersionRange -> ShowS)
-> (VersionRange -> String)
-> ([VersionRange] -> ShowS)
-> Show VersionRange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VersionRange] -> ShowS
$cshowList :: [VersionRange] -> ShowS
show :: VersionRange -> String
$cshow :: VersionRange -> String
showsPrec :: Int -> VersionRange -> ShowS
$cshowsPrec :: Int -> VersionRange -> ShowS
Show)

instance NFData VersionRange

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

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

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

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


data LogLevel = Warn
              | Info
              | Debug
              | Error
  deriving (LogLevel -> LogLevel -> Bool
(LogLevel -> LogLevel -> Bool)
-> (LogLevel -> LogLevel -> Bool) -> Eq LogLevel
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
Eq LogLevel
-> (LogLevel -> LogLevel -> Ordering)
-> (LogLevel -> LogLevel -> Bool)
-> (LogLevel -> LogLevel -> Bool)
-> (LogLevel -> LogLevel -> Bool)
-> (LogLevel -> LogLevel -> Bool)
-> (LogLevel -> LogLevel -> LogLevel)
-> (LogLevel -> LogLevel -> LogLevel)
-> Ord 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
$cp1Ord :: Eq LogLevel
Ord, Int -> LogLevel -> ShowS
[LogLevel] -> ShowS
LogLevel -> String
(Int -> LogLevel -> ShowS)
-> (LogLevel -> String) -> ([LogLevel] -> ShowS) -> Show LogLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogLevel] -> ShowS
$cshowList :: [LogLevel] -> ShowS
show :: LogLevel -> String
$cshow :: LogLevel -> String
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 -> String
(Int -> LoggerConfig -> ShowS)
-> (LoggerConfig -> String)
-> ([LoggerConfig] -> ShowS)
-> Show LoggerConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LoggerConfig] -> ShowS
$cshowList :: [LoggerConfig] -> ShowS
show :: LoggerConfig -> String
$cshow :: LoggerConfig -> String
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) = (Bool, Bool) -> ()
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 -> String
(Int -> ProcessError -> ShowS)
-> (ProcessError -> String)
-> ([ProcessError] -> ShowS)
-> Show ProcessError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProcessError] -> ShowS
$cshowList :: [ProcessError] -> ShowS
show :: ProcessError -> String
$cshow :: ProcessError -> String
showsPrec :: Int -> ProcessError -> ShowS
$cshowsPrec :: Int -> ProcessError -> ShowS
Show

instance Pretty ProcessError where
  pPrint :: ProcessError -> Doc
pPrint (NonZeroExit Int
e String
exe [String]
args) =
    String -> Doc
text String
"Process" Doc -> Doc -> Doc
<+> String -> Doc
forall a. Pretty a => a -> Doc
pPrint String
exe Doc -> Doc -> Doc
<+> String -> Doc
text String
"with arguments" Doc -> Doc -> Doc
<+> [String] -> Doc
forall a. Pretty a => a -> Doc
pPrint [String]
args Doc -> Doc -> Doc
<+> String -> Doc
text String
"failed with exit code" Doc -> Doc -> Doc
<+> String -> Doc
text (Int -> String
forall a. Show a => a -> String
show Int
e String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
".")
  pPrint (PTerminated String
exe [String]
args) =
    String -> Doc
text String
"Process" Doc -> Doc -> Doc
<+> String -> Doc
forall a. Pretty a => a -> Doc
pPrint String
exe Doc -> Doc -> Doc
<+> String -> Doc
text String
"with arguments" Doc -> Doc -> Doc
<+> [String] -> Doc
forall a. Pretty a => a -> Doc
pPrint [String]
args Doc -> Doc -> Doc
<+> String -> Doc
text String
"terminated."
  pPrint (PStopped String
exe [String]
args) =
    String -> Doc
text String
"Process" Doc -> Doc -> Doc
<+> String -> Doc
forall a. Pretty a => a -> Doc
pPrint String
exe Doc -> Doc -> Doc
<+> String -> Doc
text String
"with arguments" Doc -> Doc -> Doc
<+> [String] -> Doc
forall a. Pretty a => a -> Doc
pPrint [String]
args Doc -> Doc -> Doc
<+> String -> Doc
text String
"stopped."
  pPrint (NoSuchPid String
exe [String]
args) =
    String -> Doc
text String
"Could not find PID for process running " Doc -> Doc -> Doc
<+> String -> Doc
forall a. Pretty a => a -> Doc
pPrint String
exe Doc -> Doc -> Doc
<+> String -> Doc
text String
" with arguments " Doc -> Doc -> Doc
<+> String -> Doc
text ([String] -> String
forall a. Show a => a -> String
show [String]
args) Doc -> Doc -> Doc
<+> String -> Doc
text String
"."
data CapturedProcess = CapturedProcess
  { CapturedProcess -> ExitCode
_exitCode :: ExitCode
  , CapturedProcess -> ByteString
_stdOut   :: BL.ByteString
  , CapturedProcess -> ByteString
_stdErr   :: BL.ByteString
  }
  deriving (CapturedProcess -> CapturedProcess -> Bool
(CapturedProcess -> CapturedProcess -> Bool)
-> (CapturedProcess -> CapturedProcess -> Bool)
-> Eq CapturedProcess
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 -> String
(Int -> CapturedProcess -> ShowS)
-> (CapturedProcess -> String)
-> ([CapturedProcess] -> ShowS)
-> Show CapturedProcess
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CapturedProcess] -> ShowS
$cshowList :: [CapturedProcess] -> ShowS
show :: CapturedProcess -> String
$cshow :: CapturedProcess -> String
showsPrec :: Int -> CapturedProcess -> ShowS
$cshowsPrec :: Int -> CapturedProcess -> ShowS
Show)

makeLenses ''CapturedProcess


data InstallDir = IsolateDir FilePath
                | GHCupInternal
  deriving (InstallDir -> InstallDir -> Bool
(InstallDir -> InstallDir -> Bool)
-> (InstallDir -> InstallDir -> Bool) -> Eq InstallDir
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 -> String
(Int -> InstallDir -> ShowS)
-> (InstallDir -> String)
-> ([InstallDir] -> ShowS)
-> Show InstallDir
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InstallDir] -> ShowS
$cshowList :: [InstallDir] -> ShowS
show :: InstallDir -> String
$cshow :: InstallDir -> String
showsPrec :: Int -> InstallDir -> ShowS
$cshowsPrec :: Int -> InstallDir -> ShowS
Show)

data InstallDirResolved = IsolateDirResolved FilePath
                        | GHCupDir FilePath
  deriving (InstallDirResolved -> InstallDirResolved -> Bool
(InstallDirResolved -> InstallDirResolved -> Bool)
-> (InstallDirResolved -> InstallDirResolved -> Bool)
-> Eq InstallDirResolved
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 -> String
(Int -> InstallDirResolved -> ShowS)
-> (InstallDirResolved -> String)
-> ([InstallDirResolved] -> ShowS)
-> Show InstallDirResolved
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InstallDirResolved] -> ShowS
$cshowList :: [InstallDirResolved] -> ShowS
show :: InstallDirResolved -> String
$cshow :: InstallDirResolved -> String
showsPrec :: Int -> InstallDirResolved -> ShowS
$cshowsPrec :: Int -> InstallDirResolved -> ShowS
Show)

fromInstallDir :: InstallDirResolved -> FilePath
fromInstallDir :: InstallDirResolved -> String
fromInstallDir (IsolateDirResolved String
fp) = String
fp
fromInstallDir (GHCupDir String
fp) = String
fp