|
3 | 3 | -- | Translate Copilot Core expressions and operators to C99.
|
4 | 4 | module Copilot.Compile.C99.Translate where
|
5 | 5 |
|
6 |
| -import Control.Monad.State |
| 6 | +import Control.Monad.State |
| 7 | +import qualified Data.List.NonEmpty as NonEmpty |
7 | 8 |
|
8 | 9 | import Copilot.Core
|
9 | 10 | import Copilot.Compile.C99.Error (impossible)
|
@@ -226,7 +227,7 @@ constty ty = case ty of
|
226 | 227 | Float -> explicitty ty . C.LitFloat
|
227 | 228 | Double -> explicitty ty . C.LitDouble
|
228 | 229 | Struct _ -> \v ->
|
229 |
| - C.InitVal (transtypename ty) (map constfieldinit (toValues v)) |
| 230 | + C.InitVal (transtypename ty) (constStruct (toValues v)) |
230 | 231 | Array ty' -> \v ->
|
231 | 232 | C.InitVal (transtypename ty) (constarray ty' (arrayelems v))
|
232 | 233 |
|
@@ -254,26 +255,30 @@ constinit ty val = case ty of
|
254 | 255 | -- whole expression as an array of two int32_t's (as opposed to a nested
|
255 | 256 | -- array). This can either lead to compile-time errors (if you're lucky) or
|
256 | 257 | -- incorrect runtime semantics (if you're unlucky).
|
257 |
| - Array ty' -> C.InitArray $ constarray ty' $ arrayelems val |
| 258 | + Array ty' -> C.InitList $ constarray ty' $ arrayelems val |
258 | 259 |
|
259 | 260 | -- We use InitArray to initialize a struct because the syntax used for
|
260 | 261 | -- initializing arrays and structs is compatible. For instance, {1, 2} works
|
261 | 262 | -- both for initializing an int array of length 2 as well as a struct with
|
262 | 263 | -- two int fields, although the two expressions are conceptually different
|
263 |
| - -- (structs can also be initialized as { .a = 1, .b = 2}, but language-c99 |
264 |
| - -- does not support such syntax and does not provide a specialized |
265 |
| - -- initialization construct for structs). |
266 |
| - Struct _ -> C.InitArray $ map constfieldinit $ toValues val |
| 264 | + -- (structs can also be initialized as { .a = 1, .b = 2}. |
| 265 | + Struct _ -> C.InitList $ constStruct (toValues val) |
267 | 266 | _ -> C.InitExpr $ constty ty val
|
268 | 267 |
|
269 | 268 | -- | Transform a Copilot Core struct field into a C99 initializer.
|
270 |
| -constfieldinit :: Value a -> C.Init |
271 |
| -constfieldinit (Value ty (Field val)) = constinit ty val |
| 269 | +constfieldinit :: Value a -> C.InitItem |
| 270 | +constfieldinit (Value ty (Field val)) = C.InitItem Nothing $ constinit ty val |
| 271 | + |
| 272 | +-- | Transform a Copilot Struct, based on the struct fields, into a list of C99 |
| 273 | +-- initializer values. |
| 274 | +constStruct :: [Value a] -> NonEmpty.NonEmpty C.InitItem |
| 275 | +constStruct val = NonEmpty.fromList $ map constfieldinit val |
272 | 276 |
|
273 | 277 | -- | Transform a Copilot Array, based on the element values and their type,
|
274 | 278 | -- into a list of C99 initializer values.
|
275 |
| -constarray :: Type a -> [a] -> [C.Init] |
276 |
| -constarray ty = map (constinit ty) |
| 279 | +constarray :: Type a -> [a] -> NonEmpty.NonEmpty C.InitItem |
| 280 | +constarray ty = |
| 281 | + NonEmpty.fromList . map (C.InitItem Nothing . constinit ty) |
277 | 282 |
|
278 | 283 | -- | Explicitly cast a C99 value to a type.
|
279 | 284 | explicitty :: Type a -> C.Expr -> C.Expr
|
|
0 commit comments