Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
18 changes: 9 additions & 9 deletions bin/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import Codec.CBOR.Cuddle.CDDL.Postlude (appendPostlude)
import Codec.CBOR.Cuddle.CDDL.Resolve (
fullResolveCDDL,
)
import Codec.CBOR.Cuddle.IndexMappable (IndexMappable (..))
import Codec.CBOR.Cuddle.IndexMappable (IndexMappable (..), mapCDDLDropExt)
import Codec.CBOR.Cuddle.Parser (pCDDL)
import Codec.CBOR.Cuddle.Pretty (PrettyStage)
import Codec.CBOR.FlatTerm (toFlatTerm)
Expand Down Expand Up @@ -192,24 +192,24 @@ run (Opts cmd cddlFile) = do
putDocW 80 . pretty $ mapIndex @_ @_ @PrettyStage defs
Validate vOpts ->
let
res'
cddl
| vNoPrelude vOpts = res
| otherwise = appendPostlude res
in
case fullResolveCDDL $ mapIndex res' of
case fullResolveCDDL $ mapCDDLDropExt cddl of
Left err -> putStrLnErr (show err) >> exitFailure
Right _ -> exitSuccess
(GenerateCBOR gOpts) ->
let
res'
cddl
| gNoPrelude gOpts = res
| otherwise = appendPostlude res
in
case fullResolveCDDL $ mapIndex res' of
case fullResolveCDDL $ mapCDDLDropExt cddl of
Left err -> putStrLnErr (show err) >> exitFailure
Right mt -> do
stdGen <- getStdGen
let term = generateCBORTerm mt (Name (itemName gOpts) mempty) stdGen
let term = generateCBORTerm mt (Name $ itemName gOpts) stdGen
in case outputFormat gOpts of
AsTerm -> print term
AsFlatTerm -> print $ toFlatTerm (encodeTerm term)
Expand All @@ -219,15 +219,15 @@ run (Opts cmd cddlFile) = do
AsPrettyCBOR -> putStrLn . prettyHexEnc $ encodeTerm term
ValidateCBOR vcOpts ->
let
res'
cddl
| vcNoPrelude vcOpts = res
| otherwise = res
in
case fullResolveCDDL $ mapIndex res' of
case fullResolveCDDL $ mapCDDLDropExt cddl of
Left err -> putStrLnErr (show err) >> exitFailure
Right mt -> do
cbor <- BSC.readFile (vcInput vcOpts)
validateCBOR cbor (Name (vcItemName vcOpts) mempty) mt
validateCBOR cbor (Name $ vcItemName vcOpts) (mapIndex mt)

