{-# LANGUAGE RecordWildCards #-}
module LLVM.Triple (
Triple (..), Architecture (..), Vendor (..), OS (..), unknownTriple, parseTriple, tripleToString
) where
import LLVM.Prelude
import Control.Monad.Trans.Except
import Data.Attoparsec.ByteString
import Data.Attoparsec.ByteString.Char8
import Data.ByteString.Char8 as ByteString hiding (map, foldr)
import Data.ByteString.Short hiding (pack, foldr)
import Data.Map (Map, (!))
import qualified Data.Map as Map
data Architecture
= UnknownArch
| Arm
| Armeb
| Aarch64
| Aarch64_be
| Aarch64_32
| Arc
| Avr
| Bpfel
| Bpfeb
| Csky
| Hexagon
| Mips
| Mipsel
| Mips64
| Mips64el
| Msp430
| Ppc
| Ppcle
| Ppc64
| Ppc64le
| R600
| Amdgcn
| Riscv32
| Riscv64
| Sparc
| Sparcv9
| Sparcel
| Systemz
| Tce
| Tcele
| Thumb
| Thumbeb
| X86
| X86_64
| Xcore
| Nvptx
| Nvptx64
| Le32
| Le64
| Amdil
| Amdil64
| Hsail
| Hsail64
| Spir
| Spir64
| Kalimba
| Shave
| Lanai
| Wasm32
| Wasm64
| Renderscript32
| Renderscript64
| Ve
deriving (Architecture -> Architecture -> Bool
(Architecture -> Architecture -> Bool)
-> (Architecture -> Architecture -> Bool) -> Eq Architecture
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Architecture -> Architecture -> Bool
== :: Architecture -> Architecture -> Bool
$c/= :: Architecture -> Architecture -> Bool
/= :: Architecture -> Architecture -> Bool
Eq, Eq Architecture
Eq Architecture
-> (Architecture -> Architecture -> Ordering)
-> (Architecture -> Architecture -> Bool)
-> (Architecture -> Architecture -> Bool)
-> (Architecture -> Architecture -> Bool)
-> (Architecture -> Architecture -> Bool)
-> (Architecture -> Architecture -> Architecture)
-> (Architecture -> Architecture -> Architecture)
-> Ord Architecture
Architecture -> Architecture -> Bool
Architecture -> Architecture -> Ordering
Architecture -> Architecture -> Architecture
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
$ccompare :: Architecture -> Architecture -> Ordering
compare :: Architecture -> Architecture -> Ordering
$c< :: Architecture -> Architecture -> Bool
< :: Architecture -> Architecture -> Bool
$c<= :: Architecture -> Architecture -> Bool
<= :: Architecture -> Architecture -> Bool
$c> :: Architecture -> Architecture -> Bool
> :: Architecture -> Architecture -> Bool
$c>= :: Architecture -> Architecture -> Bool
>= :: Architecture -> Architecture -> Bool
$cmax :: Architecture -> Architecture -> Architecture
max :: Architecture -> Architecture -> Architecture
$cmin :: Architecture -> Architecture -> Architecture
min :: Architecture -> Architecture -> Architecture
Ord, Int -> Architecture -> ShowS
[Architecture] -> ShowS
Architecture -> String
(Int -> Architecture -> ShowS)
-> (Architecture -> String)
-> ([Architecture] -> ShowS)
-> Show Architecture
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Architecture -> ShowS
showsPrec :: Int -> Architecture -> ShowS
$cshow :: Architecture -> String
show :: Architecture -> String
$cshowList :: [Architecture] -> ShowS
showList :: [Architecture] -> ShowS
Show)
data SubArchitecture
= NoSubArch
| ARMSubArch_v8_7a
| ARMSubArch_v8_6a
| ARMSubArch_v8_5a
| ARMSubArch_v8_4a
| ARMSubArch_v8_3a
| ARMSubArch_v8_2a
| ARMSubArch_v8_1a
| ARMSubArch_v8
| ARMSubArch_v8r
| ARMSubArch_v8m_baseline
| ARMSubArch_v8m_mainline
| ARMSubArch_v8_1m_mainline
| ARMSubArch_v7
| ARMSubArch_v7em
| ARMSubArch_v7m
| ARMSubArch_v7s
| ARMSubArch_v7k
| ARMSubArch_v7ve
| ARMSubArch_v6
| ARMSubArch_v6m
| ARMSubArch_v6k
| ARMSubArch_v6t2
| ARMSubArch_v5
| ARMSubArch_v5te
| ARMSubArch_v4t
| AArch64SubArch_arm64e
| KalimbaSubArch_v3
| KalimbaSubArch_v4
| KalimbaSubArch_v5
| MipsSubArch_r6
| PPCSubArch_spe
deriving (SubArchitecture -> SubArchitecture -> Bool
(SubArchitecture -> SubArchitecture -> Bool)
-> (SubArchitecture -> SubArchitecture -> Bool)
-> Eq SubArchitecture
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubArchitecture -> SubArchitecture -> Bool
== :: SubArchitecture -> SubArchitecture -> Bool
$c/= :: SubArchitecture -> SubArchitecture -> Bool
/= :: SubArchitecture -> SubArchitecture -> Bool
Eq, Eq SubArchitecture
Eq SubArchitecture
-> (SubArchitecture -> SubArchitecture -> Ordering)
-> (SubArchitecture -> SubArchitecture -> Bool)
-> (SubArchitecture -> SubArchitecture -> Bool)
-> (SubArchitecture -> SubArchitecture -> Bool)
-> (SubArchitecture -> SubArchitecture -> Bool)
-> (SubArchitecture -> SubArchitecture -> SubArchitecture)
-> (SubArchitecture -> SubArchitecture -> SubArchitecture)
-> Ord SubArchitecture
SubArchitecture -> SubArchitecture -> Bool
SubArchitecture -> SubArchitecture -> Ordering
SubArchitecture -> SubArchitecture -> SubArchitecture
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
$ccompare :: SubArchitecture -> SubArchitecture -> Ordering
compare :: SubArchitecture -> SubArchitecture -> Ordering
$c< :: SubArchitecture -> SubArchitecture -> Bool
< :: SubArchitecture -> SubArchitecture -> Bool
$c<= :: SubArchitecture -> SubArchitecture -> Bool
<= :: SubArchitecture -> SubArchitecture -> Bool
$c> :: SubArchitecture -> SubArchitecture -> Bool
> :: SubArchitecture -> SubArchitecture -> Bool
$c>= :: SubArchitecture -> SubArchitecture -> Bool
>= :: SubArchitecture -> SubArchitecture -> Bool
$cmax :: SubArchitecture -> SubArchitecture -> SubArchitecture
max :: SubArchitecture -> SubArchitecture -> SubArchitecture
$cmin :: SubArchitecture -> SubArchitecture -> SubArchitecture
min :: SubArchitecture -> SubArchitecture -> SubArchitecture
Ord, Int -> SubArchitecture -> ShowS
[SubArchitecture] -> ShowS
SubArchitecture -> String
(Int -> SubArchitecture -> ShowS)
-> (SubArchitecture -> String)
-> ([SubArchitecture] -> ShowS)
-> Show SubArchitecture
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubArchitecture -> ShowS
showsPrec :: Int -> SubArchitecture -> ShowS
$cshow :: SubArchitecture -> String
show :: SubArchitecture -> String
$cshowList :: [SubArchitecture] -> ShowS
showList :: [SubArchitecture] -> ShowS
Show)
data Vendor
= UnknownVendor
| Apple
| PC
| SCEI
| Freescale
| IBM
| ImaginationTechnologies
| MipsTechnologies
| NVIDIA
| CSR
| Myriad
| AMD
| Mesa
| SUSE
| OpenEmbedded
deriving (Vendor -> Vendor -> Bool
(Vendor -> Vendor -> Bool)
-> (Vendor -> Vendor -> Bool) -> Eq Vendor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Vendor -> Vendor -> Bool
== :: Vendor -> Vendor -> Bool
$c/= :: Vendor -> Vendor -> Bool
/= :: Vendor -> Vendor -> Bool
Eq, Eq Vendor
Eq Vendor
-> (Vendor -> Vendor -> Ordering)
-> (Vendor -> Vendor -> Bool)
-> (Vendor -> Vendor -> Bool)
-> (Vendor -> Vendor -> Bool)
-> (Vendor -> Vendor -> Bool)
-> (Vendor -> Vendor -> Vendor)
-> (Vendor -> Vendor -> Vendor)
-> Ord Vendor
Vendor -> Vendor -> Bool
Vendor -> Vendor -> Ordering
Vendor -> Vendor -> Vendor
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
$ccompare :: Vendor -> Vendor -> Ordering
compare :: Vendor -> Vendor -> Ordering
$c< :: Vendor -> Vendor -> Bool
< :: Vendor -> Vendor -> Bool
$c<= :: Vendor -> Vendor -> Bool
<= :: Vendor -> Vendor -> Bool
$c> :: Vendor -> Vendor -> Bool
> :: Vendor -> Vendor -> Bool
$c>= :: Vendor -> Vendor -> Bool
>= :: Vendor -> Vendor -> Bool
$cmax :: Vendor -> Vendor -> Vendor
max :: Vendor -> Vendor -> Vendor
$cmin :: Vendor -> Vendor -> Vendor
min :: Vendor -> Vendor -> Vendor
Ord, Int -> Vendor -> ShowS
[Vendor] -> ShowS
Vendor -> String
(Int -> Vendor -> ShowS)
-> (Vendor -> String) -> ([Vendor] -> ShowS) -> Show Vendor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Vendor -> ShowS
showsPrec :: Int -> Vendor -> ShowS
$cshow :: Vendor -> String
show :: Vendor -> String
$cshowList :: [Vendor] -> ShowS
showList :: [Vendor] -> ShowS
Show)
data OS
= UnknownOS
| Ananas
| CloudABI
| Darwin
| DragonFly
| FreeBSD
| Fuchsia
| IOS
| KFreeBSD
| Linux
| Lv2
| MacOSX
| NetBSD
| OpenBSD
| Solaris
| Win32
| ZOS
| Haiku
| Minix
| RTEMS
| NaCl
| AIX
| CUDA
| NVCL
| AMDHSA
| PS4
| ELFIAMCU
| TvOS
| WatchOS
| Mesa3D
| Contiki
| AMDPAL
| HermitCore
| Hurd
| WASI
| Emscripten
deriving (OS -> OS -> Bool
(OS -> OS -> Bool) -> (OS -> OS -> Bool) -> Eq OS
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OS -> OS -> Bool
== :: OS -> OS -> Bool
$c/= :: OS -> OS -> Bool
/= :: OS -> OS -> Bool
Eq, 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
$ccompare :: OS -> OS -> Ordering
compare :: OS -> OS -> Ordering
$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
>= :: OS -> OS -> Bool
$cmax :: OS -> OS -> OS
max :: OS -> OS -> OS
$cmin :: OS -> OS -> OS
min :: OS -> OS -> 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
$cshowsPrec :: Int -> OS -> ShowS
showsPrec :: Int -> OS -> ShowS
$cshow :: OS -> String
show :: OS -> String
$cshowList :: [OS] -> ShowS
showList :: [OS] -> ShowS
Show)
data Environment
= UnknownEnvironment
| GNU
| GNUABIN32
| GNUABI64
| GNUEABI
| GNUEABIHF
| GNUX32
| GNUILP32
| CODE16
| EABI
| EABIHF
| Android
| Musl
| MuslEABI
| MuslEABIHF
| MSVC
| Itanium
| Cygnus
| CoreCLR
| Simulator
| MacABI
deriving (Environment -> Environment -> Bool
(Environment -> Environment -> Bool)
-> (Environment -> Environment -> Bool) -> Eq Environment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Environment -> Environment -> Bool
== :: Environment -> Environment -> Bool
$c/= :: Environment -> Environment -> Bool
/= :: Environment -> Environment -> Bool
Eq, Eq Environment
Eq Environment
-> (Environment -> Environment -> Ordering)
-> (Environment -> Environment -> Bool)
-> (Environment -> Environment -> Bool)
-> (Environment -> Environment -> Bool)
-> (Environment -> Environment -> Bool)
-> (Environment -> Environment -> Environment)
-> (Environment -> Environment -> Environment)
-> Ord Environment
Environment -> Environment -> Bool
Environment -> Environment -> Ordering
Environment -> Environment -> Environment
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
$ccompare :: Environment -> Environment -> Ordering
compare :: Environment -> Environment -> Ordering
$c< :: Environment -> Environment -> Bool
< :: Environment -> Environment -> Bool
$c<= :: Environment -> Environment -> Bool
<= :: Environment -> Environment -> Bool
$c> :: Environment -> Environment -> Bool
> :: Environment -> Environment -> Bool
$c>= :: Environment -> Environment -> Bool
>= :: Environment -> Environment -> Bool
$cmax :: Environment -> Environment -> Environment
max :: Environment -> Environment -> Environment
$cmin :: Environment -> Environment -> Environment
min :: Environment -> Environment -> Environment
Ord, Int -> Environment -> ShowS
[Environment] -> ShowS
Environment -> String
(Int -> Environment -> ShowS)
-> (Environment -> String)
-> ([Environment] -> ShowS)
-> Show Environment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Environment -> ShowS
showsPrec :: Int -> Environment -> ShowS
$cshow :: Environment -> String
show :: Environment -> String
$cshowList :: [Environment] -> ShowS
showList :: [Environment] -> ShowS
Show)
data ObjectFormat
= UnknownObjectFormat
| COFF
| ELF
| GOFF
| MachO
| Wasm
| XCOFF
deriving (ObjectFormat -> ObjectFormat -> Bool
(ObjectFormat -> ObjectFormat -> Bool)
-> (ObjectFormat -> ObjectFormat -> Bool) -> Eq ObjectFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectFormat -> ObjectFormat -> Bool
== :: ObjectFormat -> ObjectFormat -> Bool
$c/= :: ObjectFormat -> ObjectFormat -> Bool
/= :: ObjectFormat -> ObjectFormat -> Bool
Eq, Eq ObjectFormat
Eq ObjectFormat
-> (ObjectFormat -> ObjectFormat -> Ordering)
-> (ObjectFormat -> ObjectFormat -> Bool)
-> (ObjectFormat -> ObjectFormat -> Bool)
-> (ObjectFormat -> ObjectFormat -> Bool)
-> (ObjectFormat -> ObjectFormat -> Bool)
-> (ObjectFormat -> ObjectFormat -> ObjectFormat)
-> (ObjectFormat -> ObjectFormat -> ObjectFormat)
-> Ord ObjectFormat
ObjectFormat -> ObjectFormat -> Bool
ObjectFormat -> ObjectFormat -> Ordering
ObjectFormat -> ObjectFormat -> ObjectFormat
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
$ccompare :: ObjectFormat -> ObjectFormat -> Ordering
compare :: ObjectFormat -> ObjectFormat -> Ordering
$c< :: ObjectFormat -> ObjectFormat -> Bool
< :: ObjectFormat -> ObjectFormat -> Bool
$c<= :: ObjectFormat -> ObjectFormat -> Bool
<= :: ObjectFormat -> ObjectFormat -> Bool
$c> :: ObjectFormat -> ObjectFormat -> Bool
> :: ObjectFormat -> ObjectFormat -> Bool
$c>= :: ObjectFormat -> ObjectFormat -> Bool
>= :: ObjectFormat -> ObjectFormat -> Bool
$cmax :: ObjectFormat -> ObjectFormat -> ObjectFormat
max :: ObjectFormat -> ObjectFormat -> ObjectFormat
$cmin :: ObjectFormat -> ObjectFormat -> ObjectFormat
min :: ObjectFormat -> ObjectFormat -> ObjectFormat
Ord, Int -> ObjectFormat -> ShowS
[ObjectFormat] -> ShowS
ObjectFormat -> String
(Int -> ObjectFormat -> ShowS)
-> (ObjectFormat -> String)
-> ([ObjectFormat] -> ShowS)
-> Show ObjectFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectFormat -> ShowS
showsPrec :: Int -> ObjectFormat -> ShowS
$cshow :: ObjectFormat -> String
show :: ObjectFormat -> String
$cshowList :: [ObjectFormat] -> ShowS
showList :: [ObjectFormat] -> ShowS
Show)
data Triple = Triple {
Triple -> Architecture
architecture :: Architecture,
Triple -> SubArchitecture
subarchitecture :: SubArchitecture,
Triple -> OS
os :: OS,
Triple -> Vendor
vendor :: Vendor,
Triple -> Environment
environment :: Environment,
Triple -> ObjectFormat
objectFormat :: ObjectFormat
} deriving (Triple -> Triple -> Bool
(Triple -> Triple -> Bool)
-> (Triple -> Triple -> Bool) -> Eq Triple
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Triple -> Triple -> Bool
== :: Triple -> Triple -> Bool
$c/= :: Triple -> Triple -> Bool
/= :: Triple -> Triple -> Bool
Eq, Eq Triple
Eq Triple
-> (Triple -> Triple -> Ordering)
-> (Triple -> Triple -> Bool)
-> (Triple -> Triple -> Bool)
-> (Triple -> Triple -> Bool)
-> (Triple -> Triple -> Bool)
-> (Triple -> Triple -> Triple)
-> (Triple -> Triple -> Triple)
-> Ord Triple
Triple -> Triple -> Bool
Triple -> Triple -> Ordering
Triple -> Triple -> Triple
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
$ccompare :: Triple -> Triple -> Ordering
compare :: Triple -> Triple -> Ordering
$c< :: Triple -> Triple -> Bool
< :: Triple -> Triple -> Bool
$c<= :: Triple -> Triple -> Bool
<= :: Triple -> Triple -> Bool
$c> :: Triple -> Triple -> Bool
> :: Triple -> Triple -> Bool
$c>= :: Triple -> Triple -> Bool
>= :: Triple -> Triple -> Bool
$cmax :: Triple -> Triple -> Triple
max :: Triple -> Triple -> Triple
$cmin :: Triple -> Triple -> Triple
min :: Triple -> Triple -> Triple
Ord, Int -> Triple -> ShowS
[Triple] -> ShowS
Triple -> String
(Int -> Triple -> ShowS)
-> (Triple -> String) -> ([Triple] -> ShowS) -> Show Triple
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Triple -> ShowS
showsPrec :: Int -> Triple -> ShowS
$cshow :: Triple -> String
show :: Triple -> String
$cshowList :: [Triple] -> ShowS
showList :: [Triple] -> ShowS
Show)
unknownTriple :: Triple
unknownTriple :: Triple
unknownTriple = Triple {
architecture :: Architecture
architecture = Architecture
UnknownArch,
subarchitecture :: SubArchitecture
subarchitecture = SubArchitecture
NoSubArch,
vendor :: Vendor
vendor = Vendor
UnknownVendor,
os :: OS
os = OS
UnknownOS,
environment :: Environment
environment = Environment
UnknownEnvironment,
objectFormat :: ObjectFormat
objectFormat = ObjectFormat
UnknownObjectFormat
}
invertBijection :: (Ord k, Ord v) => Map k v -> Map v k
invertBijection :: forall k v. (Ord k, Ord v) => Map k v -> Map v k
invertBijection = (k -> v -> Map v k -> Map v k) -> Map v k -> Map k v -> Map v k
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
Map.foldrWithKey ((v -> k -> Map v k -> Map v k) -> k -> v -> Map v k -> Map v k
forall a b c. (a -> b -> c) -> b -> a -> c
flip v -> k -> Map v k -> Map v k
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert) Map v k
forall k a. Map k a
Map.empty
architectureFromStringMap :: Map String Architecture
architectureFromStringMap :: Map String Architecture
architectureFromStringMap = [(String, Architecture)] -> Map String Architecture
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String
"unknown", Architecture
UnknownArch),
(String
"arm", Architecture
Arm),
(String
"armeb", Architecture
Armeb),
(String
"aarch64", Architecture
Aarch64),
(String
"aarch64_be", Architecture
Aarch64_be),
(String
"aarch64_32", Architecture
Aarch64_32),
(String
"arc", Architecture
Arc),
(String
"avr", Architecture
Avr),
(String
"bpfel", Architecture
Bpfel),
(String
"bpfeb", Architecture
Bpfeb),
(String
"csky", Architecture
Csky),
(String
"hexagon", Architecture
Hexagon),
(String
"mips", Architecture
Mips),
(String
"mipsel", Architecture
Mipsel),
(String
"mips64", Architecture
Mips64),
(String
"mips64el", Architecture
Mips64el),
(String
"msp430", Architecture
Msp430),
(String
"ppc", Architecture
Ppc),
(String
"ppcle", Architecture
Ppcle),
(String
"ppc64", Architecture
Ppc64),
(String
"ppc64le", Architecture
Ppc64le),
(String
"r600", Architecture
R600),
(String
"amdgcn", Architecture
Amdgcn),
(String
"riscv32", Architecture
Riscv32),
(String
"riscv64", Architecture
Riscv64),
(String
"sparc", Architecture
Sparc),
(String
"sparcv9", Architecture
Sparcv9),
(String
"sparcel", Architecture
Sparcel),
(String
"systemz", Architecture
Systemz),
(String
"tce", Architecture
Tce),
(String
"tcele", Architecture
Tcele),
(String
"thumb", Architecture
Thumb),
(String
"thumbeb", Architecture
Thumbeb),
(String
"x86", Architecture
X86),
(String
"x86_64", Architecture
X86_64),
(String
"xcore", Architecture
Xcore),
(String
"nvptx", Architecture
Nvptx),
(String
"nvptx64", Architecture
Nvptx64),
(String
"le32", Architecture
Le32),
(String
"le64", Architecture
Le64),
(String
"amdil", Architecture
Amdil),
(String
"amdil64", Architecture
Amdil64),
(String
"hsail", Architecture
Hsail),
(String
"hsail64", Architecture
Hsail64),
(String
"spir", Architecture
Spir),
(String
"spir64", Architecture
Spir64),
(String
"kalimba", Architecture
Kalimba),
(String
"shave", Architecture
Shave),
(String
"lanai", Architecture
Lanai),
(String
"wasm32", Architecture
Wasm32),
(String
"wasm64", Architecture
Wasm64),
(String
"renderscript32", Architecture
Renderscript32),
(String
"renderscript64", Architecture
Renderscript64),
(String
"ve", Architecture
Ve)
]
architectureToStringMap :: Map Architecture String
architectureToStringMap :: Map Architecture String
architectureToStringMap = Map String Architecture -> Map Architecture String
forall k v. (Ord k, Ord v) => Map k v -> Map v k
invertBijection Map String Architecture
architectureFromStringMap
vendorFromStringMap :: Map String Vendor
vendorFromStringMap :: Map String Vendor
vendorFromStringMap = [(String, Vendor)] -> Map String Vendor
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String
"apple" , Vendor
Apple ),
(String
"pc" , Vendor
PC ),
(String
"scei" , Vendor
SCEI ),
(String
"freescale" , Vendor
Freescale ),
(String
"ibm" , Vendor
IBM ),
(String
"imaginationtechnologies", Vendor
ImaginationTechnologies),
(String
"mipstechnologies" , Vendor
MipsTechnologies ),
(String
"nvidia" , Vendor
NVIDIA ),
(String
"csr" , Vendor
CSR ),
(String
"myriad" , Vendor
Myriad ),
(String
"amd" , Vendor
AMD ),
(String
"mesa" , Vendor
Mesa ),
(String
"suse" , Vendor
SUSE ),
(String
"openembedded" , Vendor
OpenEmbedded )
]
vendorToStringMap :: Map Vendor String
vendorToStringMap :: Map Vendor String
vendorToStringMap = Map String Vendor -> Map Vendor String
forall k v. (Ord k, Ord v) => Map k v -> Map v k
invertBijection Map String Vendor
vendorFromStringMap
osFromStringMap :: Map String OS
osFromStringMap :: Map String OS
osFromStringMap = [(String, OS)] -> Map String OS
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String
"ananas" , OS
Ananas ),
(String
"cloudabi" , OS
CloudABI ),
(String
"darwin" , OS
Darwin ),
(String
"dragonfly" , OS
DragonFly ),
(String
"freebsd" , OS
FreeBSD ),
(String
"fuchsia" , OS
Fuchsia ),
(String
"ios" , OS
IOS ),
(String
"kfreebsd" , OS
KFreeBSD ),
(String
"linux" , OS
Linux ),
(String
"lv2" , OS
Lv2 ),
(String
"macosx" , OS
MacOSX ),
(String
"netbsd" , OS
NetBSD ),
(String
"openbsd" , OS
OpenBSD ),
(String
"solaris" , OS
Solaris ),
(String
"win32" , OS
Win32 ),
(String
"zos" , OS
ZOS ),
(String
"haiku" , OS
Haiku ),
(String
"minix" , OS
Minix ),
(String
"rtems" , OS
RTEMS ),
(String
"nacl" , OS
NaCl ),
(String
"aix" , OS
AIX ),
(String
"cuda" , OS
CUDA ),
(String
"nvcl" , OS
NVCL ),
(String
"amdhsa" , OS
AMDHSA ),
(String
"ps4" , OS
PS4 ),
(String
"elfiamcu" , OS
ELFIAMCU ),
(String
"tvos" , OS
TvOS ),
(String
"watchos" , OS
WatchOS ),
(String
"mesa3d" , OS
Mesa3D ),
(String
"contiki" , OS
Contiki ),
(String
"amdpal" , OS
AMDPAL ),
(String
"hermitcore", OS
HermitCore),
(String
"hurd" , OS
Hurd ),
(String
"wasi" , OS
WASI ),
(String
"emscripten", OS
Emscripten)
]
osToStringMap :: Map OS String
osToStringMap :: Map OS String
osToStringMap = Map String OS -> Map OS String
forall k v. (Ord k, Ord v) => Map k v -> Map v k
invertBijection Map String OS
osFromStringMap
tripleToString :: Triple -> ShortByteString
tripleToString :: Triple -> ShortByteString
tripleToString Triple {ObjectFormat
Environment
OS
Vendor
SubArchitecture
Architecture
architecture :: Triple -> Architecture
subarchitecture :: Triple -> SubArchitecture
os :: Triple -> OS
vendor :: Triple -> Vendor
environment :: Triple -> Environment
objectFormat :: Triple -> ObjectFormat
architecture :: Architecture
subarchitecture :: SubArchitecture
os :: OS
vendor :: Vendor
environment :: Environment
objectFormat :: ObjectFormat
..} =
ByteString -> ShortByteString
toShort (ByteString -> ShortByteString) -> ByteString -> ShortByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString] -> ByteString
ByteString.intercalate (String -> ByteString
pack String
"-") [
String -> ByteString
pack (Map Architecture String
architectureToStringMap Map Architecture String -> Architecture -> String
forall k a. Ord k => Map k a -> k -> a
! Architecture
architecture),
String -> ByteString
pack (Map Vendor String
vendorToStringMap Map Vendor String -> Vendor -> String
forall k a. Ord k => Map k a -> k -> a
! Vendor
vendor),
String -> ByteString
pack (Map OS String
osToStringMap Map OS String -> OS -> String
forall k a. Ord k => Map k a -> k -> a
! OS
os)
]
parseTriple :: ShortByteString -> Except String Triple
parseTriple :: ShortByteString -> Except String Triple
parseTriple ShortByteString
triple = do
let
tripleStr :: ByteString
tripleStr = ShortByteString -> ByteString
fromShort ShortByteString
triple
parseSpec :: Parser (Triple -> Triple)
parseSpec :: Parser (Triple -> Triple)
parseSpec = [Parser (Triple -> Triple)] -> Parser (Triple -> Triple)
forall (f :: * -> *) a. Alternative f => [f a] -> f a
choice [
do
Architecture
arch <- [Parser ByteString Architecture] -> Parser ByteString Architecture
forall (f :: * -> *) a. Alternative f => [f a] -> f a
choice [ByteString -> Parser ByteString
string (String -> ByteString
pack String
s) Parser ByteString -> Architecture -> Parser ByteString Architecture
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Architecture
a | (String
s, Architecture
a) <- Map String Architecture -> [(String, Architecture)]
forall k a. Map k a -> [(k, a)]
Map.toList Map String Architecture
architectureFromStringMap]
(Triple -> Triple) -> Parser (Triple -> Triple)
forall a. a -> Parser ByteString a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Triple -> Triple) -> Parser (Triple -> Triple))
-> (Triple -> Triple) -> Parser (Triple -> Triple)
forall a b. (a -> b) -> a -> b
$ \Triple
t -> Triple
t { architecture :: Architecture
architecture = Architecture
arch },
do
Vendor
vendor <- [Parser ByteString Vendor] -> Parser ByteString Vendor
forall (f :: * -> *) a. Alternative f => [f a] -> f a
choice [ByteString -> Parser ByteString
string (String -> ByteString
pack String
s) Parser ByteString -> Vendor -> Parser ByteString Vendor
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Vendor
v | (String
s, Vendor
v) <- Map String Vendor -> [(String, Vendor)]
forall k a. Map k a -> [(k, a)]
Map.toList Map String Vendor
vendorFromStringMap]
(Triple -> Triple) -> Parser (Triple -> Triple)
forall a. a -> Parser ByteString a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Triple -> Triple) -> Parser (Triple -> Triple))
-> (Triple -> Triple) -> Parser (Triple -> Triple)
forall a b. (a -> b) -> a -> b
$ \Triple
t -> Triple
t { vendor :: Vendor
vendor = Vendor
vendor },
do
OS
os <- [Parser ByteString OS] -> Parser ByteString OS
forall (f :: * -> *) a. Alternative f => [f a] -> f a
choice [ByteString -> Parser ByteString
string (String -> ByteString
pack String
s) Parser ByteString -> OS -> Parser ByteString OS
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> OS
o | (String
s, OS
o) <- Map String OS -> [(String, OS)]
forall k a. Map k a -> [(k, a)]
Map.toList Map String OS
osFromStringMap]
(Triple -> Triple) -> Parser (Triple -> Triple)
forall a. a -> Parser ByteString a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Triple -> Triple) -> Parser (Triple -> Triple))
-> (Triple -> Triple) -> Parser (Triple -> Triple)
forall a b. (a -> b) -> a -> b
$ \Triple
t -> Triple
t { os :: OS
os = OS
os }
]
in
case Parser [Triple -> Triple]
-> ByteString -> Either String [Triple -> Triple]
forall a. Parser a -> ByteString -> Either String a
parseOnly (Parser (Triple -> Triple)
parseSpec Parser (Triple -> Triple)
-> Parser ByteString Char -> Parser [Triple -> Triple]
forall (f :: * -> *) a s. Alternative f => f a -> f s -> f [a]
`sepBy` Char -> Parser ByteString Char
char Char
'-') ByteString
tripleStr of
Left String
_ -> String -> Except String Triple
forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE (String -> Except String Triple) -> String -> Except String Triple
forall a b. (a -> b) -> a -> b
$ String
"ill-formed triple: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show ByteString
tripleStr
Right [Triple -> Triple]
fs -> Triple -> Except String Triple
forall a. a -> ExceptT String Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Triple -> Except String Triple) -> Triple -> Except String Triple
forall a b. (a -> b) -> a -> b
$ ((Triple -> Triple) -> Triple -> Triple)
-> Triple -> [Triple -> Triple] -> Triple
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Triple -> Triple) -> Triple -> Triple
forall a b. (a -> b) -> a -> b
($) Triple
unknownTriple [Triple -> Triple]
fs