Skip to content

Commit ae41a73

Browse files
committed
copilot: Update struct examples to use generic method implementations. Refs #564.
Currently, using structs in Copilot requires defining instances of several type classes. Defining those instances is unnecessarily cumbersome, and it exposes the user to a substantial amount of Haskell even when they want to stay at the level of the Copilot language. In a previous commit, we added `Generic`-based defaults for the methods of the `Struct` and `Typed` classes. In this commit, we leverage these default implementations to remove much of the boilerplate code needed to define `Struct` and `Typed` instances in the struct-related `copilot` examples. Note that I have intentionally _not_ used `updateFieldDefault` in the `StructsUpdateField.hs` example, as that example is intended to demonstrate how one would implement `updateField` by hand. This work is based off of an initial implementation by Marten Wijnja (@Qqwy).
1 parent 428209e commit ae41a73

File tree

3 files changed

+62
-66
lines changed

3 files changed

+62
-66
lines changed

copilot/examples/Structs.hs

Lines changed: 19 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -1,28 +1,29 @@
11
-- | An example showing how specifications involving structs (in particular,
22
-- nested structs) are compiled to C using copilot-c99.
33

4-
{-# LANGUAGE DataKinds #-}
4+
{-# LANGUAGE DataKinds #-}
5+
{-# LANGUAGE DeriveGeneric #-}
56

67
module Main where
78

89
import qualified Prelude as P
910
import Control.Monad (void, forM_)
11+
import GHC.Generics (Generic)
1012

1113
import Language.Copilot
1214
import Copilot.Compile.C99
1315

1416
-- | Definition for `Volts`.
1517
data Volts = Volts
16-
{ numVolts :: Field "numVolts" Word16
17-
, flag :: Field "flag" Bool
18-
}
18+
{ numVolts :: Field "numVolts" Word16
19+
, flag :: Field "flag" Bool
20+
}
21+
deriving Generic
1922

2023
-- | `Struct` instance for `Volts`.
2124
instance Struct Volts where
22-
typeName _ = "volts"
23-
toValues volts = [ Value Word16 (numVolts volts)
24-
, Value Bool (flag volts)
25-
]
25+
typeName = typeNameDefault
26+
toValues = toValuesDefault
2627
-- Note that we do not implement `updateField` here. `updateField` is only
2728
-- needed to make updates to structs work in the Copilot interpreter, and we
2829
-- do not use the interpreter in this example. (See
@@ -31,29 +32,25 @@ instance Struct Volts where
3132

3233
-- | `Volts` instance for `Typed`.
3334
instance Typed Volts where
34-
typeOf = Struct (Volts (Field 0) (Field False))
35+
typeOf = typeOfDefault
3536

3637
data Battery = Battery
37-
{ temp :: Field "temp" Word16
38-
, volts :: Field "volts" (Array 10 Volts)
39-
, other :: Field "other" (Array 10 (Array 5 Word32))
40-
}
38+
{ temp :: Field "temp" Word16
39+
, volts :: Field "volts" (Array 10 Volts)
40+
, other :: Field "other" (Array 10 (Array 5 Word32))
41+
}
42+
deriving Generic
4143

4244
-- | `Battery` instance for `Struct`.
4345
instance Struct Battery where
44-
typeName _ = "battery"
45-
toValues battery = [ Value typeOf (temp battery)
46-
, Value typeOf (volts battery)
47-
, Value typeOf (other battery)
48-
]
46+
typeName = typeNameDefault
47+
toValues = toValuesDefault
4948
-- Note that we do not implement `updateField` here for the same reasons as in
5049
-- the `Struct Volts` instance above.
5150

52-
-- | `Battery` instance for `Typed`. Note that `undefined` is used as an
53-
-- argument to `Field`. This argument is never used, so `undefined` will never
54-
-- throw an error.
51+
-- | `Battery` instance for `Typed`.
5552
instance Typed Battery where
56-
typeOf = Struct (Battery (Field 0) (Field undefined) (Field undefined))
53+
typeOf = typeOfDefault
5754

5855
spec :: Spec
5956
spec = do

copilot/examples/StructsUpdateField.hs

Lines changed: 24 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
-- copilot-c99.
44

55
{-# LANGUAGE DataKinds #-}
6+
{-# LANGUAGE DeriveGeneric #-}
67
{-# LANGUAGE GADTs #-}
78
{-# LANGUAGE ScopedTypeVariables #-}
89
{-# LANGUAGE TypeApplications #-}
@@ -13,27 +14,30 @@ import qualified Prelude as P
1314
import Control.Monad (void, forM_)
1415
import Data.Proxy (Proxy(..))
1516
import Data.Type.Equality (TestEquality(..), (:~:)(..))
17+
import GHC.Generics (Generic)
1618
import GHC.TypeLits (sameSymbol)
1719

1820
import Language.Copilot
1921
import Copilot.Compile.C99
2022

2123
-- | Definition for `Volts`.
2224
data Volts = Volts
23-
{ numVolts :: Field "numVolts" Word16
24-
, flag :: Field "flag" Bool
25-
}
25+
{ numVolts :: Field "numVolts" Word16
26+
, flag :: Field "flag" Bool
27+
}
28+
deriving Generic
2629

2730
-- | `Struct` instance for `Volts`.
2831
instance Struct Volts where
29-
typeName _ = "volts"
30-
toValues volts = [ Value Word16 (numVolts volts)
31-
, Value Bool (flag volts)
32-
]
32+
typeName = typeNameDefault
33+
toValues = toValuesDefault
3334
-- In order to run struct updates (as used in the "equalityStructUpdate"
3435
-- trigger below) in the Copilot interpreter, we must implement the
3536
-- `updateField` method. To do so, we must check to see if the supplied
3637
-- `Value` has a `Field` with the same name and type as a field in `Volts`.
38+
-- (Alternatively, we could define this as @updateField = updateFieldDefault@,
39+
-- but we demonstrate how to manually implement it below for educational
40+
-- purposes.)
3741
updateField volts (Value fieldTy (field :: Field fieldName a))
3842
-- For each field in `Volts`, we must:
3943
--
@@ -67,23 +71,23 @@ instance Struct Volts where
6771

6872
-- | `Volts` instance for `Typed`.
6973
instance Typed Volts where
70-
typeOf = Struct (Volts (Field 0) (Field False))
74+
typeOf = typeOfDefault
7175

7276
data Battery = Battery
73-
{ temp :: Field "temp" Word16
74-
, volts :: Field "volts" (Array 10 Volts)
75-
, other :: Field "other" (Array 10 (Array 5 Word32))
76-
}
77+
{ temp :: Field "temp" Word16
78+
, volts :: Field "volts" (Array 10 Volts)
79+
, other :: Field "other" (Array 10 (Array 5 Word32))
80+
}
81+
deriving Generic
7782

7883
-- | `Battery` instance for `Struct`.
7984
instance Struct Battery where
80-
typeName _ = "battery"
81-
toValues battery = [ Value typeOf (temp battery)
82-
, Value typeOf (volts battery)
83-
, Value typeOf (other battery)
84-
]
85+
typeName = typeNameDefault
86+
toValues = toValuesDefault
8587
-- We implement `updateField` similarly to how we implement it in the
86-
-- `Struct Volts` instance above.
88+
-- `Struct Volts` instance above. (Alternatively, we could define this as
89+
-- @updateField = updateFieldDefault@, but we demonstrate how to manually
90+
-- implement it below for educational purposes.)
8791
updateField battery (Value fieldTy (field :: Field fieldName a))
8892
| Just Refl <- sameSymbol (Proxy @fieldName) (Proxy @"temp")
8993
, Just Refl <- testEquality fieldTy Word16
@@ -103,11 +107,9 @@ instance Struct Battery where
103107
| otherwise
104108
= error $ "Unexpected field: " P.++ show field
105109

106-
-- | `Battery` instance for `Typed`. Note that `undefined` is used as an
107-
-- argument to `Field`. This argument is never used, so `undefined` will never
108-
-- throw an error.
110+
-- | `Battery` instance for `Typed`.
109111
instance Typed Battery where
110-
typeOf = Struct (Battery (Field 0) (Field undefined) (Field undefined))
112+
typeOf = typeOfDefault
111113

112114
spec :: Spec
113115
spec = do

copilot/examples/what4/Structs.hs

Lines changed: 19 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -2,28 +2,29 @@
22
-- structs and arrays. Particular focus is on nested structs.
33
-- For general usage of structs, refer to the general structs example.
44

5-
{-# LANGUAGE DataKinds #-}
5+
{-# LANGUAGE DataKinds #-}
6+
{-# LANGUAGE DeriveGeneric #-}
67

78
module Main where
89

910
import qualified Prelude as P
1011
import Control.Monad (void, forM_)
12+
import GHC.Generics (Generic)
1113

1214
import Language.Copilot
1315
import Copilot.Theorem.What4
1416

1517
-- | Definition for `Volts`.
1618
data Volts = Volts
17-
{ numVolts :: Field "numVolts" Word16
18-
, flag :: Field "flag" Bool
19-
}
19+
{ numVolts :: Field "numVolts" Word16
20+
, flag :: Field "flag" Bool
21+
}
22+
deriving Generic
2023

2124
-- | `Struct` instance for `Volts`.
2225
instance Struct Volts where
23-
typeName _ = "volts"
24-
toValues volts = [ Value Word16 (numVolts volts)
25-
, Value Bool (flag volts)
26-
]
26+
typeName = typeNameDefault
27+
toValues = toValuesDefault
2728
-- Note that we do not implement `updateField` here. `updateField` is only
2829
-- needed to make updates to structs work in the Copilot interpreter, and we
2930
-- do not use the interpreter in this example. (See
@@ -32,29 +33,25 @@ instance Struct Volts where
3233

3334
-- | `Volts` instance for `Typed`.
3435
instance Typed Volts where
35-
typeOf = Struct (Volts (Field 0) (Field False))
36+
typeOf = typeOfDefault
3637

3738
data Battery = Battery
38-
{ temp :: Field "temp" Word16
39-
, volts :: Field "volts" (Array 10 Volts)
40-
, other :: Field "other" (Array 10 (Array 5 Word32))
41-
}
39+
{ temp :: Field "temp" Word16
40+
, volts :: Field "volts" (Array 10 Volts)
41+
, other :: Field "other" (Array 10 (Array 5 Word32))
42+
}
43+
deriving Generic
4244

4345
-- | `Battery` instance for `Struct`.
4446
instance Struct Battery where
45-
typeName _ = "battery"
46-
toValues battery = [ Value typeOf (temp battery)
47-
, Value typeOf (volts battery)
48-
, Value typeOf (other battery)
49-
]
47+
typeName = typeNameDefault
48+
toValues = toValuesDefault
5049
-- Note that we do not implement `updateField` here for the same reasons as in
5150
-- the `Struct Volts` instance above.
5251

53-
-- | `Battery` instance for `Typed`. Note that `undefined` is used as an
54-
-- argument to `Field`. This argument is never used, so `undefined` will never
55-
-- throw an error.
52+
-- | `Battery` instance for `Typed`.
5653
instance Typed Battery where
57-
typeOf = Struct (Battery (Field 0) (Field undefined) (Field undefined))
54+
typeOf = typeOfDefault
5855

5956
spec :: Spec
6057
spec = do

0 commit comments

Comments
 (0)