putStrLnErr :: String -> IO ()
putStrLnErr = hPutStrLn stderr
Expand Down
5 changes: 5 additions & 0 deletions cuddle.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ library
Codec.CBOR.Cuddle.CBOR.Gen
Codec.CBOR.Cuddle.CBOR.Validator
Codec.CBOR.Cuddle.CDDL
Codec.CBOR.Cuddle.CDDL.CBORGenerator
Codec.CBOR.Cuddle.CDDL.CTree
Codec.CBOR.Cuddle.CDDL.CtlOp
Codec.CBOR.Cuddle.CDDL.Postlude
Expand Down Expand Up @@ -135,6 +136,7 @@ test-suite cuddle-test
Paths_cuddle
Test.Codec.CBOR.Cuddle.CDDL.Examples
Test.Codec.CBOR.Cuddle.CDDL.Gen
Test.Codec.CBOR.Cuddle.CDDL.GeneratorSpec
Test.Codec.CBOR.Cuddle.CDDL.Parser
Test.Codec.CBOR.Cuddle.CDDL.Pretty
Test.Codec.CBOR.Cuddle.Huddle
Expand All @@ -147,13 +149,16 @@ test-suite cuddle-test
QuickCheck >=2.14,
base,
bytestring,
cborg,
containers,
cuddle,
data-default-class,
generic-random,
hspec >=2.11,
hspec-megaparsec >=2.2,
megaparsec,
prettyprinter,
random,
string-qq >=0.0.6,
text,
tree-diff,
4 changes: 0 additions & 4 deletions nix/shell.nix
Original file line number Diff line number Diff line change
Expand Up @@ -36,10 +36,6 @@ let
enable = true;
package = tools.fourmolu;
};
hlint = {
enable = true;
package = tools.hlint;
};
nixpkgs-fmt = {
enable = true;
package = pkgs.nixpkgs-fmt;
Expand Down
67 changes: 36 additions & 31 deletions src/Codec/CBOR/Cuddle/CBOR/Gen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,10 +7,13 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeData #-}
{-# LANGUAGE ViewPatterns #-}

#if MIN_VERSION_random(1,3,0)
{-# OPTIONS_GHC -Wno-deprecations #-} -- Due to usage of `split`
{-# LANGUAGE TypeData #-}
{-# LANGUAGE TypeFamilies #-}
#endif
-- | Generate example CBOR given a CDDL specification
module Codec.CBOR.Cuddle.CBOR.Gen (generateCBORTerm, generateCBORTerm') where
Expand All @@ -25,10 +28,10 @@
Value (..),
ValueVariant (..),
)
import Codec.CBOR.Cuddle.CDDL.CTree (CTree, CTreePhase, CTreeRoot (..), PTerm (..))
import Codec.CBOR.Cuddle.CDDL.CTree (CTree (..), CTreeRoot (..), PTerm (..), foldCTree)
import Codec.CBOR.Cuddle.CDDL.CTree qualified as CTree
import Codec.CBOR.Cuddle.CDDL.CtlOp qualified as CtlOp
import Codec.CBOR.Cuddle.CDDL.Resolve (MonoRef (..), MonoReferenced)
import Codec.CBOR.Cuddle.CDDL.Resolve (MonoReferenced, XXCTree (..))
import Codec.CBOR.Term (Term (..))
import Codec.CBOR.Term qualified as CBOR
import Codec.CBOR.Write qualified as CBOR
Expand Down Expand Up @@ -59,8 +62,21 @@
import System.Random.Stateful (
SplitGen (..)
)
import Codec.CBOR.Cuddle.CDDL.CBORGenerator (WrappedTerm (..), CBORGenerator (..))
import Codec.CBOR.Cuddle.IndexMappable (IndexMappable (..))
#endif

type data MonoDropGen

newtype instance XXCTree MonoDropGen = MDGRef Name
deriving (Show)

instance IndexMappable CTree MonoReferenced MonoDropGen where

Check failure on line 74 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-22)

Not in scope: type constructor or class ‘IndexMappable’

Check failure on line 74 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-24)

Not in scope: type constructor or class ‘IndexMappable’

Check failure on line 74 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-23)

Not in scope: type constructor or class ‘IndexMappable’
mapIndex = foldCTree mapExt mapIndex
where
mapExt (MRuleRef n) = CTreeE $ MDGRef n
mapExt (MGenerator _ x) = mapIndex x

--------------------------------------------------------------------------------
-- Generator infrastructure
--------------------------------------------------------------------------------
Expand Down Expand Up @@ -209,49 +225,37 @@
-- Kinds of terms
--------------------------------------------------------------------------------

data WrappedTerm
= SingleTerm Term
| PairTerm Term Term
| GroupTerm [WrappedTerm]
deriving (Eq, Show)

-- | Recursively flatten wrapped list. That is, expand any groups out to their
-- individual entries.
flattenWrappedList :: [WrappedTerm] -> [WrappedTerm]

Check failure on line 230 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-22)

Not in scope: type constructor or class ‘WrappedTerm’

Check failure on line 230 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-22)

Not in scope: type constructor or class ‘WrappedTerm’

Check failure on line 230 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-24)

Not in scope: type constructor or class ‘WrappedTerm’

Check failure on line 230 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-24)

Not in scope: type constructor or class ‘WrappedTerm’

Check failure on line 230 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-23)

Not in scope: type constructor or class ‘WrappedTerm’

Check failure on line 230 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-23)

