{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
module Distribution.System (
OS(..),
buildOS,
Arch(..),
buildArch,
Platform(..),
buildPlatform,
platformFromTriple,
knownOSs,
knownArches,
ClassificationStrictness (..),
classifyOS,
classifyArch,
) where
import Prelude ()
import Distribution.Compat.Prelude
import Control.Applicative (liftA2)
import qualified System.Info (os, arch)
import Distribution.Utils.Generic (lowercase)
import Distribution.Parsec
import Distribution.Pretty
import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as Disp
data ClassificationStrictness = Permissive | Compat | Strict
data OS = Linux | Windows | OSX
| FreeBSD | OpenBSD | NetBSD
| DragonFly
| Solaris | AIX | HPUX | IRIX
| HaLVM
| Hurd
| IOS | Android
| Ghcjs
| OtherOS String
deriving (OS -> OS -> Bool
(OS -> OS -> Bool) -> (OS -> OS -> Bool) -> Eq OS
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OS -> OS -> Bool
$c/= :: OS -> OS -> Bool
== :: OS -> OS -> Bool
$c== :: OS -> OS -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
Eq, (forall x. OS -> Rep OS x)
-> (forall x. Rep OS x -> OS) -> Generic OS
forall x. Rep OS x -> OS
forall x. OS -> Rep OS x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OS x -> OS
$cfrom :: forall x. OS -> Rep OS x
Generic, Eq OS
Eq OS
-> (OS -> OS -> Ordering)
-> (OS -> OS -> Bool)
-> (OS -> OS -> Bool)
-> (OS -> OS -> Bool)
-> (OS -> OS -> Bool)
-> (OS -> OS -> OS)
-> (OS -> OS -> OS)
-> Ord OS
OS -> OS -> Bool
OS -> OS -> Ordering
OS -> OS -> OS
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 :: OS -> OS -> OS
$cmin :: OS -> OS -> OS
max :: OS -> OS -> OS
$cmax :: OS -> OS -> OS
>= :: OS -> OS -> Bool
$c>= :: OS -> OS -> Bool
> :: OS -> OS -> Bool
$c> :: OS -> OS -> Bool
<= :: OS -> OS -> Bool
$c<= :: OS -> OS -> Bool
< :: OS -> OS -> Bool
$c< :: OS -> OS -> Bool
compare :: OS -> OS -> Ordering
$ccompare :: OS -> OS -> Ordering
External instance of the constraint type Ord Char
External instance of the constraint type Ord Char
External instance of the constraint type forall a. Ord a => Ord [a]
Instance of class: Eq of the constraint type Eq OS
Instance of class: Eq of the constraint type Eq OS
Ord, Int -> OS -> ShowS
[OS] -> ShowS
OS -> String
(Int -> OS -> ShowS)
-> (OS -> String) -> ([OS] -> ShowS) -> Show OS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OS] -> ShowS
$cshowList :: [OS] -> ShowS
show :: OS -> String
$cshow :: OS -> String
showsPrec :: Int -> OS -> ShowS
$cshowsPrec :: Int -> OS -> ShowS
External instance of the constraint type Show Char
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Ord Int
Show, ReadPrec [OS]
ReadPrec OS
Int -> ReadS OS
ReadS [OS]
(Int -> ReadS OS)
-> ReadS [OS] -> ReadPrec OS -> ReadPrec [OS] -> Read OS
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OS]
$creadListPrec :: ReadPrec [OS]
readPrec :: ReadPrec OS
$creadPrec :: ReadPrec OS
readList :: ReadS [OS]
$creadList :: ReadS [OS]
readsPrec :: Int -> ReadS OS
$creadsPrec :: Int -> ReadS OS
External instance of the constraint type Read Char
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read OS
Read, Typeable, Typeable OS
DataType
Constr
Typeable OS
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OS -> c OS)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OS)
-> (OS -> Constr)
-> (OS -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OS))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OS))
-> ((forall b. Data b => b -> b) -> OS -> OS)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r)
-> (forall u. (forall d. Data d => d -> u) -> OS -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> OS -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OS -> m OS)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OS -> m OS)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OS -> m OS)
-> Data OS
OS -> DataType
OS -> Constr
(forall b. Data b => b -> b) -> OS -> OS
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OS -> c OS
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OS
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> OS -> u
forall u. (forall d. Data d => d -> u) -> OS -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OS -> m OS
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OS -> m OS
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OS
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OS -> c OS
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OS)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OS)
$cOtherOS :: Constr
$cGhcjs :: Constr
$cAndroid :: Constr
$cIOS :: Constr
$cHurd :: Constr
$cHaLVM :: Constr
$cIRIX :: Constr
$cHPUX :: Constr
$cAIX :: Constr
$cSolaris :: Constr
$cDragonFly :: Constr
$cNetBSD :: Constr
$cOpenBSD :: Constr
$cFreeBSD :: Constr
$cOSX :: Constr
$cWindows :: Constr
$cLinux :: Constr
$tOS :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> OS -> m OS
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OS -> m OS
gmapMp :: (forall d. Data d => d -> m d) -> OS -> m OS
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OS -> m OS
gmapM :: (forall d. Data d => d -> m d) -> OS -> m OS
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OS -> m OS
gmapQi :: Int -> (forall d. Data d => d -> u) -> OS -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OS -> u
gmapQ :: (forall d. Data d => d -> u) -> OS -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OS -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r
gmapT :: (forall b. Data b => b -> b) -> OS -> OS
$cgmapT :: (forall b. Data b => b -> b) -> OS -> OS
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OS)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OS)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c OS)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OS)
dataTypeOf :: OS -> DataType
$cdataTypeOf :: OS -> DataType
toConstr :: OS -> Constr
$ctoConstr :: OS -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OS
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OS
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OS -> c OS
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OS -> c OS
External instance of the constraint type Data Char
External instance of the constraint type Data Char
External instance of the constraint type Data Char
External instance of the constraint type forall a. Data a => Data [a]
Data)
instance Binary OS
instance Structured OS
instance NFData OS where rnf :: OS -> ()
rnf = OS -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
Instance of class: Generic of the constraint type Generic OS
genericRnf
knownOSs :: [OS]
knownOSs :: [OS]
knownOSs = [OS
Linux, OS
Windows, OS
OSX
,OS
FreeBSD, OS
OpenBSD, OS
NetBSD, OS
DragonFly
,OS
Solaris, OS
AIX, OS
HPUX, OS
IRIX
,OS
HaLVM
,OS
Hurd
,OS
IOS, OS
Android
,OS
Ghcjs]
osAliases :: ClassificationStrictness -> OS -> [String]
osAliases :: ClassificationStrictness -> OS -> [String]
osAliases ClassificationStrictness
Permissive OS
Windows = [String
"mingw32", String
"win32", String
"cygwin32"]
osAliases ClassificationStrictness
Compat OS
Windows = [String
"mingw32", String
"win32"]
osAliases ClassificationStrictness
_ OS
OSX = [String
"darwin"]
osAliases ClassificationStrictness
_ OS
Hurd = [String
"gnu"]
osAliases ClassificationStrictness
Permissive OS
FreeBSD = [String
"kfreebsdgnu"]
osAliases ClassificationStrictness
Compat OS
FreeBSD = [String
"kfreebsdgnu"]
osAliases ClassificationStrictness
Permissive OS
Solaris = [String
"solaris2"]
osAliases ClassificationStrictness
Compat OS
Solaris = [String
"solaris2"]
osAliases ClassificationStrictness
_ OS
Android = [String
"linux-android"]
osAliases ClassificationStrictness
_ OS
_ = []
instance Pretty OS where
pretty :: OS -> Doc
pretty (OtherOS String
name) = String -> Doc
Disp.text String
name
pretty OS
other = String -> Doc
Disp.text (ShowS
lowercase (OS -> String
forall a. Show a => a -> String
Instance of class: Show of the constraint type Show OS
show OS
other))
instance Parsec OS where
parsec :: m OS
parsec = ClassificationStrictness -> String -> OS
classifyOS ClassificationStrictness
Compat (String -> OS) -> m String -> m OS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
<$> m String
forall (m :: * -> *). CabalParsing m => m String
Evidence bound by a type signature of the constraint type CabalParsing m
parsecIdent
classifyOS :: ClassificationStrictness -> String -> OS
classifyOS :: ClassificationStrictness -> String -> OS
classifyOS ClassificationStrictness
strictness String
s =
OS -> Maybe OS -> OS
forall a. a -> Maybe a -> a
fromMaybe (String -> OS
OtherOS String
s) (Maybe OS -> OS) -> Maybe OS -> OS
forall a b. (a -> b) -> a -> b
$ String -> [(String, OS)] -> Maybe OS
forall a b. Eq a => a -> [(a, b)] -> Maybe b
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
lookup (ShowS
lowercase String
s) [(String, OS)]
osMap
where
osMap :: [(String, OS)]
osMap = [ (String
name, OS
os)
| OS
os <- [OS]
knownOSs
, String
name <- OS -> String
forall a. Pretty a => a -> String
Instance of class: Pretty of the constraint type Pretty OS
prettyShow OS
os String -> [String] -> [String]
forall a. a -> [a] -> [a]
: ClassificationStrictness -> OS -> [String]
osAliases ClassificationStrictness
strictness OS
os ]
buildOS :: OS
buildOS :: OS
buildOS = ClassificationStrictness -> String -> OS
classifyOS ClassificationStrictness
Permissive String
System.Info.os
data Arch = I386 | X86_64 | PPC | PPC64 | Sparc
| Arm | AArch64 | Mips | SH
| IA64 | S390
| Alpha | Hppa | Rs6000
| M68k | Vax
| JavaScript
| OtherArch String
deriving (Arch -> Arch -> Bool
(Arch -> Arch -> Bool) -> (Arch -> Arch -> Bool) -> Eq Arch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Arch -> Arch -> Bool
$c/= :: Arch -> Arch -> Bool
== :: Arch -> Arch -> Bool
$c== :: Arch -> Arch -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
Eq, (forall x. Arch -> Rep Arch x)
-> (forall x. Rep Arch x -> Arch) -> Generic Arch
forall x. Rep Arch x -> Arch
forall x. Arch -> Rep Arch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Arch x -> Arch
$cfrom :: forall x. Arch -> Rep Arch x
Generic, Eq Arch
Eq Arch
-> (Arch -> Arch -> Ordering)
-> (Arch -> Arch -> Bool)
-> (Arch -> Arch -> Bool)
-> (Arch -> Arch -> Bool)
-> (Arch -> Arch -> Bool)
-> (Arch -> Arch -> Arch)
-> (Arch -> Arch -> Arch)
-> Ord Arch
Arch -> Arch -> Bool
Arch -> Arch -> Ordering
Arch -> Arch -> Arch
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 :: Arch -> Arch -> Arch
$cmin :: Arch -> Arch -> Arch
max :: Arch -> Arch -> Arch
$cmax :: Arch -> Arch -> Arch
>= :: Arch -> Arch -> Bool
$c>= :: Arch -> Arch -> Bool
> :: Arch -> Arch -> Bool
$c> :: Arch -> Arch -> Bool
<= :: Arch -> Arch -> Bool
$c<= :: Arch -> Arch -> Bool
< :: Arch -> Arch -> Bool
$c< :: Arch -> Arch -> Bool
compare :: Arch -> Arch -> Ordering
$ccompare :: Arch -> Arch -> Ordering
External instance of the constraint type Ord Char
Instance of class: Eq of the constraint type Eq Arch
External instance of the constraint type Ord Char
External instance of the constraint type forall a. Ord a => Ord [a]
Instance of class: Eq of the constraint type Eq Arch
Ord, Int -> Arch -> ShowS
[Arch] -> ShowS
Arch -> String
(Int -> Arch -> ShowS)
-> (Arch -> String) -> ([Arch] -> ShowS) -> Show Arch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Arch] -> ShowS
$cshowList :: [Arch] -> ShowS
show :: Arch -> String
$cshow :: Arch -> String
showsPrec :: Int -> Arch -> ShowS
$cshowsPrec :: Int -> Arch -> ShowS
External instance of the constraint type Show Char
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Ord Int
Show, ReadPrec [Arch]
ReadPrec Arch
Int -> ReadS Arch
ReadS [Arch]
(Int -> ReadS Arch)
-> ReadS [Arch] -> ReadPrec Arch -> ReadPrec [Arch] -> Read Arch
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Arch]
$creadListPrec :: ReadPrec [Arch]
readPrec :: ReadPrec Arch
$creadPrec :: ReadPrec Arch
readList :: ReadS [Arch]
$creadList :: ReadS [Arch]
readsPrec :: Int -> ReadS Arch
$creadsPrec :: Int -> ReadS Arch
External instance of the constraint type Read Char
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read Arch
Read, Typeable, Typeable Arch
DataType
Constr
Typeable Arch
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Arch -> c Arch)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Arch)
-> (Arch -> Constr)
-> (Arch -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Arch))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Arch))
-> ((forall b. Data b => b -> b) -> Arch -> Arch)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r)
-> (forall u. (forall d. Data d => d -> u) -> Arch -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Arch -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Arch -> m Arch)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Arch -> m Arch)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Arch -> m Arch)
-> Data Arch
Arch -> DataType
Arch -> Constr
(forall b. Data b => b -> b) -> Arch -> Arch
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Arch -> c Arch
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Arch
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Arch -> u
forall u. (forall d. Data d => d -> u) -> Arch -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Arch -> m Arch
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Arch -> m Arch
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Arch
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Arch -> c Arch
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Arch)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Arch)
$cOtherArch :: Constr
$cJavaScript :: Constr
$cVax :: Constr
$cM68k :: Constr
$cRs6000 :: Constr
$cHppa :: Constr
$cAlpha :: Constr
$cS390 :: Constr
$cIA64 :: Constr
$cSH :: Constr
$cMips :: Constr
$cAArch64 :: Constr
$cArm :: Constr
$cSparc :: Constr
$cPPC64 :: Constr
$cPPC :: Constr
$cX86_64 :: Constr
$cI386 :: Constr
$tArch :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Arch -> m Arch
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Arch -> m Arch
gmapMp :: (forall d. Data d => d -> m d) -> Arch -> m Arch
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Arch -> m Arch
gmapM :: (forall d. Data d => d -> m d) -> Arch -> m Arch
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Arch -> m Arch
gmapQi :: Int -> (forall d. Data d => d -> u) -> Arch -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Arch -> u
gmapQ :: (forall d. Data d => d -> u) -> Arch -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Arch -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r
gmapT :: (forall b. Data b => b -> b) -> Arch -> Arch
$cgmapT :: (forall b. Data b => b -> b) -> Arch -> Arch
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Arch)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Arch)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Arch)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Arch)
dataTypeOf :: Arch -> DataType
$cdataTypeOf :: Arch -> DataType
toConstr :: Arch -> Constr
$ctoConstr :: Arch -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Arch
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Arch
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Arch -> c Arch
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Arch -> c Arch
External instance of the constraint type Data Char
External instance of the constraint type Data Char
External instance of the constraint type Data Char
External instance of the constraint type forall a. Data a => Data [a]
Data)
instance Binary Arch
instance Structured Arch
instance NFData Arch where rnf :: Arch -> ()
rnf = Arch -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
Instance of class: Generic of the constraint type Generic Arch
genericRnf
knownArches :: [Arch]
knownArches :: [Arch]
knownArches = [Arch
I386, Arch
X86_64, Arch
PPC, Arch
PPC64, Arch
Sparc
,Arch
Arm, Arch
AArch64, Arch
Mips, Arch
SH
,Arch
IA64, Arch
S390
,Arch
Alpha, Arch
Hppa, Arch
Rs6000
,Arch
M68k, Arch
Vax
,Arch
JavaScript]
archAliases :: ClassificationStrictness -> Arch -> [String]
archAliases :: ClassificationStrictness -> Arch -> [String]
archAliases ClassificationStrictness
Strict Arch
_ = []
archAliases ClassificationStrictness
Compat Arch
_ = []
archAliases ClassificationStrictness
_ Arch
PPC = [String
"powerpc"]
archAliases ClassificationStrictness
_ Arch
PPC64 = [String
"powerpc64", String
"powerpc64le"]
archAliases ClassificationStrictness
_ Arch
Sparc = [String
"sparc64", String
"sun4"]
archAliases ClassificationStrictness
_ Arch
Mips = [String
"mipsel", String
"mipseb"]
archAliases ClassificationStrictness
_ Arch
Arm = [String
"armeb", String
"armel"]
archAliases ClassificationStrictness
_ Arch
AArch64 = [String
"arm64"]
archAliases ClassificationStrictness
_ Arch
_ = []
instance Pretty Arch where
pretty :: Arch -> Doc
pretty (OtherArch String
name) = String -> Doc
Disp.text String
name
pretty Arch
other = String -> Doc
Disp.text (ShowS
lowercase (Arch -> String
forall a. Show a => a -> String
Instance of class: Show of the constraint type Show Arch
show Arch
other))
instance Parsec Arch where
parsec :: m Arch
parsec = ClassificationStrictness -> String -> Arch
classifyArch ClassificationStrictness
Strict (String -> Arch) -> m String -> m Arch
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
<$> m String
forall (m :: * -> *). CabalParsing m => m String
Evidence bound by a type signature of the constraint type CabalParsing m
parsecIdent
classifyArch :: ClassificationStrictness -> String -> Arch
classifyArch :: ClassificationStrictness -> String -> Arch
classifyArch ClassificationStrictness
strictness String
s =
Arch -> Maybe Arch -> Arch
forall a. a -> Maybe a -> a
fromMaybe (String -> Arch
OtherArch String
s) (Maybe Arch -> Arch) -> Maybe Arch -> Arch
forall a b. (a -> b) -> a -> b
$ String -> [(String, Arch)] -> Maybe Arch
forall a b. Eq a => a -> [(a, b)] -> Maybe b
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
lookup (ShowS
lowercase String
s) [(String, Arch)]
archMap
where
archMap :: [(String, Arch)]
archMap = [ (String
name, Arch
arch)
| Arch
arch <- [Arch]
knownArches
, String
name <- Arch -> String
forall a. Pretty a => a -> String
Instance of class: Pretty of the constraint type Pretty Arch
prettyShow Arch
arch String -> [String] -> [String]
forall a. a -> [a] -> [a]
: ClassificationStrictness -> Arch -> [String]
archAliases ClassificationStrictness
strictness Arch
arch ]
buildArch :: Arch
buildArch :: Arch
buildArch = ClassificationStrictness -> String -> Arch
classifyArch ClassificationStrictness
Permissive String
System.Info.arch
data Platform = Platform Arch OS
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
Instance of class: Eq of the constraint type Eq OS
Instance of class: Eq of the constraint type Eq Arch
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
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
Instance of class: Eq of the constraint type Eq Platform
Instance of class: Ord of the constraint type Ord OS
Instance of class: Ord of the constraint type Ord Arch
Instance of class: Ord of the constraint type Ord Platform
Instance of class: Eq of the constraint type 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
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show OS
Instance of class: Show of the constraint type Show Arch
Show, ReadPrec [Platform]
ReadPrec Platform
Int -> ReadS Platform
ReadS [Platform]
(Int -> ReadS Platform)
-> ReadS [Platform]
-> ReadPrec Platform
-> ReadPrec [Platform]
-> Read Platform
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Platform]
$creadListPrec :: ReadPrec [Platform]
readPrec :: ReadPrec Platform
$creadPrec :: ReadPrec Platform
readList :: ReadS [Platform]
$creadList :: ReadS [Platform]
readsPrec :: Int -> ReadS Platform
$creadsPrec :: Int -> ReadS Platform
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read OS
Instance of class: Read of the constraint type Read Arch
Instance of class: Read of the constraint type Read Platform
Read, Typeable, Typeable Platform
DataType
Constr
Typeable Platform
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Platform -> c Platform)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Platform)
-> (Platform -> Constr)
-> (Platform -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Platform))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Platform))
-> ((forall b. Data b => b -> b) -> Platform -> Platform)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Platform -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Platform -> r)
-> (forall u. (forall d. Data d => d -> u) -> Platform -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Platform -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Platform -> m Platform)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Platform -> m Platform)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Platform -> m Platform)
-> Data Platform
Platform -> DataType
Platform -> Constr
(forall b. Data b => b -> b) -> Platform -> Platform
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Platform -> c Platform
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Platform
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Platform -> u
forall u. (forall d. Data d => d -> u) -> Platform -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Platform -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Platform -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Platform -> m Platform
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Platform -> m Platform
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Platform
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Platform -> c Platform
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Platform)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Platform)
$cPlatform :: Constr
$tPlatform :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Platform -> m Platform
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Platform -> m Platform
gmapMp :: (forall d. Data d => d -> m d) -> Platform -> m Platform
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Platform -> m Platform
gmapM :: (forall d. Data d => d -> m d) -> Platform -> m Platform
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Platform -> m Platform
gmapQi :: Int -> (forall d. Data d => d -> u) -> Platform -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Platform -> u
gmapQ :: (forall d. Data d => d -> u) -> Platform -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Platform -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Platform -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Platform -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Platform -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Platform -> r
gmapT :: (forall b. Data b => b -> b) -> Platform -> Platform
$cgmapT :: (forall b. Data b => b -> b) -> Platform -> Platform
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Platform)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Platform)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Platform)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Platform)
dataTypeOf :: Platform -> DataType
$cdataTypeOf :: Platform -> DataType
toConstr :: Platform -> Constr
$ctoConstr :: Platform -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Platform
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Platform
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Platform -> c Platform
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Platform -> c Platform
Instance of class: Data of the constraint type Data OS
Instance of class: Data of the constraint type Data Arch
Data)
instance Binary Platform
instance Structured Platform
instance NFData Platform where rnf :: Platform -> ()
rnf = Platform -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
Instance of class: NFData of the constraint type NFData Arch
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
Instance of class: NFData of the constraint type NFData OS
Instance of class: Generic of the constraint type Generic Platform
genericRnf
instance Pretty Platform where
pretty :: Platform -> Doc
pretty (Platform Arch
arch OS
os) = Arch -> Doc
forall a. Pretty a => a -> Doc
Instance of class: Pretty of the constraint type Pretty Arch
pretty Arch
arch Doc -> Doc -> Doc
<<>> Char -> Doc
Disp.char Char
'-' Doc -> Doc -> Doc
<<>> OS -> Doc
forall a. Pretty a => a -> Doc
Instance of class: Pretty of the constraint type Pretty OS
pretty OS
os
instance Parsec Platform where
parsec :: m Platform
parsec = do
Arch
arch <- m Arch
parsecDashlessArch
Char
_ <- Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.char Char
'-'
OS
os <- m OS
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
Evidence bound by a type signature of the constraint type CabalParsing m
Instance of class: Parsec of the constraint type Parsec OS
parsec
Platform -> m Platform
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
return (Arch -> OS -> Platform
Platform Arch
arch OS
os)
where
parsecDashlessArch :: m Arch
parsecDashlessArch = ClassificationStrictness -> String -> Arch
classifyArch ClassificationStrictness
Strict (String -> Arch) -> m String -> m Arch
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
<$> m String
dashlessIdent
dashlessIdent :: m String
dashlessIdent = (Char -> ShowS) -> m Char -> m String -> m String
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
liftA2 (:) m Char
firstChar m String
rest
where
firstChar :: m Char
firstChar = (Char -> Bool) -> m Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.satisfy Char -> Bool
isAlpha
rest :: m String
rest = (Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.munch (\Char
c -> Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Char
== Char
'_')
buildPlatform :: Platform
buildPlatform :: Platform
buildPlatform = Arch -> OS -> Platform
Platform Arch
buildArch OS
buildOS
parsecIdent :: CabalParsing m => m String
parsecIdent :: m String
parsecIdent = (:) (Char -> ShowS) -> m Char -> m ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
<$> m Char
firstChar m ShowS -> m String -> m String
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
<*> m String
rest
where
firstChar :: m Char
firstChar = (Char -> Bool) -> m Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.satisfy Char -> Bool
isAlpha
rest :: m String
rest = (Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.munch (\Char
c -> Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Char
== Char
'_' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Char
== Char
'-')
platformFromTriple :: String -> Maybe Platform
platformFromTriple :: String -> Maybe Platform
platformFromTriple String
triple =
(String -> Maybe Platform)
-> (Platform -> Maybe Platform)
-> Either String Platform
-> Maybe Platform
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe Platform -> String -> Maybe Platform
forall a b. a -> b -> a
const Maybe Platform
forall a. Maybe a
Nothing) Platform -> Maybe Platform
forall a. a -> Maybe a
Just (Either String Platform -> Maybe Platform)
-> Either String Platform -> Maybe Platform
forall a b. (a -> b) -> a -> b
$ ParsecParser Platform -> String -> Either String Platform
forall a. ParsecParser a -> String -> Either String a
explicitEitherParsec ParsecParser Platform
parseTriple String
triple
where parseWord :: ParsecParser String
parseWord = (Char -> Bool) -> ParsecParser String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
External instance of the constraint type CharParsing ParsecParser
P.munch1 (\Char
c -> Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Char
== Char
'_')
parseTriple :: ParsecParser Platform
parseTriple = do
Arch
arch <- (String -> Arch) -> ParsecParser String -> ParsecParser Arch
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor ParsecParser
fmap (ClassificationStrictness -> String -> Arch
classifyArch ClassificationStrictness
Permissive) ParsecParser String
parseWord
Char
_ <- Char -> ParsecParser Char
forall (m :: * -> *). CharParsing m => Char -> m Char
External instance of the constraint type CharParsing ParsecParser
P.char Char
'-'
String
_ <- ParsecParser String
parseWord
Char
_ <- Char -> ParsecParser Char
forall (m :: * -> *). CharParsing m => Char -> m Char
External instance of the constraint type CharParsing ParsecParser
P.char Char
'-'
OS
os <- (String -> OS) -> ParsecParser String -> ParsecParser OS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor ParsecParser
fmap (ClassificationStrictness -> String -> OS
classifyOS ClassificationStrictness
Permissive) ParsecParser String
forall (m :: * -> *). CabalParsing m => m String
External instance of the constraint type CabalParsing ParsecParser
parsecIdent
Platform -> ParsecParser Platform
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ParsecParser
return (Platform -> ParsecParser Platform)
-> Platform -> ParsecParser Platform
forall a b. (a -> b) -> a -> b
$ Arch -> OS -> Platform
Platform Arch
arch OS
os