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

Synopsis

Operating System

data OS Source #

Instances

Eq OS Source # 

Methods

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

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

Data OS Source # 

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 :: (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 #

Ord OS Source # 

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 Source # 
Show OS Source # 

Methods

showsPrec :: Int -> OS -> ShowS #

show :: OS -> String #

showList :: [OS] -> ShowS #

Generic OS Source # 

Associated Types

type Rep OS :: * -> * #

Methods

from :: OS -> Rep OS x #

to :: Rep OS x -> OS #

Binary OS Source # 

Methods

put :: OS -> Put #

get :: Get OS #

putList :: [OS] -> Put #

Text OS Source # 

Methods

disp :: OS -> Doc Source #

parse :: ReadP r OS Source #

type Rep OS Source # 
type Rep OS = D1 (MetaData "OS" "Distribution.System" "Cabal-1.24.1.0-Ljj1oIJNQht1MqGf4TeTWN" 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 Source # 

Methods

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

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

Data Arch Source # 

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 :: (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 #

Ord Arch Source # 

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 Source # 
Show Arch Source # 

Methods

showsPrec :: Int -> Arch -> ShowS #

show :: Arch -> String #

showList :: [Arch] -> ShowS #

Generic Arch Source # 

Associated Types

type Rep Arch :: * -> * #

Methods

from :: Arch -> Rep Arch x #

to :: Rep Arch x -> Arch #

Binary Arch Source # 

Methods

put :: Arch -> Put #

get :: Get Arch #

putList :: [Arch] -> Put #

Text Arch Source # 

Methods

disp :: Arch -> Doc Source #

parse :: ReadP r Arch Source #

type Rep Arch Source # 
type Rep Arch = D1 (MetaData "Arch" "Distribution.System" "Cabal-1.24.1.0-Ljj1oIJNQht1MqGf4TeTWN" 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 Source # 
Data Platform Source # 

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 :: (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 #

Ord Platform Source # 
Read Platform Source # 
Show Platform Source # 
Generic Platform Source # 

Associated Types

type Rep Platform :: * -> * #

Methods

from :: Platform -> Rep Platform x #

to :: Rep Platform x -> Platform #

Binary Platform Source # 

Methods

put :: Platform -> Put #

get :: Get Platform #

putList :: [Platform] -> Put #

Text Platform Source # 
type Rep Platform Source # 
type Rep Platform = D1 (MetaData "Platform" "Distribution.System" "Cabal-1.24.1.0-Ljj1oIJNQht1MqGf4TeTWN" 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