Not in scope: type constructor or class ‘WrappedTerm’
flattenWrappedList [] = []
flattenWrappedList (GroupTerm xxs : xs) =
flattenWrappedList (G xxs : xs) =

Check failure on line 232 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-22)

Not in scope: data constructor ‘G’

Check failure on line 232 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-24)

Not in scope: data constructor ‘G’

Check failure on line 232 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-23)

Not in scope: data constructor ‘G’
flattenWrappedList xxs <> flattenWrappedList xs
flattenWrappedList (y : xs) = y : flattenWrappedList xs

pattern S :: Term -> WrappedTerm
pattern S t = SingleTerm t

-- | Convert a list of wrapped terms to a list of terms. If any 'PairTerm's are
-- present, we just take their "value" part.
singleTermList :: [WrappedTerm] -> Maybe [Term]

Check failure on line 238 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-22)

Not in scope: type constructor or class ‘WrappedTerm’

Check failure on line 238 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-24)

Not in scope: type constructor or class ‘WrappedTerm’

Check failure on line 238 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-23)

Not in scope: type constructor or class ‘WrappedTerm’
singleTermList [] = Just []
singleTermList (S x : xs) = (x :) <$> singleTermList xs

Check failure on line 240 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-22)

Not in scope: data constructor ‘S’

Check failure on line 240 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-24)

Not in scope: data constructor ‘S’

Check failure on line 240 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-23)

Not in scope: data constructor ‘S’
singleTermList (P _ y : xs) = (y :) <$> singleTermList xs

Check failure on line 241 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-22)

Not in scope: data constructor ‘P’

Check failure on line 241 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-24)

Not in scope: data constructor ‘P’

Check failure on line 241 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-23)

Not in scope: data constructor ‘P’
singleTermList _ = Nothing

pattern P :: Term -> Term -> WrappedTerm
pattern P t1 t2 = PairTerm t1 t2

-- | Convert a list of wrapped terms to a list of pairs of terms, or fail if any
-- 'SingleTerm's are present.
pairTermList :: [WrappedTerm] -> Maybe [(Term, Term)]

Check failure on line 246 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-22)

Not in scope: type constructor or class ‘WrappedTerm’

Check failure on line 246 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-24)

Not in scope: type constructor or class ‘WrappedTerm’

Check failure on line 246 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-23)

Not in scope: type constructor or class ‘WrappedTerm’
pairTermList [] = Just []
pairTermList (P x y : xs) = ((x, y) :) <$> pairTermList xs

Check failure on line 248 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-22)

Not in scope: data constructor ‘P’

Check failure on line 248 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-24)

Not in scope: data constructor ‘P’

Check failure on line 248 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-23)

Not in scope: data constructor ‘P’
pairTermList _ = Nothing

pattern G :: [WrappedTerm] -> WrappedTerm
pattern G xs = GroupTerm xs
showDropGen :: CTree MonoReferenced -> String
showDropGen = show . mapIndex @_ @_ @MonoDropGen

--------------------------------------------------------------------------------
-- Generator functions
--------------------------------------------------------------------------------

genForCTree :: RandomGen g => CTree MonoReferenced -> M g WrappedTerm

Check failure on line 258 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-22)

Not in scope: type constructor or class ‘WrappedTerm’

Check failure on line 258 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-24)

Not in scope: type constructor or class ‘WrappedTerm’

Check failure on line 258 in src/Codec/CBOR/Cuddle/CBOR/Gen.hs

View workflow job for this annotation

GitHub Actions / Stack (ubuntu-latest, lts-23)

