summaryrefslogtreecommitdiff
path: root/libraries/ghc-boot/GHC/Platform/ArchOS.hs
blob: 4aa42baa3b84b8241d64821e6aa738a20c6d5c7e (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
{-# LANGUAGE LambdaCase, ScopedTypeVariables #-}

-- | Platform architecture and OS
--
-- We need it in ghc-boot because ghc-pkg needs it.
module GHC.Platform.ArchOS
   ( ArchOS(..)
   , Arch(..)
   , OS(..)
   , ArmISA(..)
   , ArmISAExt(..)
   , ArmABI(..)
   , PPC_64ABI(..)
   , stringEncodeArch
   , stringEncodeOS
   )
where

import Prelude -- See Note [Why do we import Prelude here?]

-- | Platform architecture and OS.
data ArchOS
   = ArchOS
      { archOS_arch :: Arch
      , archOS_OS   :: OS
      }
   deriving (Read, Show, Eq, Ord)

-- | Architectures
--
-- TODO: It might be nice to extend these constructors with information about
-- what instruction set extensions an architecture might support.
--
data Arch
   = ArchUnknown
   | ArchX86
   | ArchX86_64
   | ArchPPC
   | ArchPPC_64 PPC_64ABI
   | ArchS390X
   | ArchARM ArmISA [ArmISAExt] ArmABI
   | ArchAArch64
   | ArchAlpha
   | ArchMipseb
   | ArchMipsel
   | ArchRISCV64
   | ArchLoongArch64
   | ArchJavaScript
   | ArchWasm32
   deriving (Read, Show, Eq, Ord)

-- | ARM Instruction Set Architecture
data ArmISA
   = ARMv5
   | ARMv6
   | ARMv7
   deriving (Read, Show, Eq, Ord)

-- | ARM extensions
data ArmISAExt
   = VFPv2
   | VFPv3
   | VFPv3D16
   | NEON
   | IWMMX2
   deriving (Read, Show, Eq, Ord)

-- | ARM ABI
data ArmABI
   = SOFT
   | SOFTFP
   | HARD
   deriving (Read, Show, Eq, Ord)

-- | PowerPC 64-bit ABI
data PPC_64ABI
   = ELF_V1 -- ^ PowerPC64
   | ELF_V2 -- ^ PowerPC64 LE
   deriving (Read, Show, Eq, Ord)

-- | Operating systems.
--
-- Using OSUnknown to generate code should produce a sensible default, but no
-- promises.
data OS
   = OSUnknown
   | OSLinux
   | OSDarwin
   | OSSolaris2
   | OSMinGW32
   | OSFreeBSD
   | OSDragonFly
   | OSOpenBSD
   | OSNetBSD
   | OSKFreeBSD
   | OSHaiku
   | OSQNXNTO
   | OSAIX
   | OSHurd
   | OSWasi
   | OSGhcjs
   deriving (Read, Show, Eq, Ord)


-- Note [Platform Syntax]
-- ~~~~~~~~~~~~~~~~~~~~~~
--
-- There is a very loose encoding of platforms shared by many tools we are
-- encoding to here. GNU Config (http://git.savannah.gnu.org/cgit/config.git),
-- and LLVM's http://llvm.org/doxygen/classllvm_1_1Triple.html are perhaps the
-- most definitional parsers. The basic syntax is a list of '-'-separated
-- components. The Unix 'uname' command syntax is related but briefer.
--
-- Those two parsers are quite forgiving, and even the 'config.sub'
-- normalization is forgiving too. The "best" way to encode a platform is
-- therefore somewhat a matter of taste.
--
-- The 'stringEncode*' functions here convert each part of GHC's structured
-- notion of a platform into one dash-separated component.

-- | See Note [Platform Syntax].
stringEncodeArch :: Arch -> String
stringEncodeArch = \case
  ArchUnknown       -> "unknown"
  ArchX86           -> "i386"
  ArchX86_64        -> "x86_64"
  ArchPPC           -> "powerpc"
  ArchPPC_64 ELF_V1 -> "powerpc64"
  ArchPPC_64 ELF_V2 -> "powerpc64le"
  ArchS390X         -> "s390x"
  ArchARM ARMv5 _ _ -> "armv5"
  ArchARM ARMv6 _ _ -> "armv6"
  ArchARM ARMv7 _ _ -> "armv7"
  ArchAArch64       -> "aarch64"
  ArchAlpha         -> "alpha"
  ArchMipseb        -> "mipseb"
  ArchMipsel        -> "mipsel"
  ArchRISCV64       -> "riscv64"
  ArchLoongArch64   -> "loongarch64"
  ArchJavaScript    -> "javascript"
  ArchWasm32        -> "wasm32"

-- | See Note [Platform Syntax].
stringEncodeOS :: OS -> String
stringEncodeOS = \case
  OSUnknown   -> "unknown"
  OSLinux     -> "linux"
  OSDarwin    -> "darwin"
  OSSolaris2  -> "solaris2"
  OSMinGW32   -> "mingw32"
  OSFreeBSD   -> "freebsd"
  OSDragonFly -> "dragonfly"
  OSOpenBSD   -> "openbsd"
  OSNetBSD    -> "netbsd"
  OSKFreeBSD  -> "kfreebsdgnu"
  OSHaiku     -> "haiku"
  OSQNXNTO    -> "nto-qnx"
  OSAIX       -> "aix"
  OSHurd      -> "hurd"
  OSWasi      -> "wasi"
  OSGhcjs     -> "ghcjs"