Skip to content

Commit 05868c8

Browse files
fdeddenivanperez-keera
authored andcommitted
copilot-c99: Adapt to work with language-c99-simple >= 0.2. Refs #371.
The new (0.2) version of the language-c99-simple library now requires constructing some non-empty list with a dedicated value constructor (NonEmpty) as opposed to using Haskell lists. This change was made to better fit the C99 standard. This makes the current copilot-c99 code not compile with the new version of the library. This commit adapts copilot-c99 so that the new value constructor NonEmpty is used where required.
1 parent 80fec5f commit 05868c8

File tree

2 files changed

+22
-16
lines changed

2 files changed

+22
-16
lines changed

copilot-c99/src/Copilot/Compile/C99/CodeGen.hs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -4,9 +4,10 @@
44
-- | High-level translation of Copilot Core into C99.
55
module Copilot.Compile.C99.CodeGen where
66

7-
import Control.Monad.State (runState)
8-
import Data.List (union, unzip4)
9-
import Data.Typeable (Typeable)
7+
import Control.Monad.State (runState)
8+
import Data.List (union, unzip4)
9+
import qualified Data.List.NonEmpty as NonEmpty
10+
import Data.Typeable (Typeable)
1011

1112
import qualified Language.C99.Simple as C
1213

@@ -50,7 +51,7 @@ mkbuffdecln sid ty xs = C.VarDecln (Just C.Static) cty name initvals
5051
name = streamname sid
5152
cty = C.Array (transtype ty) (Just $ C.LitInt $ fromIntegral buffsize)
5253
buffsize = length xs
53-
initvals = Just $ C.InitArray $ constarray ty xs
54+
initvals = Just $ C.InitList $ constarray ty xs
5455

5556
-- | Make a C index variable and initialise it to 0.
5657
mkindexdecln :: Id -> C.Decln
@@ -224,7 +225,7 @@ mkstructdecln :: Struct a => Type a -> C.Decln
224225
mkstructdecln (Struct x) = C.TypeDecln struct
225226
where
226227
struct = C.TypeSpec $ C.StructDecln (Just $ typename x) fields
227-
fields = map mkfield (toValues x)
228+
fields = NonEmpty.fromList $ map mkfield (toValues x)
228229

229230
mkfield :: Value a -> C.FieldDecln
230231
mkfield (Value ty field) = C.FieldDecln (transtype ty) (fieldname field)

copilot-c99/src/Copilot/Compile/C99/Translate.hs

Lines changed: 16 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,8 @@
33
-- | Translate Copilot Core expressions and operators to C99.
44
module Copilot.Compile.C99.Translate where
55

6-
import Control.Monad.State
6+
import Control.Monad.State
7+
import qualified Data.List.NonEmpty as NonEmpty
78

89
import Copilot.Core
910
import Copilot.Compile.C99.Error (impossible)
@@ -226,7 +227,7 @@ constty ty = case ty of
226227
Float -> explicitty ty . C.LitFloat
227228
Double -> explicitty ty . C.LitDouble
228229
Struct _ -> \v ->
229-
C.InitVal (transtypename ty) (map constfieldinit (toValues v))
230+
C.InitVal (transtypename ty) (constStruct (toValues v))
230231
Array ty' -> \v ->
231232
C.InitVal (transtypename ty) (constarray ty' (arrayelems v))
232233

@@ -254,26 +255,30 @@ constinit ty val = case ty of
254255
-- whole expression as an array of two int32_t's (as opposed to a nested
255256
-- array). This can either lead to compile-time errors (if you're lucky) or
256257
-- 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
258259

259260
-- We use InitArray to initialize a struct because the syntax used for
260261
-- initializing arrays and structs is compatible. For instance, {1, 2} works
261262
-- both for initializing an int array of length 2 as well as a struct with
262263
-- 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)
267266
_ -> C.InitExpr $ constty ty val
268267

269268
-- | 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
272276

273277
-- | Transform a Copilot Array, based on the element values and their type,
274278
-- 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)
277282

278283
-- | Explicitly cast a C99 value to a type.
279284
explicitty :: Type a -> C.Expr -> C.Expr

0 commit comments

Comments
 (0)