Not in scope: type constructor or class ‘WrappedTerm’
genForCTree (CTree.Literal v) = S <$> genValue v
genForCTree (CTree.Postlude pt) = S <$> genPostlude pt
genForCTree (CTree.Map nodes) = do
Expand Down Expand Up @@ -284,9 +288,9 @@
_ ->
error $
"Non single-term generated outside of group context: "
<> show key
<> showDropGen key
<> " => "
<> show value
<> showDropGen value
genForCTree (CTree.Occur item occurs) =
applyOccurenceIndicator occurs (genForCTree item)
genForCTree (CTree.Range from to _bounds) = do
Expand All @@ -306,11 +310,11 @@
(CtlOp.Le, CTree.Literal (Value (VUInt n) _)) -> case target of
CTree.Postlude PTUInt -> S . TInteger <$> genUniformRM (0, fromIntegral n)
_ -> error "Cannot apply le operator to target"
(CtlOp.Le, _) -> error $ "Invalid controller for .le operator: " <> show controller
(CtlOp.Le, _) -> error $ "Invalid controller for .le operator: " <> showDropGen controller
(CtlOp.Lt, CTree.Literal (Value (VUInt n) _)) -> case target of
CTree.Postlude PTUInt -> S . TInteger <$> genUniformRM (0, fromIntegral n - 1)
_ -> error "Cannot apply lt operator to target"
(CtlOp.Lt, _) -> error $ "Invalid controller for .lt operator: " <> show controller
(CtlOp.Lt, _) -> error $ "Invalid controller for .lt operator: " <> showDropGen controller
(CtlOp.Size, CTree.Literal (Value (VUInt n) _)) -> case target of
CTree.Postlude PTText -> S . TString <$> genText (fromIntegral n)
CTree.Postlude PTBytes -> S . TBytes <$> genBytes (fromIntegral n)
Expand All @@ -328,15 +332,15 @@
CTree.Postlude PTUInt ->
S . TInteger
<$> genUniformRM (fromIntegral f1, fromIntegral t1)
_ -> error $ "Cannot apply size operator to target: " <> show target
_ -> error $ "Cannot apply size operator to target: " <> showDropGen target
_ ->
error $
"Invalid controller for .size operator: "
<> show controller
<> showDropGen controller
(CtlOp.Size, _) ->
error $
"Invalid controller for .size operator: "
<> show controller
<> showDropGen controller
(CtlOp.Cbor, _) -> do
enc <- genForCTree controller
case enc of
Expand All @@ -355,15 +359,16 @@
case enc of
S x -> pure $ S $ TTagged tag x
_ -> error "Tag controller does not correspond to a single term"
genForCTree (CTree.CTreeE x) = genForNode x
genForCTree (CTree.CTreeE (MRuleRef n)) = genForNode n
genForCTree (CTree.CTreeE (MGenerator (CBORGenerator gen) _)) = gen StateGenM

genForNode :: RandomGen g => CTree.Node MonoReferenced -> M g WrappedTerm
genForNode :: RandomGen g => Name -> M g WrappedTerm
genForNode = genForCTree <=< resolveRef

-- | Take a reference and resolve it to the relevant Tree, following multiple
-- links if necessary.
resolveRef :: RandomGen g => CTree.Node MonoReferenced -> M g (CTree MonoReferenced)
resolveRef (MRuleRef n) = do
resolveRef :: RandomGen g => Name -> M g (CTree MonoReferenced)
resolveRef n = do
(CTreeRoot cddl) <- ask @"cddl"
-- Since we follow a reference, we increase the 'depth' of the gen monad.
modify @"depth" (+ 1)
Expand All @@ -379,7 +384,7 @@
-- This will throw an error if the generated item does not correspond to a
-- single CBOR term (e.g. if the name resolves to a group, which cannot be
-- generated outside a context).
genForName :: RandomGen g => Name CTreePhase -> M g Term
genForName :: RandomGen g => Name -> M g Term
genForName n = do
(CTreeRoot cddl) <- ask @"cddl"
case Map.lookup n cddl of
Expand Down Expand Up @@ -433,13 +438,13 @@
-- Generator functions
--------------------------------------------------------------------------------

generateCBORTerm :: RandomGen g => CTreeRoot MonoReferenced -> Name CTreePhase -> g -> Term
generateCBORTerm :: RandomGen g => CTreeRoot MonoReferenced -> Name -> g -> Term
generateCBORTerm cddl n stdGen =
let genEnv = GenEnv {cddl}
genState = GenState {randomSeed = stdGen, depth = 1}
in evalGen (genForName n) genEnv genState

