module Distribution.System (
OS(..),
buildOS,
Arch(..),
buildArch,
Platform(..),
buildPlatform,
platformFromTriple,
knownOSs,
knownArches,
ClassificationStrictness (..),
classifyOS,
classifyArch,
) where
import Prelude ()
import Distribution.Compat.Prelude
import qualified System.Info (os, arch)
import Distribution.Text
import qualified Distribution.Compat.ReadP as Parse
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 (Eq, Generic, Ord, Show, Read, Typeable, Data)
instance Binary OS
knownOSs :: [OS]
knownOSs = [Linux, Windows, OSX
,FreeBSD, OpenBSD, NetBSD, DragonFly
,Solaris, AIX, HPUX, IRIX
,HaLVM
,Hurd
,IOS, Android
,Ghcjs]
osAliases :: ClassificationStrictness -> OS -> [String]
osAliases Permissive Windows = ["mingw32", "win32", "cygwin32"]
osAliases Compat Windows = ["mingw32", "win32"]
osAliases _ OSX = ["darwin"]
osAliases _ Hurd = ["gnu"]
osAliases Permissive FreeBSD = ["kfreebsdgnu"]
osAliases Compat FreeBSD = ["kfreebsdgnu"]
osAliases Permissive Solaris = ["solaris2"]
osAliases Compat Solaris = ["solaris2"]
osAliases _ _ = []
instance Text OS where
disp (OtherOS name) = Disp.text name
disp other = Disp.text (lowercase (show other))
parse = fmap (classifyOS Compat) ident
classifyOS :: ClassificationStrictness -> String -> OS
classifyOS strictness s =
fromMaybe (OtherOS s) $ lookup (lowercase s) osMap
where
osMap = [ (name, os)
| os <- knownOSs
, name <- display os : osAliases strictness os ]
buildOS :: OS
buildOS = classifyOS Permissive System.Info.os
data Arch = I386 | X86_64 | PPC | PPC64 | Sparc
| Arm | Mips | SH
| IA64 | S390
| Alpha | Hppa | Rs6000
| M68k | Vax
| JavaScript
| OtherArch String
deriving (Eq, Generic, Ord, Show, Read, Typeable, Data)
instance Binary Arch
knownArches :: [Arch]
knownArches = [I386, X86_64, PPC, PPC64, Sparc
,Arm, Mips, SH
,IA64, S390
,Alpha, Hppa, Rs6000
,M68k, Vax
,JavaScript]
archAliases :: ClassificationStrictness -> Arch -> [String]
archAliases Strict _ = []
archAliases Compat _ = []
archAliases _ PPC = ["powerpc"]
archAliases _ PPC64 = ["powerpc64"]
archAliases _ Sparc = ["sparc64", "sun4"]
archAliases _ Mips = ["mipsel", "mipseb"]
archAliases _ Arm = ["armeb", "armel"]
archAliases _ _ = []
instance Text Arch where
disp (OtherArch name) = Disp.text name
disp other = Disp.text (lowercase (show other))
parse = fmap (classifyArch Strict) ident
classifyArch :: ClassificationStrictness -> String -> Arch
classifyArch strictness s =
fromMaybe (OtherArch s) $ lookup (lowercase s) archMap
where
archMap = [ (name, arch)
| arch <- knownArches
, name <- display arch : archAliases strictness arch ]
buildArch :: Arch
buildArch = classifyArch Permissive System.Info.arch
data Platform = Platform Arch OS
deriving (Eq, Generic, Ord, Show, Read, Typeable, Data)
instance Binary Platform
instance Text Platform where
disp (Platform arch os) = disp arch <<>> Disp.char '-' <<>> disp os
parse = do
arch <- parseDashlessArch
_ <- Parse.char '-'
os <- parse
return (Platform arch os)
where
parseDashlessArch :: Parse.ReadP r Arch
parseDashlessArch = fmap (classifyArch Strict) dashlessIdent
buildPlatform :: Platform
buildPlatform = Platform buildArch buildOS
ident :: Parse.ReadP r String
ident = liftM2 (:) firstChar rest
where firstChar = Parse.satisfy isAlpha
rest = Parse.munch (\c -> isAlphaNum c || c == '_' || c == '-')
dashlessIdent :: Parse.ReadP r String
dashlessIdent = liftM2 (:) firstChar rest
where firstChar = Parse.satisfy isAlpha
rest = Parse.munch (\c -> isAlphaNum c || c == '_')
lowercase :: String -> String
lowercase = map toLower
platformFromTriple :: String -> Maybe Platform
platformFromTriple triple =
fmap fst (listToMaybe $ Parse.readP_to_S parseTriple triple)
where parseWord = Parse.munch1 (\c -> isAlphaNum c || c == '_')
parseTriple = do
arch <- fmap (classifyArch Permissive) parseWord
_ <- Parse.char '-'
_ <- parseWord
_ <- Parse.char '-'
os <- fmap (classifyOS Permissive) ident
return $ Platform arch os