Skip to content

Commit f553d4e

Browse files
committed
Generics, take 2
This commit adds an alternative attempt at generics. It has both advantages and disadvantages. The principal advantage is that it really allows generics to work with HuddleM - see the example in example/Monad.hs for a demonstration. The previous way of writing this was quite horrible. There are two main disadvantages: - Now, rather than treating a generic function as a regular Haskell function, we have to treat it specially and call it with the special syntax (<--). - Only one generic parameter is supported. We can potentially fix this, but it's always going to play unkindly with the (<--) syntax. That having been said, we had only implemented up to two parameters before. For these reasons, these new-style generics are currently implemented alongside the existing ones for consideration.
1 parent 4e70e44 commit f553d4e

File tree

4 files changed

+139
-25
lines changed

4 files changed

+139
-25
lines changed

example/Monad.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ spec = huddleDef $ mdo
1919
"transaction"
2020
=:= mp
2121
[ idx 0 ==> set txIn,
22-
idx 1 ==> set txOut
22+
idx 1 ==> set' <-- txOut
2323
]
2424
txIn <- "txIn" =:= arr ["transaction_id" ==> hash32, "index" ==> txId]
2525
txOut <- "txOut" =:= arr [idx 0 ==> address, idx 1 ==> value]
@@ -28,6 +28,7 @@ spec = huddleDef $ mdo
2828
hash32 <- "hash32" =:= VBytes `sized` (32 :: Word64)
2929
value <- "value" =:= VUInt
3030
set <- include hdl_set
31+
set' <- binding' $ \x -> "set'" Huddle.=:= arr [0 <+ a x]
3132

3233
setRootRules [transaction]
3334

