Cabal-1.23.1.0: A framework for packaging Haskell software

CopyrightDuncan Coutts 2007-2008
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Distribution.System

Contents

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 "ming32"). So to make it more consistent and easy to use we have an OS enumeration.

Synopsis

Operating System

data OS Source

Instances

Eq OS 

Methods

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

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

Data OS 

Methods

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

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

toConstr :: OS -> Constr Source

dataTypeOf :: OS -> DataType Source

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

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

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

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

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

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

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

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

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

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

Ord OS 

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

Read OS 
Show OS 
Generic OS 

Associated Types

type Rep OS :: * -> * Source

Methods

from :: OS -> Rep OS x Source

to :: Rep OS x -> OS Source

Binary OS 

Methods

put :: OS -> Put Source

get :: Get OS Source

Text OS 

Methods

disp :: OS -> Doc Source

parse :: ReadP r OS Source

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

Machine Architecture

data Arch Source

Instances

Eq Arch 

Methods

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

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

Data Arch 

Methods

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

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

toConstr :: Arch -> Constr Source

dataTypeOf :: Arch -> DataType Source

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

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

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

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

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

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

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

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

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

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

Ord Arch 

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

Read Arch 
Show Arch 
Generic Arch 

Associated Types

type Rep Arch :: * -> * Source

Methods

from :: Arch -> Rep Arch x Source

to :: Rep Arch x -> Arch Source

Binary Arch 

Methods

put :: Arch -> Put Source

get :: Get Arch Source

Text Arch 
type Rep Arch = D1 (MetaData "Arch" "Distribution.System" "Cabal-1.23.1.0" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "I386" PrefixI False) U1) (C1 (MetaCons "X86_64" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PPC" PrefixI False) U1) (C1 (MetaCons "PPC64" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Sparc" PrefixI False) U1) (C1 (MetaCons "Arm" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Mips" PrefixI False) U1) (C1 (MetaCons "SH" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "IA64" PrefixI False) U1) (C1 (MetaCons "S390" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Alpha" PrefixI False) U1) (C1 (MetaCons "Hppa" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Rs6000" PrefixI False) U1) (C1 (MetaCons "M68k" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Vax" PrefixI False) U1) ((:+:) (C1 (MetaCons "JavaScript" PrefixI False) U1) (C1 (MetaCons "OtherArch" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))))) 

Platform is a pair of arch and OS

data Platform Source

Constructors

Platform Arch OS 

Instances

Eq Platform 
Data Platform 

Methods

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

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

toConstr :: Platform -> Constr Source

dataTypeOf :: Platform -> DataType Source

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

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

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

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

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

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

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

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

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

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

Ord Platform 
Read Platform 
Show Platform 
Generic Platform 

Associated Types

type Rep Platform :: * -> * Source

Binary Platform 
Text Platform 
type Rep Platform = D1 (MetaData "Platform" "Distribution.System" "Cabal-1.23.1.0" False) (C1 (MetaCons "Platform" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Arch)) (S1 (MetaSel (Nothing 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