Skip to content

Commit 8c63a4e

Browse files
Merge branch 'develop-update-arrays'. Close #36.
**Description** Copilot currently supports reading values from streams of arrays, but not changing them. We'd like to be able to modify an array by adjusting the value at a specific position. **Type** - Feature: new extension to the language. **Additional context** None. **Requester** - Ivan Perez **Method to check presence of bug** No applicable (not a bug). **Expected result** Copilot provides a mechanism to update elements in an array. The following Dockerfile installs copilot and runs a file with struct update operations, which it then links and compares against its expected output, printing the message "Success" if the output matches the expectation: ``` --- Dockerfile FROM ubuntu:focal ENV DEBIAN_FRONTEND=noninteractive RUN apt-get update RUN apt-get install --yes libz-dev RUN apt-get install --yes git RUN apt-get install --yes wget RUN mkdir -p $HOME/.ghcup/bin RUN wget https://downloads.haskell.org/~ghcup/0.1.19.2/x86_64-linux-ghcup-0.1.19.2 -O $HOME/.ghcup/bin/ghcup RUN chmod a+x $HOME/.ghcup/bin/ghcup ENV PATH=$PATH:/root/.ghcup/bin/ ENV PATH=$PATH:/root/.cabal/bin/ RUN apt-get install --yes curl RUN apt-get install --yes gcc g++ make libgmp3-dev RUN apt-get install --yes pkg-config SHELL ["/bin/bash", "-c"] RUN ghcup install ghc 9.4 RUN ghcup install cabal 3.2 RUN ghcup set ghc 9.4.8 RUN cabal update ADD Arrays.hs /tmp/Arrays.hs ADD main.c /tmp/main.c ADD expected /tmp/expected CMD git clone $REPO \ && cd $NAME \ && git checkout $COMMIT \ && cabal v1-sandbox init \ && cabal v1-install alex happy \ && cabal v1-install copilot**/ \ && cabal v1-exec -- runhaskell /tmp/Arrays.hs \ && mv /tmp/main.c . \ && gcc main.c arrays.c -o main \ && ./main > actual \ && diff actual /tmp/expected \ && echo Success --- Arrays.hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-} module Main (main) where import Copilot.Compile.C99 import Data.Type.Equality as DE import Language.Copilot -- Sample values arr :: Stream (Array 2 Float) arr = [ array [1.0, 2.5] , array [2.5, 1.0] ] ++ arr arr1 = (arr !! 1 =$ (+1)) !! 0 =$ (+100) arr2 = arr1 !! 1 =$ ([0.0] ++) spec :: Spec spec = do trigger "arrays" true [arg arr2] main :: IO () main = do spec' <- reify spec compile "arrays" spec' --- main.c #include <stdio.h> #include <stdlib.h> #include <stdint.h> #include "arrays.h" #include "arrays_types.h" void arrays( float* arrays_arg0 ) { printf("%f %f\n" , arrays_arg0[0] , arrays_arg0[1]); } int main() { step(); step(); step(); step(); } --- expected 101.000000 0.000000 102.500000 3.500000 101.000000 2.000000 102.500000 3.500000 ``` Command (substitute variables based on new path after merge): ``` $ docker run -e "REPO=https://github.com/Copilot-Language/copilot" -e "NAME=copilot" -e "COMMIT=<HASH>" -it copilot-verify-36 ``` **Solution implemented** Extend `copilot-language` to provide operations to modify values of arrays in streams, with a syntax that is uniform for structs and arrays. Extend `copilot-core`, `copilot-c99`, `copilot-theorem`, `copilot-interpreter` and `copilot-prettyprinter` as needed. Provide examples that demonstrate the new features. Provide (!) alternative to (.!!) to make syntax uniform. Adjust examples to use (!). Hide (!!) in copilot-libraries, and provide an alternative (!!!). **Further notes** None.
2 parents 6ea0338 + 191a75f commit 8c63a4e

File tree

24 files changed

+420
-86
lines changed

24 files changed

+420
-86
lines changed