@@ -36,14 +37,14 @@ spec2 =
3637
spec
3738
<> huddleDef
3839
( mdo
39-
set <- include hdl_set
40+
set <- unsafeIncludeFromHuddle spec "set'"
4041
txIn <- unsafeIncludeFromHuddle spec "txIn"
4142
txOut <- unsafeIncludeFromHuddle spec "txOut"
4243
_transaction <-
4344
"transaction"
4445
=:= mp
45-
[ comment "Transaction inputs" $ idx 0 ==> set txIn,
46-
comment "Transaction outputs" $ idx 1 ==> set txOut,
46+
[ comment "Transaction inputs" $ idx 0 ==> set <-- txIn,
47+
comment "Transaction outputs" $ idx 1 ==> set <-- txOut,
4748
comment "Metadata" $ idx 2 ==> metadata
4849
]
4950
metadata <- "metadata" =:= VBytes

src/Codec/CBOR/Cuddle/Huddle.hs

Lines changed: 107 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@
88
{-# LANGUAGE TypeApplications #-}
99
{-# LANGUAGE TypeFamilies #-}
1010
{-# LANGUAGE UndecidableInstances #-}
11+
{-# LANGUAGE ViewPatterns #-}
1112
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
1213

1314
-- | Module for building CDDL in Haskell
@@ -76,10 +77,15 @@ module Codec.CBOR.Cuddle.Huddle
7677
-- * Generics
7778
GRef,
7879
GRuleDef,
80+
GRuleDef',
7981
GRuleCall,
82+
GRuleCall',
8083
binding,
8184
binding2,
85+
binding',
8286
callToDef,
87+
callToDef',
88+
(<--),
8389

8490
-- * Conversion to CDDL
8591
collectFrom,
@@ -91,6 +97,7 @@ where
9197
import Codec.CBOR.Cuddle.CDDL (CDDL)
9298
import Codec.CBOR.Cuddle.CDDL qualified as C
9399
import Codec.CBOR.Cuddle.CDDL.CtlOp qualified as CtlOp
100+
import Codec.CBOR.Cuddle.Huddle.Generic (FnWithArg (..), result)
94101
import Control.Monad (when)
95102
import Control.Monad.State (MonadState (get), execState, modify)
96103
import Data.ByteString (ByteString)
@@ -128,6 +135,7 @@ type Rule = Named Type0
128135
data HuddleItem
129136
= HIRule Rule
130137
| HIGRule GRuleDef
138+
| HIGRule' GRuleDef'
131139
| HIGroup (Named Group)
132140
deriving (Generic, Show)
133141

@@ -273,6 +281,7 @@ data Type2
273281
| T2Group (Named Group)
274282
| -- | Call to a generic rule, binding arguments
275283
T2Generic GRuleCall
284+
| T2Generic' GRuleCall'
276285
| -- | Reference to a generic parameter within the body of the definition
277286
T2GenericRef GRef
278287
deriving (Show)
@@ -433,7 +442,7 @@ class IsSize a where
433442

434443
instance IsSize Word where
435444
sizeAsCDDL = C.T2Value . C.VUInt . fromIntegral
436-
sizeAsString = show
445+
sizeAsString = show
437446

438447
instance IsSize Word64 where
439448
sizeAsCDDL = C.T2Value . C.VUInt
@@ -474,10 +483,13 @@ sized v sz =
474483
}
475484
[]
476485

477-
class IsCborable a
478-
instance IsCborable ByteString
479-
instance IsCborable CRef
480-
instance IsCborable CGRef
486+
class IsCborable a
487+
488+
instance IsCborable ByteString
489+
490+
instance IsCborable CRef
491+
492+
instance IsCborable CGRef
481493

482494
cbor :: (IsCborable b, IsConstrainable c b) => c -> Rule -> Constrained
483495
cbor v r@(Named n _ _) =
@@ -492,9 +504,12 @@ cbor v r@(Named n _ _) =
492504
}
493505
[r]
494506

495-
class IsComparable a
496-
instance IsComparable Int
497-
instance IsComparable CRef
507+
class IsComparable a
508+
509+
instance IsComparable Int
510+
511+
instance IsComparable CRef
512+
498513
instance IsComparable CGRef
499514

500515
le :: (IsComparable a, IsConstrainable c a) => c -> Word64 -> Constrained
@@ -512,16 +527,16 @@ le v bound =
512527

513528
-- Ranges
514529

515-
data RangeBound =
516-
RangeBoundLiteral Literal
517-
| RangeBoundRef (Named Type0)
518-
deriving Show
530+
data RangeBound
531+
= RangeBoundLiteral Literal
532+
| RangeBoundRef (Named Type0)
533+
deriving (Show)
519534

520535
class IsRangeBound a where
521-
toRangeBound :: a -> RangeBound
536+
toRangeBound :: a -> RangeBound
522537

523538
instance IsRangeBound Literal where
524-
toRangeBound = RangeBoundLiteral
539+
toRangeBound = RangeBoundLiteral
525540

526541
instance IsRangeBound Integer where
527542
toRangeBound = RangeBoundLiteral . inferInteger
@@ -605,6 +620,9 @@ instance IsType0 (Named Group) where
605620
instance IsType0 GRuleCall where
606621
toType0 = NoChoice . T2Generic
607622

623+
instance IsType0 GRuleCall' where
624+
toType0 = NoChoice . T2Generic'
625+
608626
instance IsType0 GRef where
609627
toType0 = NoChoice . T2GenericRef
610628

@@ -617,6 +635,9 @@ instance IsType0 HuddleItem where
617635
toType0 (HIGRule g) =
618636
error $
619637
"Attempt to reference generic rule from HuddleItem not supported: " <> show g
638+
toType0 (HIGRule' g) =
639+
error $
640+
"Attempt to reference generic rule from HuddleItem not supported: " <> show g
620641

621642
class CanQuantify a where
622643
-- | Apply a lower bound
@@ -933,6 +954,53 @@ binding2 fRule t0 t1 =
933954
NoChoice x -> x
934955
_ -> error "Cannot use a choice of types as a generic argument"
935956

957+
--------------------------------------------------------------------------------
958+
-- Generics (Take 2)
959+
--------------------------------------------------------------------------------
960+
961+
type GRuleDef' = Named (FnWithArg GRef Type0)
962+
963+
data GRuleCallAux = GRuleCallAux
964+
{ defFn :: FnWithArg GRef Type0,
965+
callArg :: Type2
966+
}
967+
968+
type GRuleCall' = Named GRuleCallAux
969+
970+
binding' :: (GRef -> Rule) -> GRuleDef'
971+
binding' fRule =
972+
Named
973+
(getField @"name" $ result defFn)
974+
(getField @"value" <$> defFn)
975+
Nothing
976+
where
977+
defFn = FnWithArg fRule (freshName 0)
978+
979+
class IsGRuleDef f where
980+
toGRuleDef :: f -> GRuleDef'
981+
982+
instance IsGRuleDef GRuleDef' where
983+
toGRuleDef = id
984+
985+
instance IsGRuleDef HuddleItem where
986+
toGRuleDef (HIGRule' gd) = gd
987+
toGRuleDef _ = error "Attempt to use a non-generic rule as a GRuleDef"
988+
989+
(<--) :: (IsType0 t0, IsGRuleDef gd) => gd -> t0 -> GRuleCall'
990+
(toGRuleDef -> f) <-- t0 = fmap toCall f
991+
where
992+
toCall rd =
993+
GRuleCallAux
994+
{ defFn = rd,
995+
callArg = t2
996+
}
997+
t2 = case toType0 t0 of
998+
NoChoice x -> x
999+
_ -> error "Cannot use a choice of types as a generic argument"
1000+
1001+
callToDef' :: GRuleCall' -> GRuleDef'
1002+
callToDef' (Named n r c) = Named n (defFn r) c
1003+
9361004
--------------------------------------------------------------------------------
9371005
-- Collecting all top-level rules
9381006
--------------------------------------------------------------------------------
@@ -960,7 +1028,7 @@ collectFrom topRs =
9601028
goChoice f (NoChoice x) = f x
9611029
goChoice f (ChoiceOf x xs) = f x >> goChoice f xs
9621030
goT0 = goChoice goT2
963-
goT2 (T2Range r) = goRanged r
1031+
goT2 (T2Range r) = goRanged r
9641032
goT2 (T2Map m) = goChoice (mapM_ goMapEntry . unMapChoice) m
9651033
goT2 (T2Array m) = goChoice (mapM_ goArrayEntry . unArrayChoice) m
9661034
goT2 (T2Tagged (Tagged _ t0)) = goT0 t0
@@ -993,10 +1061,10 @@ collectFrom topRs =
9931061
goKey _ = pure ()
9941062
goGroup (Group g) = mapM_ goArrayEntry g
9951063
goRanged (Unranged _) = pure ()
996-
goRanged (Ranged lb ub _) = goRangeBound lb >> goRangeBound ub
1064+
goRanged (Ranged lb ub _) = goRangeBound lb >> goRangeBound ub
9971065
goRangeBound (RangeBoundLiteral _) = pure ()
9981066
goRangeBound (RangeBoundRef r) = goRule r
999-
1067+
10001068
--------------------------------------------------------------------------------
10011069
-- Conversion to CDDL
10021070
--------------------------------------------------------------------------------
@@ -1022,6 +1090,7 @@ toCDDL' mkPseudoRoot hdl =
10221090
toCDDLItem (HIRule r) = toCDDLRule r
10231091
toCDDLItem (HIGroup g) = toCDDLGroup g
10241092
toCDDLItem (HIGRule g) = toGenRuleDef g
1093+
toCDDLItem (HIGRule' g) = toGenRuleDef' g
10251094
toTopLevelPseudoRoot :: [Rule] -> C.WithComments C.Rule
10261095
toTopLevelPseudoRoot topRs =
10271096
toCDDLRule $
@@ -1084,6 +1153,7 @@ toCDDL' mkPseudoRoot hdl =
10841153
T2Ref (Named n _ _) -> C.Type1 (C.T2Name (C.Name n) Nothing) Nothing
10851154
T2Group (Named n _ _) -> C.Type1 (C.T2Name (C.Name n) Nothing) Nothing
10861155
T2Generic g -> C.Type1 (toGenericCall g) Nothing
1156+
T2Generic' g -> C.Type1 (toGenericCall' g) Nothing
10871157
T2GenericRef (GRef n) -> C.Type1 (C.T2Name (C.Name n) Nothing) Nothing
10881158

10891159
toMemberKey :: Key -> C.MemberKey
@@ -1136,7 +1206,7 @@ toCDDL' mkPseudoRoot hdl =
11361206
(toCDDLRangeBound lb)
11371207
(Just (C.RangeOp rop, toCDDLRangeBound ub))
11381208

1139-
toCDDLRangeBound :: RangeBound -> C.Type2
1209+
toCDDLRangeBound :: RangeBound -> C.Type2
11401210
toCDDLRangeBound (RangeBoundLiteral l) = C.T2Value $ toCDDLValue l
11411211
toCDDLRangeBound (RangeBoundRef (Named n _ _)) = C.T2Name (C.Name n) Nothing
11421212

@@ -1158,6 +1228,12 @@ toCDDL' mkPseudoRoot hdl =
11581228
(C.Name n)
11591229
(Just . C.GenericArg $ fmap toCDDLType1 (args gr))
11601230

1231+
toGenericCall' :: GRuleCall' -> C.Type2
1232+
toGenericCall' (Named n gr _) =
1233+
C.T2Name
1234+
(C.Name n)
1235+
(Just . C.GenericArg $ NE.singleton (toCDDLType1 (callArg gr)))
1236+
11611237
toGenRuleDef :: GRuleDef -> C.WithComments C.Rule
11621238
toGenRuleDef (Named n gr c) =
11631239
C.WithComments
@@ -1170,3 +1246,16 @@ toCDDL' mkPseudoRoot hdl =
11701246
where
11711247
gps =
11721248
C.GenericParam $ fmap (\(GRef t) -> C.Name t) (args gr)
1249+
1250+
toGenRuleDef' :: GRuleDef' -> C.WithComments C.Rule
1251+
toGenRuleDef' (Named n g c) =
1252+
C.WithComments
1253+
( C.Rule (C.Name n) (Just gps) C.AssignEq
1254+
. C.TOGType
1255+
$ C.Type0
1256+
$ toCDDLType1 <$> choiceToNE (fn g (arg g))
1257+
)
1258+
(fmap C.Comment c)
1259+
where
1260+
gps =
1261+
C.GenericParam $ fmap (\(GRef t) -> C.Name t) (NE.singleton $ arg g)
Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
module Codec.CBOR.Cuddle.Huddle.Generic where
2+
3+
-- | Function carrying its argument
4+
data FnWithArg a result = FnWithArg
5+
{ fn :: a -> result,
6+
arg :: a
7+
}
8+
deriving (Functor)
9+
10+
-- | Evaluate a function carrying its argument to its result
11+
result :: FnWithArg a result -> result
12+
result a = fn a (arg a)

src/Codec/CBOR/Cuddle/Huddle/HuddleM.hs

Lines changed: 15 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module Codec.CBOR.Cuddle.Huddle.HuddleM
55
(=:~),
66
(=::=),
77
binding,
8+
binding',
89
setRootRules,
910
huddleDef,
1011
huddleDef',
@@ -13,7 +14,7 @@ module Codec.CBOR.Cuddle.Huddle.HuddleM
1314
)
1415
where
1516

16-
import Codec.CBOR.Cuddle.Huddle hiding (binding, (=:=), (=:~))
17+
import Codec.CBOR.Cuddle.Huddle hiding (binding, binding', (=:=), (=:~))
1718
import Codec.CBOR.Cuddle.Huddle qualified as Huddle
1819
import Control.Monad.State.Strict (State, modify, runState)
1920
import Data.Default.Class (def)
@@ -43,6 +44,11 @@ binding ::
4344
HuddleM (t0 -> GRuleCall)
4445
binding fRule = include (Huddle.binding fRule)
4546

47+
binding' ::
48+
(GRef -> Rule) ->
49+
HuddleM GRuleDef'
50+
binding' fRule = include (Huddle.binding' fRule)
51+
4652
-- | Renamed version of Huddle's underlying '=:=' for use in generic bindings
4753
(=::=) :: (IsType0 a) => T.Text -> a -> Rule
4854
n =::= b = n Huddle.=:= b
@@ -84,9 +90,15 @@ instance (IsType0 t0) => Includable (t0 -> GRuleCall) where
8490
modify (field @"items" %~ (OMap.|> (n, HIGRule grDef)))
8591
pure gr
8692

93+
instance Includable GRuleDef' where
94+
include r =
95+
modify (field @"items" %~ (OMap.|> (r ^. field @"name", HIGRule' r)))
96+
>> pure r
97+
8798
instance Includable HuddleItem where
8899
include x@(HIRule r) = include r >> pure x
89100
include x@(HIGroup g) = include g >> pure x
101+
include x@(HIGRule' g) = include g >> pure x
90102
include x@(HIGRule g) =
91103
let n = g ^. field @"name"
92104
in do
@@ -95,10 +107,10 @@ instance Includable HuddleItem where
95107

96108
unsafeIncludeFromHuddle ::
97109
Huddle ->
98-
T.Text ->
110+
T.Text ->
99111
HuddleM HuddleItem
100112
unsafeIncludeFromHuddle h name =
101113
let items = h ^. field @"items"
102-
in case OMap.lookup name items of
114+
in case OMap.lookup name items of
103115
Just v -> include v
104116
Nothing -> error $ show name <> " was not found in Huddle spec"

0 commit comments

Comments
 (0)