Cabal-syntax-3.11.0.0: A library for working with .cabal files
CopyrightDuncan Coutts 2007-2008
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.System

Description

Cabal often needs to do slightly different things on specific platforms. You probably know about the os however using that is very inconvenient because it is a string and different Haskell implementations do not agree on using the same strings for the same platforms! (In particular see the controversy over "windows" vs "mingw32"). So to make it more consistent and easy to use we have an OS enumeration.

Synopsis

Operating System

data OS Source #

These are the known OS names: Linux, Windows, OSX ,FreeBSD, OpenBSD, NetBSD, DragonFly ,Solaris, AIX, HPUX, IRIX ,HaLVM ,Hurd ,IOS, Android, Ghcjs, Wasi

The following aliases can also be used:, * Windows aliases: mingw32, win32, cygwin32 * OSX alias: darwin * Hurd alias: gnu * FreeBSD alias: kfreebsdgnu * Solaris alias: solaris2

Instances

Instances details
Parsec OS Source # 
Instance details

Defined in Distribution.System

Methods

parsec :: CabalParsing m => m OS Source #

Pretty OS Source # 
Instance details

Defined in Distribution.System

Structured OS Source # 
Instance details

Defined in Distribution.System

Binary OS Source # 
Instance details

Defined in Distribution.System

Methods

put :: OS -> Put Source #

get :: Get OS Source #

putList :: [OS] -> Put Source #

NFData OS Source # 
Instance details

Defined in Distribution.System

Methods

rnf :: OS -> () Source #

Data OS Source # 
Instance details

Defined in Distribution.System

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OS -> c OS #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OS #

toConstr :: OS -> Constr #

dataTypeOf :: OS -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OS) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OS) #

gmapT :: (forall b. Data b => b -> b) -> OS -> OS #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OS -> r #

gmapQ :: (forall d. Data d => d -> u) -> OS -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OS -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OS -> m OS #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OS -> m OS #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OS -> m OS #

Generic OS Source # 
Instance details

Defined in Distribution.System

Associated Types

type Rep OS 
Instance details

Defined in Distribution.System

