Skip to content

Commit b05e9be

Browse files
committed
An example default implementation of Struct based on GHC.Generics
1 parent 9e4b1cb commit b05e9be

File tree

2 files changed

+41
-17
lines changed

2 files changed

+41
-17
lines changed

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

Lines changed: 34 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,9 @@
88
{-# LANGUAGE ScopedTypeVariables #-}
99
{-# LANGUAGE TypeOperators #-}
1010
{-# LANGUAGE UndecidableInstances #-}
11+
{-# LANGUAGE DefaultSignatures #-}
12+
{-# LANGUAGE TypeApplications #-}
13+
{-# LANGUAGE TypeFamilies #-}
1114
-- |
1215
-- Description: Typing for Core.
1316
-- Copyright: (c) 2011 National Institute of Aerospace / Galois, Inc.
@@ -47,6 +50,8 @@ import Data.Word (Word16, Word32, Word64, Word8)
4750
import GHC.TypeLits (KnownNat, KnownSymbol, Symbol, natVal, sameNat,
4851
symbolVal)
4952

53+
import GHC.Generics
54+
5055
-- Internal imports
5156
import Copilot.Core.Type.Array (Array)
5257

@@ -58,6 +63,32 @@ class Struct a where
5863

5964
-- | Transforms all the struct's fields into a list of values.
6065
toValues :: a -> [Value a]
66+
default toValues :: (Generic a, GStruct (Rep a)) => a -> [Value a]
67+
toValues x = coerceValuePhantom <$> gToValues (from x)
68+
69+
class GStruct f where
70+
gToValues :: f p -> [Value (f p)]
71+
72+
instance GStruct U1 where
73+
-- A unit-like type has no fields, so its values list is empty
74+
gToValues U1 = []
75+
76+
instance (GStruct f) => GStruct (M1 _i _t f) where
77+
-- Generics Metadata is not used by this typeclass
78+
-- we are only interested in its contents
79+
gToValues (M1 x) = coerceValuePhantom <$> gToValues x
80+
81+
instance (Typed ty, KnownSymbol name) => GStruct (K1 i (Field name ty)) where
82+
-- Base case for each contained field
83+
gToValues (K1 field) = [Value typeOf field]
84+
85+
instance (GStruct f, GStruct g) => GStruct (f :*: g) where
86+
-- Product types (structs) contain the fields of all their elements
87+
gToValues (f :*: g) = (coerceValuePhantom <$> (gToValues f)) ++ (coerceValuePhantom <$> (gToValues g))
88+
89+
-- Turn one Value into another, changing its phantom type
90+
coerceValuePhantom :: forall a b. Value a -> Value b
91+
coerceValuePhantom (Value t v) = (Value t v)
6192

6293
-- | The field of a struct, together with a representation of its type.
6394
data Value a =
@@ -190,6 +221,9 @@ instance Eq SimpleType where
190221
class (Show a, Typeable a) => Typed a where
191222
typeOf :: Type a
192223
simpleType :: Type a -> SimpleType
224+
225+
instance {-# OVERLAPPABLE #-} (Show a, Typeable a, Struct a) => Typed a where
226+
typeOf = Struct undefined
193227
simpleType _ = SStruct
194228

195229
instance Typed Bool where

copilot/examples/Structs.hs

Lines changed: 7 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
-- nested structs) are compiled to C using copilot-c99.
33

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

67
module Main where
78

@@ -11,42 +12,31 @@ import Control.Monad (void, forM_)
1112
import Language.Copilot
1213
import Copilot.Compile.C99
1314

15+
import GHC.Generics
16+
1417
-- | Definition for `Volts`.
1518
data Volts = Volts
1619
{ numVolts :: Field "numVolts" Word16
1720
, flag :: Field "flag" Bool
1821
}
22+
deriving Generic
1923

2024
-- | `Struct` instance for `Volts`.
25+
-- toValues is automatically implemented using Generic
26+
-- Also, no need to manually implement `Typed` is necessary.
2127
instance Struct Volts where
2228
typeName _ = "volts"
23-
toValues volts = [ Value Word16 (numVolts volts)
24-
, Value Bool (flag volts)
25-
]
26-
27-
-- | `Volts` instance for `Typed`.
28-
instance Typed Volts where
29-
typeOf = Struct (Volts (Field 0) (Field False))
3029

3130
data Battery = Battery
3231
{ temp :: Field "temp" Word16
3332
, volts :: Field "volts" (Array 10 Volts)
3433
, other :: Field "other" (Array 10 (Array 5 Word32))
3534
}
35+
deriving Generic
3636

3737
-- | `Battery` instance for `Struct`.
3838
instance Struct Battery where
3939
typeName _ = "battery"
40-
toValues battery = [ Value typeOf (temp battery)
41-
, Value typeOf (volts battery)
42-
, Value typeOf (other battery)
43-
]
44-
45-
-- | `Battery` instance for `Typed`. Note that `undefined` is used as an
46-
-- argument to `Field`. This argument is never used, so `undefined` will never
47-
-- throw an error.
48-
instance Typed Battery where
49-
typeOf = Struct (Battery (Field 0) (Field undefined) (Field undefined))
5040

5141
spec :: Spec
5242
spec = do

0 commit comments

Comments
 (0)