8
8
{-# LANGUAGE ScopedTypeVariables #-}
9
9
{-# LANGUAGE TypeOperators #-}
10
10
{-# LANGUAGE UndecidableInstances #-}
11
+ {-# LANGUAGE DefaultSignatures #-}
12
+ {-# LANGUAGE TypeApplications #-}
13
+ {-# LANGUAGE TypeFamilies #-}
11
14
-- |
12
15
-- Description: Typing for Core.
13
16
-- Copyright: (c) 2011 National Institute of Aerospace / Galois, Inc.
@@ -47,6 +50,8 @@ import Data.Word (Word16, Word32, Word64, Word8)
47
50
import GHC.TypeLits (KnownNat , KnownSymbol , Symbol , natVal , sameNat ,
48
51
symbolVal )
49
52
53
+ import GHC.Generics
54
+
50
55
-- Internal imports
51
56
import Copilot.Core.Type.Array (Array )
52
57
@@ -58,6 +63,32 @@ class Struct a where
58
63
59
64
-- | Transforms all the struct's fields into a list of values.
60
65
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)
61
92
62
93
-- | The field of a struct, together with a representation of its type.
63
94
data Value a =
@@ -190,6 +221,9 @@ instance Eq SimpleType where
190
221
class (Show a , Typeable a ) => Typed a where
191
222
typeOf :: Type a
192
223
simpleType :: Type a -> SimpleType
224
+
225
+ instance {-# OVERLAPPABLE #-} (Show a , Typeable a , Struct a ) => Typed a where
226
+ typeOf = Struct undefined
193
227
simpleType _ = SStruct
194
228
195
229
instance Typed Bool where
0 commit comments