generateCBORTerm' :: RandomGen g => CTreeRoot MonoReferenced -> Name CTreePhase -> g -> (Term, g)
generateCBORTerm' :: RandomGen g => CTreeRoot MonoReferenced -> Name -> g -> (Term, g)
generateCBORTerm' cddl n stdGen =
let genEnv = GenEnv {cddl}
genState = GenState {randomSeed = stdGen, depth = 1}
Expand Down
34 changes: 27 additions & 7 deletions src/Codec/CBOR/Cuddle/CBOR/Validator.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}

module Codec.CBOR.Cuddle.CBOR.Validator (
Expand All @@ -12,7 +14,8 @@ module Codec.CBOR.Cuddle.CBOR.Validator (
import Codec.CBOR.Cuddle.CDDL hiding (CDDL, Group, Rule)
import Codec.CBOR.Cuddle.CDDL.CTree
import Codec.CBOR.Cuddle.CDDL.CtlOp
import Codec.CBOR.Cuddle.CDDL.Resolve
import Codec.CBOR.Cuddle.CDDL.Resolve (MonoReferenced, XXCTree (..))
import Codec.CBOR.Cuddle.IndexMappable (IndexMappable (..))
import Codec.CBOR.Read
import Codec.CBOR.Term
import Control.Exception
Expand All @@ -37,8 +40,25 @@ import System.Exit
import System.IO
import Text.Regex.TDFA

type CDDL = CTreeRoot MonoReferenced
type Rule = CTree MonoReferenced
type data ValidatorStage

data instance XTerm ValidatorStage = ValidatorXTerm
deriving (Show)

newtype instance XXCTree ValidatorStage = VRuleRef Name
deriving (Show)

instance IndexMappable CTreeRoot MonoReferenced ValidatorStage where
mapIndex (CTreeRoot m) = CTreeRoot $ mapIndex <$> m

instance IndexMappable CTree MonoReferenced ValidatorStage where
mapIndex = foldCTree mapExt mapIndex
where
mapExt (MRuleRef n) = CTreeE $ VRuleRef n
mapExt (MGenerator _ x) = mapIndex x

type CDDL = CTreeRoot ValidatorStage
type Rule = CTree ValidatorStage

data CBORTermResult = CBORTermResult Term CDDLResult
deriving (Show)
Expand Down Expand Up @@ -114,7 +134,7 @@ data AMatchedItem = AMatchedItem
--------------------------------------------------------------------------------
-- Main entry point

validateCBOR :: BS.ByteString -> Name CTreePhase -> CDDL -> IO ()
validateCBOR :: BS.ByteString -> Name -> CDDL -> IO ()
validateCBOR bs rule cddl =
( case validateCBOR' bs rule cddl of
ok@(CBORTermResult _ (Valid _)) -> do
Expand All @@ -131,7 +151,7 @@ validateCBOR bs rule cddl =
)

validateCBOR' ::
BS.ByteString -> Name CTreePhase -> CDDL -> CBORTermResult
BS.ByteString -> Name -> CDDL -> CBORTermResult
validateCBOR' bs rule cddl@(CTreeRoot tree) =
case deserialiseFromBytes decodeTerm (BSL.fromStrict bs) of
Left e -> error $ show e
Expand Down Expand Up @@ -1016,7 +1036,7 @@ validateChoice v rules = go rules
. ($ dummyRule)

dummyRule :: Rule
dummyRule = CTreeE $ MRuleRef (Name "dummy" mempty)
dummyRule = CTreeE $ VRuleRef "dummy"

--------------------------------------------------------------------------------
-- Control helpers
Expand Down Expand Up @@ -1108,7 +1128,7 @@ getIndicesOfEnum g =
-- Resolving rules from the CDDL spec

resolveIfRef :: CDDL -> Rule -> Rule
resolveIfRef ct@(CTreeRoot cddl) (CTreeE (MRuleRef n)) = do
resolveIfRef ct@(CTreeRoot cddl) (CTreeE (VRuleRef n)) = do
case Map.lookup n cddl of
Nothing -> error $ "Unbound reference: " <> show n
Just val -> resolveIfRef ct val
Expand Down
Loading