type Rep OS = D1 ('MetaData "OS" "Distribution.System" "Cabal-syntax-3.11.0.0-inplace" 'False) ((((C1 ('MetaCons "Linux" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Windows" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OSX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FreeBSD" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OpenBSD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NetBSD" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DragonFly" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Solaris" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AIX" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "HPUX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IRIX" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HaLVM" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Hurd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IOS" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Android" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ghcjs" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Wasi" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Haiku" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherOS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))))

Methods

from :: OS -> Rep OS x #

to :: Rep OS x -> OS #

Read OS Source # 
Instance details

Defined in Distribution.System

Show OS Source # 
Instance details

Defined in Distribution.System

Methods

showsPrec :: Int -> OS -> ShowS #

show :: OS -> String #

showList :: [OS] -> ShowS #

Eq OS Source # 
Instance details

Defined in Distribution.System

Methods

(==) :: OS -> OS -> Bool #

(/=) :: OS -> OS -> Bool #

Ord OS Source # 
Instance details

Defined in Distribution.System

Methods

compare :: OS -> OS -> Ordering #

(<) :: OS -> OS -> Bool #

(<=) :: OS -> OS -> Bool #

(>) :: OS -> OS -> Bool #

(>=) :: OS -> OS -> Bool #

max :: OS -> OS -> OS #

min :: OS -> OS -> OS #

type Rep OS Source # 
Instance details

Defined in Distribution.System

type Rep OS = D1 ('MetaData "OS" "Distribution.System" "Cabal-syntax-3.11.0.0-inplace" 'False) ((((C1 ('MetaCons "Linux" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Windows" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OSX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FreeBSD" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OpenBSD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NetBSD" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DragonFly" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Solaris" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AIX" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "HPUX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IRIX" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HaLVM" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Hurd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IOS" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Android" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ghcjs" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Wasi" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Haiku" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherOS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))))

Machine Architecture

data Arch Source #

These are the known Arches: I386, X86_64, PPC, PPC64, PPC64LE, Sparc, Sparc64, Arm, AArch64, Mips, SH, IA64, S390, S390X, Alpha, Hppa, Rs6000, M68k, Vax, RISCV64, LoongArch64, JavaScript and Wasm32.

The following aliases can also be used: * PPC alias: powerpc * PPC64 alias : powerpc64 * PPC64LE alias : powerpc64le * Mips aliases: mipsel, mipseb * Arm aliases: armeb, armel * AArch64 aliases: arm64

Instances

Instances details
Parsec Arch Source # 
Instance details

Defined in Distribution.System

Methods

parsec :: CabalParsing m => m Arch Source #

Pretty Arch Source # 
Instance details

Defined in Distribution.System

Structured Arch Source # 
Instance details

Defined in Distribution.System

Binary Arch Source # 
Instance details

Defined in Distribution.System

NFData Arch Source # 
Instance details

Defined in Distribution.System

Methods

rnf :: Arch -> () Source #

Data Arch Source # 
Instance details

Defined in Distribution.System

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Arch -> c Arch #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Arch #

toConstr :: Arch -> Constr #

dataTypeOf :: Arch -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Arch) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Arch) #

gmapT :: (forall b. Data b => b -> b) -> Arch -> Arch #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arch -> r #

gmapQ :: (forall d. Data d => d -> u) -> Arch -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Arch -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Arch -> m Arch #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Arch -> m Arch #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Arch -> m Arch #

Generic Arch Source # 
Instance details

Defined in Distribution.System

Associated Types

type Rep Arch 
Instance details

Defined in Distribution.System

type Rep Arch = D1 ('MetaData "Arch" "Distribution.System" "Cabal-syntax-3.11.0.0-inplace" 'False) ((((C1 ('MetaCons "I386" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "X86_64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PPC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PPC64" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PPC64LE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sparc" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Sparc64" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Arm" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AArch64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mips" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SH" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IA64" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "S390" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "S390X" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Alpha" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Hppa" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Rs6000" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "M68k" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Vax" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RISCV64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LoongArch64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "JavaScript" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Wasm32" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherArch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))))

Methods

from :: Arch -> Rep Arch x #

to :: Rep Arch x -> Arch #

Read Arch Source # 
Instance details

Defined in Distribution.System

Show Arch Source # 
Instance details

Defined in Distribution.System

Methods

showsPrec :: Int -> Arch -> ShowS #

show :: Arch -> String #

showList :: [Arch] -> ShowS #

Eq Arch Source # 
Instance details

Defined in Distribution.System

Methods

(==) :: Arch -> Arch -> Bool #

(/=) :: Arch -> Arch -> Bool #

Ord Arch Source # 
Instance details

Defined in Distribution.System

Methods

compare :: Arch -> Arch -> Ordering #

(<) :: Arch -> Arch -> Bool #

(<=) :: Arch -> Arch -> Bool #

(>) :: Arch -> Arch -> Bool #

(>=) :: Arch -> Arch -> Bool #

max :: Arch -> Arch -> Arch #

min :: Arch -> Arch -> Arch #

type Rep Arch Source # 
Instance details

Defined in Distribution.System

type Rep Arch = D1 ('MetaData "Arch" "Distribution.System" "Cabal-syntax-3.11.0.0-inplace" 'False) ((((C1 ('MetaCons "I386" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "X86_64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PPC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PPC64" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PPC64LE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sparc" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Sparc64" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Arm" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AArch64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mips" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SH" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IA64" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "S390" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "S390X" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Alpha" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Hppa" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Rs6000" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "M68k" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Vax" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RISCV64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LoongArch64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "JavaScript" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Wasm32" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherArch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))))

Platform is a pair of arch and OS

data Platform Source #

Constructors

Platform Arch OS 

Instances

Instances details
Parsec Platform Source # 
Instance details

Defined in Distribution.System

Pretty Platform Source # 
Instance details

Defined in Distribution.System

Structured Platform Source # 
Instance details

Defined in Distribution.System

Binary Platform Source # 
Instance details

Defined in Distribution.System

NFData Platform Source # 
Instance details

Defined in Distribution.System

Methods

rnf :: Platform -> () Source #

Data Platform Source # 
Instance details

Defined in Distribution.System

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Platform -> c Platform #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Platform #

toConstr :: Platform -> Constr #

dataTypeOf :: Platform -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Platform) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Platform) #

gmapT :: (forall b. Data b => b -> b) -> Platform -> Platform #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Platform -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Platform -> r #

gmapQ :: (forall d. Data d => d -> u) -> Platform -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Platform -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Platform -> m Platform #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Platform -> m Platform #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Platform -> m Platform #

Generic Platform Source # 
Instance details

Defined in Distribution.System

Associated Types

type Rep Platform 
Instance details

Defined in Distribution.System

type Rep Platform = D1 ('MetaData "Platform" "Distribution.System" "Cabal-syntax-3.11.0.0-inplace" 'False) (C1 ('MetaCons "Platform" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Arch) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OS)))

Methods

from :: Platform -> Rep Platform x #

to :: Rep Platform x -> Platform #

Read Platform Source # 
Instance details

Defined in Distribution.System

Show Platform Source # 
Instance details

Defined in Distribution.System

Eq Platform Source # 
Instance details

Defined in Distribution.System

Ord Platform Source # 
Instance details

Defined in Distribution.System

type Rep Platform Source # 
Instance details

Defined in Distribution.System

type Rep Platform = D1 ('MetaData "Platform" "Distribution.System" "Cabal-syntax-3.11.0.0-inplace" 'False) (C1 ('MetaCons "Platform" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Arch) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OS)))

buildPlatform :: Platform Source #

The platform Cabal was compiled on. In most cases, LocalBuildInfo.hostPlatform should be used instead (the platform we're targeting).

Internal

Classification

data ClassificationStrictness Source #

How strict to be when classifying strings into the OS and Arch enums.

The reason we have multiple ways to do the classification is because there are two situations where we need to do it.

For parsing OS and arch names in .cabal files we really want everyone to be referring to the same or arch by the same name. Variety is not a virtue in this case. We don't mind about case though.

For the System.Info.os/arch different Haskell implementations use different names for the same or/arch. Also they tend to distinguish versions of an OS/arch which we just don't care about.

The Compat classification allows us to recognise aliases that are already in common use but it allows us to distinguish them from the canonical name which enables us to warn about such deprecated aliases.

Constructors

Permissive 
Compat 
Strict