8
8
{-# LANGUAGE TypeApplications #-}
9
9
{-# LANGUAGE TypeFamilies #-}
10
10
{-# LANGUAGE UndecidableInstances #-}
11
+ {-# LANGUAGE ViewPatterns #-}
11
12
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
12
13
13
14
-- | Module for building CDDL in Haskell
@@ -76,10 +77,15 @@ module Codec.CBOR.Cuddle.Huddle
76
77
-- * Generics
77
78
GRef ,
78
79
GRuleDef ,
80
+ GRuleDef' ,
79
81
GRuleCall ,
82
+ GRuleCall' ,
80
83
binding ,
81
84
binding2 ,
85
+ binding' ,
82
86
callToDef ,
87
+ callToDef' ,
88
+ (<--) ,
83
89
84
90
-- * Conversion to CDDL
85
91
collectFrom ,
91
97
import Codec.CBOR.Cuddle.CDDL (CDDL )
92
98
import Codec.CBOR.Cuddle.CDDL qualified as C
93
99
import Codec.CBOR.Cuddle.CDDL.CtlOp qualified as CtlOp
100
+ import Codec.CBOR.Cuddle.Huddle.Generic (FnWithArg (.. ), result )
94
101
import Control.Monad (when )
95
102
import Control.Monad.State (MonadState (get ), execState , modify )
96
103
import Data.ByteString (ByteString )
@@ -128,6 +135,7 @@ type Rule = Named Type0
128
135
data HuddleItem
129
136
= HIRule Rule
130
137
| HIGRule GRuleDef
138
+ | HIGRule' GRuleDef'
131
139
| HIGroup (Named Group )
132
140
deriving (Generic , Show )
133
141
@@ -273,6 +281,7 @@ data Type2
273
281
| T2Group (Named Group )
274
282
| -- | Call to a generic rule, binding arguments
275
283
T2Generic GRuleCall
284
+ | T2Generic' GRuleCall'
276
285
| -- | Reference to a generic parameter within the body of the definition
277
286
T2GenericRef GRef
278
287
deriving (Show )
@@ -433,7 +442,7 @@ class IsSize a where
433
442
434
443
instance IsSize Word where
435
444
sizeAsCDDL = C. T2Value . C. VUInt . fromIntegral
436
- sizeAsString = show
445
+ sizeAsString = show
437
446
438
447
instance IsSize Word64 where
439
448
sizeAsCDDL = C. T2Value . C. VUInt
@@ -474,10 +483,13 @@ sized v sz =
474
483
}
475
484
[]
476
485
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
481
493
482
494
cbor :: (IsCborable b , IsConstrainable c b ) => c -> Rule -> Constrained
483
495
cbor v r@ (Named n _ _) =
@@ -492,9 +504,12 @@ cbor v r@(Named n _ _) =
492
504
}
493
505
[r]
494
506
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
+
498
513
instance IsComparable CGRef
499
514
500
515
le :: (IsComparable a , IsConstrainable c a ) => c -> Word64 -> Constrained
@@ -512,16 +527,16 @@ le v bound =
512
527
513
528
-- Ranges
514
529
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 )
519
534
520
535
class IsRangeBound a where
521
- toRangeBound :: a -> RangeBound
536
+ toRangeBound :: a -> RangeBound
522
537
523
538
instance IsRangeBound Literal where
524
- toRangeBound = RangeBoundLiteral
539
+ toRangeBound = RangeBoundLiteral
525
540
526
541
instance IsRangeBound Integer where
527
542
toRangeBound = RangeBoundLiteral . inferInteger
@@ -605,6 +620,9 @@ instance IsType0 (Named Group) where
605
620
instance IsType0 GRuleCall where
606
621
toType0 = NoChoice . T2Generic
607
622
623
+ instance IsType0 GRuleCall' where
624
+ toType0 = NoChoice . T2Generic'
625
+
608
626
instance IsType0 GRef where
609
627
toType0 = NoChoice . T2GenericRef
610
628
@@ -617,6 +635,9 @@ instance IsType0 HuddleItem where
617
635
toType0 (HIGRule g) =
618
636
error $
619
637
" 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
620
641
621
642
class CanQuantify a where
622
643
-- | Apply a lower bound
@@ -933,6 +954,53 @@ binding2 fRule t0 t1 =
933
954
NoChoice x -> x
934
955
_ -> error " Cannot use a choice of types as a generic argument"
935
956
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
+
936
1004
--------------------------------------------------------------------------------
937
1005
-- Collecting all top-level rules
938
1006
--------------------------------------------------------------------------------
@@ -960,7 +1028,7 @@ collectFrom topRs =
960
1028
goChoice f (NoChoice x) = f x
961
1029
goChoice f (ChoiceOf x xs) = f x >> goChoice f xs
962
1030
goT0 = goChoice goT2
963
- goT2 (T2Range r) = goRanged r
1031
+ goT2 (T2Range r) = goRanged r
964
1032
goT2 (T2Map m) = goChoice (mapM_ goMapEntry . unMapChoice) m
965
1033
goT2 (T2Array m) = goChoice (mapM_ goArrayEntry . unArrayChoice) m
966
1034
goT2 (T2Tagged (Tagged _ t0)) = goT0 t0
@@ -993,10 +1061,10 @@ collectFrom topRs =
993
1061
goKey _ = pure ()
994
1062
goGroup (Group g) = mapM_ goArrayEntry g
995
1063
goRanged (Unranged _) = pure ()
996
- goRanged (Ranged lb ub _) = goRangeBound lb >> goRangeBound ub
1064
+ goRanged (Ranged lb ub _) = goRangeBound lb >> goRangeBound ub
997
1065
goRangeBound (RangeBoundLiteral _) = pure ()
998
1066
goRangeBound (RangeBoundRef r) = goRule r
999
-
1067
+
1000
1068
--------------------------------------------------------------------------------
1001
1069
-- Conversion to CDDL
1002
1070
--------------------------------------------------------------------------------
@@ -1022,6 +1090,7 @@ toCDDL' mkPseudoRoot hdl =
1022
1090
toCDDLItem (HIRule r) = toCDDLRule r
1023
1091
toCDDLItem (HIGroup g) = toCDDLGroup g
1024
1092
toCDDLItem (HIGRule g) = toGenRuleDef g
1093
+ toCDDLItem (HIGRule' g) = toGenRuleDef' g
1025
1094
toTopLevelPseudoRoot :: [Rule ] -> C. WithComments C. Rule
1026
1095
toTopLevelPseudoRoot topRs =
1027
1096
toCDDLRule $
@@ -1084,6 +1153,7 @@ toCDDL' mkPseudoRoot hdl =
1084
1153
T2Ref (Named n _ _) -> C. Type1 (C. T2Name (C. Name n) Nothing ) Nothing
1085
1154
T2Group (Named n _ _) -> C. Type1 (C. T2Name (C. Name n) Nothing ) Nothing
1086
1155
T2Generic g -> C. Type1 (toGenericCall g) Nothing
1156
+ T2Generic' g -> C. Type1 (toGenericCall' g) Nothing
1087
1157
T2GenericRef (GRef n) -> C. Type1 (C. T2Name (C. Name n) Nothing ) Nothing
1088
1158
1089
1159
toMemberKey :: Key -> C. MemberKey
@@ -1136,7 +1206,7 @@ toCDDL' mkPseudoRoot hdl =
1136
1206
(toCDDLRangeBound lb)
1137
1207
(Just (C. RangeOp rop, toCDDLRangeBound ub))
1138
1208
1139
- toCDDLRangeBound :: RangeBound -> C. Type2
1209
+ toCDDLRangeBound :: RangeBound -> C. Type2
1140
1210
toCDDLRangeBound (RangeBoundLiteral l) = C. T2Value $ toCDDLValue l
1141
1211
toCDDLRangeBound (RangeBoundRef (Named n _ _)) = C. T2Name (C. Name n) Nothing
1142
1212
@@ -1158,6 +1228,12 @@ toCDDL' mkPseudoRoot hdl =
1158
1228
(C. Name n)
1159
1229
(Just . C. GenericArg $ fmap toCDDLType1 (args gr))
1160
1230
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
+
1161
1237
toGenRuleDef :: GRuleDef -> C. WithComments C. Rule
1162
1238
toGenRuleDef (Named n gr c) =
1163
1239
C. WithComments
@@ -1170,3 +1246,16 @@ toCDDL' mkPseudoRoot hdl =
1170
1246
where
1171
1247
gps =
1172
1248
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)
0 commit comments