copilot-c99/CHANGELOG

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,6 @@
1+
2024-09-03
2+
* Add support for array updates. (#36)
3+
14
2024-07-07
25
* Version bump (3.20). (#522)
36
* Add support for struct field updates. (#520)

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

Lines changed: 46 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -13,9 +13,9 @@ import qualified Data.List.NonEmpty as NonEmpty
1313
import qualified Language.C99.Simple as C
1414

1515
-- Internal imports: Copilot
16-
import Copilot.Core ( Expr (..), Field (..), Op1 (..), Op2 (..), Op3 (..),
17-
Type (..), Value (..), accessorName, arrayElems,
18-
toValues, typeSize )
16+
import Copilot.Core ( Array, Expr (..), Field (..), Op1 (..), Op2 (..),
17+
Op3 (..), Type (..), Value (..), accessorName,
18+
arrayElems, toValues, typeLength, typeSize )
1919

2020
-- Internal imports
2121
import Copilot.Compile.C99.Error ( impossible )
@@ -101,6 +101,47 @@ transExpr (Op2 op e1 e2) = do
101101
e2' <- transExpr e2
102102
return $ transOp2 op e1' e2'
103103

104+
transExpr e@(Op3 (UpdateArray arrTy@(Array ty2)) e1 e2 e3) = do
105+
e1' <- transExpr e1
106+
e2' <- transExpr e2
107+
e3' <- transExpr e3
108+
109+
-- Variable to hold the updated array
110+
(i, _, _) <- get
111+
let varName = "_v" ++ show i
112+
modify (\(i, x, y) -> (i + 1, x, y))
113+
114+
-- Add new var decl
115+
let initDecl = C.VarDecln Nothing cTy1 varName Nothing
116+
cTy1 = transType arrTy
117+
modify (\(i, x, y) -> (i, x ++ [initDecl], y))
118+
119+
let size :: Type (Array n t) -> C.Expr
120+
size arrTy@(Array ty) = C.LitInt (fromIntegral $ typeLength arrTy)
121+
C..* C.SizeOfType (C.TypeName $ transType ty)
122+
123+
-- Initialize the var to the same value as the original array
124+
let initStmt = C.Expr $ memcpy (C.Ident varName) e1' (size arrTy)
125+
126+
-- Update element of array
127+
let updateStmt = case ty2 of
128+
Array _ -> C.Expr $ memcpy dest e3' size
129+
where
130+
dest = C.Index (C.Ident varName) e2'
131+
size = C.LitInt
132+
(fromIntegral $ typeSize ty2)
133+
C..* C.SizeOfType (C.TypeName (tyElemName ty2))
134+
135+
_ -> C.Expr
136+
$ C.AssignOp
137+
C.Assign
138+
(C.Index (C.Ident varName) e2')
139+
e3'
140+
141+
modify (\(i, x, y) -> (i, x, y ++ [ initStmt, updateStmt ]))
142+
143+
return $ C.Ident varName
144+
104145
transExpr (Op3 op e1 e2 e3) = do
105146
e1' <- transExpr e1
106147
e2' <- transExpr e2
@@ -179,7 +220,8 @@ transOp2 op e1 e2 = case op of
179220
-- expression.
180221
transOp3 :: Op3 a b c d -> C.Expr -> C.Expr -> C.Expr -> C.Expr
181222
transOp3 op e1 e2 e3 = case op of
182-
Mux _ -> C.Cond e1 e2 e3
223+
Mux _ -> C.Cond e1 e2 e3
224+
UpdateArray _ -> impossible "transOp3" "copilot-c99"
183225

184226
-- | Translate @'Abs' e@ in Copilot Core into a C99 expression.
185227
--

copilot-core/CHANGELOG

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,6 @@
1+
2024-09-03
2+
* Update Op3, Array to support array updates. (#36)
3+
14
2024-07-07
25
* Version bump (3.20). (#522)
36
* Update Op2, Struct to support struct field updates. (#520)

copilot-core/src/Copilot/Core/Operators.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -106,3 +106,6 @@ data Op2 a b c where
106106
data Op3 a b c d where
107107
-- Conditional operator.
108108
Mux :: Type a -> Op3 Bool a a a
109+
-- Array operator.
110+
UpdateArray :: Type (Array n t) -> Op3 (Array n t) Word32 t (Array n t)
111+
-- ^ Update an element of an array.

copilot-core/src/Copilot/Core/Type/Array.hs

Lines changed: 21 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE Safe #-}
44
{-# LANGUAGE ScopedTypeVariables #-}
55
{-# LANGUAGE TypeFamilies #-}
6+
{-# LANGUAGE TypeOperators #-}
67

78
-- |
89
-- Copyright: (c) 2011 National Institute of Aerospace / Galois, Inc.
@@ -14,12 +15,13 @@ module Copilot.Core.Type.Array
1415
( Array
1516
, array
1617
, arrayElems
18+
, arrayUpdate
1719
)
1820
where
1921

2022
-- External imports
2123
import Data.Proxy (Proxy (..))
22-
import GHC.TypeLits (KnownNat, Nat, natVal)
24+
import GHC.TypeLits (KnownNat, Nat, natVal, type(-))
2325

2426
-- | Implementation of an array that uses type literals to store length.
2527
data Array (n :: Nat) t where
@@ -42,3 +44,21 @@ array xs | datalen == typelen = Array xs
4244
-- | Return the elements of an array.
4345
arrayElems :: Array n a -> [a]
4446
arrayElems (Array xs) = xs
47+
48+
-- | Update element of array to given element.
49+
--
50+
-- PRE: the second argument denotes a valid index in the array.
51+
arrayUpdate :: Array n a -> Int -> a -> Array n a
52+
arrayUpdate (Array []) _ _ = error errMsg
53+
where
54+
errMsg = "copilot-core: arrayUpdate: Attempt to update empty array"
55+
56+
arrayUpdate (Array (x:xs)) 0 y = Array (y:xs)
57+
58+
arrayUpdate (Array (x:xs)) n y =
59+
arrayAppend x (arrayUpdate (Array xs) (n - 1) y)
60+
where
61+
-- | Append to an array while preserving length information at the type
62+
-- level.
63+
arrayAppend :: a -> Array (n - 1) a -> Array n a
64+
arrayAppend x (Array xs) = Array (x:xs)

copilot-interpreter/CHANGELOG

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,6 @@
1+
2024-09-03
2+
* Add support for array updates. (#36)
3+
14
2024-07-07
25
* Version bump (3.20). (#522)
36
* Add support for struct field updates. (#520)

copilot-interpreter/src/Copilot/Interpret/Eval.hs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -19,8 +19,8 @@ module Copilot.Interpret.Eval
1919
import Copilot.Core (Expr (..), Field (..), Id, Name, Observer (..),
2020
Op1 (..), Op2 (..), Op3 (..), Spec, Stream (..),
2121
Trigger (..), Type (..), UExpr (..), Value (..),
22-
arrayElems, specObservers, specStreams,
23-
specTriggers, updateField)
22+
arrayElems, arrayUpdate, specObservers,
23+
specStreams, specTriggers, updateField)
2424
import Copilot.Interpret.Error (badUsage)
2525

2626
import Prelude hiding (id)
@@ -32,6 +32,7 @@ import Data.Dynamic (Dynamic, fromDynamic, toDyn)
3232
import Data.List (transpose)
3333
import Data.Maybe (fromJust)
3434
import Data.Typeable (Typeable)
35+
import GHC.TypeLits (KnownNat, Nat, natVal)
3536

3637
-- | Exceptions that may be thrown during interpretation of a Copilot
3738
-- specification.
@@ -265,7 +266,8 @@ catchZero f x y = f x y
265266
-- Haskell function operating on the same types as the
266267
-- 'Copilot.Core.Operators.Op3'.
267268
evalOp3 :: Op3 a b c d -> (a -> b -> c -> d)
268-
evalOp3 (Mux _) = \ !v !x !y -> if v then x else y
269+
evalOp3 (Mux _) = \ !v !x !y -> if v then x else y
270+
evalOp3 (UpdateArray ty) = \xs n x -> arrayUpdate xs (fromIntegral n) x
269271

270272
-- | Turn a stream into a key-value pair that can be added to an 'Env' for
271273
-- simulation.

copilot-language/CHANGELOG

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,6 @@
1+
2024-09-03
2+
* Add support for array updates. (#36)
3+
14
2024-07-07
25
* Version bump (3.20). (#522)
36
* Remove deprecated function Copilot.Language.Spec.forall. (#518)

copilot-language/copilot-language.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -61,6 +61,7 @@ library
6161
, Copilot.Language.Operators.Ord
6262
, Copilot.Language.Operators.Temporal
6363
, Copilot.Language.Operators.Array
64+
, Copilot.Language.Operators.Projection
6465
, Copilot.Language.Operators.Struct
6566
, Copilot.Language.Prelude
6667
, Copilot.Language.Reify
Lines changed: 72 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,29 +1,89 @@
1-
{-# LANGUAGE Safe #-}
2-
3-
{-# LANGUAGE TypeFamilies #-}
1+
{-# LANGUAGE FlexibleInstances #-}
2+
{-# LANGUAGE MultiParamTypeClasses #-}
3+
{-# LANGUAGE Safe #-}
4+
{-# LANGUAGE TypeFamilies #-}
5+
-- The following warning is disabled due to a necessary instance of Projectable
6+
-- defined in this module.
7+
{-# OPTIONS_GHC -fno-warn-orphans #-}
48

59
-- | Combinators to deal with streams carrying arrays.
610
module Copilot.Language.Operators.Array
711
( (.!!)
12+
, (!)
13+
, (!!)
14+
, (=:)
15+
, (=$)
816
) where
917

10-
import Copilot.Core ( Typed
11-
, Op2 (Index)
12-
, typeOf
13-
, Array
14-
)
15-
import Copilot.Language.Stream (Stream (..))
18+
import Copilot.Core (Array, Op2 (Index),
19+
Op3 (UpdateArray), Typed, typeOf)
20+
import Copilot.Language.Operators.Projection (Projectable(..))
21+
import Copilot.Language.Stream (Stream (..))
22+
23+
import Data.Word (Word32)
24+
import GHC.TypeLits (KnownNat)
25+
import Prelude hiding ((!!))
1626

17-
import Data.Word (Word32)
18-
import GHC.TypeLits (KnownNat)
27+
-- | Create a stream that carries an element of an array in another stream.
28+
--
29+
-- This function implements a projection of the element of an array at a given
30+
-- position, over time. For example, if @s@ is a stream of type @Stream (Array
31+
-- '5 Word8)@, then @s ! 3@ has type @Stream Word8@ and contains the 3rd
32+
-- element (starting from zero) of the arrays in @s@ at any point in time.
33+
(!) :: (KnownNat n, Typed t)
34+
=> Stream (Array n t) -> Stream Word32 -> Stream t
35+
arr ! n = Op2 (Index typeOf) arr n
1936

2037
-- | Create a stream that carries an element of an array in another stream.
2138
--
2239
-- This function implements a projection of the element of an array at a given
2340
-- position, over time. For example, if @s@ is a stream of type @Stream (Array
2441
-- '5 Word8)@, then @s .!! 3@ has type @Stream Word8@ and contains the 3rd
2542
-- element (starting from zero) of the arrays in @s@ at any point in time.
43+
{-# DEPRECATED (.!!) "This function is deprecated in Copilot 4. Use (!)." #-}
2644
(.!!) :: ( KnownNat n
2745
, Typed t
2846
) => Stream (Array n t) -> Stream Word32 -> Stream t
29-
arr .!! n = Op2 (Index typeOf) arr n
47+
(.!!) = (!)
48+
49+
-- | Pair a stream with an element accessor, without applying it to obtain the
50+
-- value of the element.
51+
--
52+
-- This function is needed to refer to an element accessor when the goal is to
53+
-- update the element value, not just to read it.
54+
(!!) :: Stream (Array n t)
55+
-> Stream Word32
56+
-> Projection (Array n t) (Stream Word32) t
57+
(!!) = ProjectionA
58+
59+
-- | Update a stream of arrays.
60+
61+
-- This is an orphan instance; we suppress the warning that GHC would
62+
-- normally produce with a GHC option at the top.
63+
instance (KnownNat n, Typed t) => Projectable (Array n t) (Stream Word32) t where
64+
65+
-- | A projection of an element of a stream of arrays.
66+
data Projection (Array n t) (Stream Word32) t =
67+
ProjectionA (Stream (Array n t)) (Stream Word32)
68+
69+
-- | Create a stream where an element of an array has been updated with
70+
-- values from another stream.
71+
--
72+
-- For example, if an array has two elements of type @Int32@, and @s@ is a
73+
-- stream of such array type (@Stream (Array 2 Int32)@), and $v0$ is a stream
74+
-- of type @Int32@, then @s !! 0 =: v0@ has type @Stream (Array 2 Int32)@ and
75+
-- contains arrays where the value of the first element of each array is that
76+
-- of @v0@ at each point in time, and the value of the second element in the
77+
-- array is the same it had in @s@.
78+
(=:) (ProjectionA s ix) v = Op3 (UpdateArray typeOf) s ix v
79+
80+
-- | Create a stream where an element of an array has been updated by
81+
-- applying a stream function to it.
82+
--
83+
-- For example, if an array has two elements of type @Int32@, and @s@ is a
84+
-- stream of such array type (@Stream (Array 2 Int32)@), and $f$ is function
85+
-- of type @Stream Int32 -> Stream Int32@, then @s !! 0 =$ f@ has type
86+
-- @Stream (Array 2 Int32)@ and contains arrays where the value of the first
87+
-- element of each array is that of @f (s ! 0)@ at each point in time, and
88+
-- the value of the second element in the array is the same it had in @s@.
89+
(=$) (ProjectionA s ix) op = Op3 (UpdateArray typeOf) s ix (op (s ! ix))

0 commit comments

Comments
 (0)