-
Notifications
You must be signed in to change notification settings - Fork 2
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Merge pull request #40 from input-output-hk/nc/huddleM
Introduce HuddleM
- Loading branch information
Showing
8 changed files
with
253 additions
and
37 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,52 @@ | ||
{-# LANGUAGE OverloadedLists #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
{-# LANGUAGE RecursiveDo #-} | ||
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} | ||
{-# HLINT ignore "Use camelCase" #-} | ||
|
||
module Monad where | ||
|
||
import Codec.CBOR.Cuddle.Huddle qualified as Huddle | ||
import Codec.CBOR.Cuddle.Huddle.HuddleM | ||
import Data.Word (Word64) | ||
|
||
hdl_set :: (IsType0 t0) => t0 -> GRuleCall | ||
hdl_set = Huddle.binding $ \x -> "set" Huddle.=:= arr [0 <+ a x] | ||
|
||
spec :: Huddle | ||
spec = huddleDef $ mdo | ||
transaction <- | ||
"transaction" | ||
=:= mp | ||
[ idx 0 ==> set txIn, | ||
idx 1 ==> set txOut | ||
] | ||
txIn <- "txIn" =:= arr ["transaction_id" ==> hash32, "index" ==> txId] | ||
txOut <- "txOut" =:= arr [idx 0 ==> address, idx 1 ==> value] | ||
txId <- "txId" =:= VUInt `sized` (2 :: Word64) | ||
address <- "address" =:= VBytes `sized` (32 :: Word64) | ||
hash32 <- "hash32" =:= VBytes `sized` (32 :: Word64) | ||
value <- "value" =:= VUInt | ||
set <- include hdl_set | ||
|
||
setRootRules [transaction] | ||
|
||
spec2 :: Huddle | ||
spec2 = | ||
spec | ||
<> huddleDef | ||
( mdo | ||
set <- include hdl_set | ||
txIn <- unsafeIncludeFromHuddle spec "txIn" | ||
txOut <- unsafeIncludeFromHuddle spec "txOut" | ||
_transaction <- | ||
"transaction" | ||
=:= mp | ||
[ idx 0 ==> set txIn, | ||
idx 1 ==> set txOut, | ||
idx 2 ==> metadata | ||
] | ||
metadata <- "metadata" =:= VBytes | ||
_value <- "value" =:= mp ["token" ==> VText, "quantity" ==> VUInt] | ||
pure () | ||
) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,104 @@ | ||
-- | Monad for declaring Huddle constructs | ||
module Codec.CBOR.Cuddle.Huddle.HuddleM | ||
( module Huddle, | ||
(=:=), | ||
(=:~), | ||
(=::=), | ||
binding, | ||
setRootRules, | ||
huddleDef, | ||
huddleDef', | ||
include, | ||
unsafeIncludeFromHuddle, | ||
) | ||
where | ||
|
||
import Codec.CBOR.Cuddle.Huddle hiding (binding, (=:=), (=:~)) | ||
import Codec.CBOR.Cuddle.Huddle qualified as Huddle | ||
import Control.Monad.State.Strict (State, modify, runState) | ||
import Data.Default.Class (def) | ||
import Data.Generics.Product (HasField (..)) | ||
import Data.Map.Ordered.Strict qualified as OMap | ||
import Data.Text qualified as T | ||
import Optics.Core (set, (%~), (^.)) | ||
|
||
type HuddleM = State Huddle | ||
|
||
-- | Overridden version of assignment which also adds the rule to the state | ||
(=:=) :: (IsType0 a) => T.Text -> a -> HuddleM Rule | ||
n =:= b = let r = n Huddle.=:= b in include r | ||
|
||
infixl 1 =:= | ||
|
||
-- | Overridden version of group assignment which adds the rule to the state | ||
(=:~) :: T.Text -> Group -> HuddleM (Named Group) | ||
n =:~ b = let r = n Huddle.=:~ b in include r | ||
|
||
infixl 1 =:~ | ||
|
||
binding :: | ||
forall t0. | ||
(IsType0 t0) => | ||
(GRef -> Rule) -> | ||
HuddleM (t0 -> GRuleCall) | ||
binding fRule = include (Huddle.binding fRule) | ||
|
||
-- | Renamed version of Huddle's underlying '=:=' for use in generic bindings | ||
(=::=) :: (IsType0 a) => T.Text -> a -> Rule | ||
n =::= b = n Huddle.=:= b | ||
|
||
infixl 1 =::= | ||
|
||
setRootRules :: [Rule] -> HuddleM () | ||
setRootRules = modify . set (field @"roots") | ||
|
||
huddleDef :: HuddleM a -> Huddle | ||
huddleDef = snd . huddleDef' | ||
|
||
huddleDef' :: HuddleM a -> (a, Huddle) | ||
huddleDef' mh = runState mh def | ||
|
||
class Includable a where | ||
-- | Include a rule, group, or generic rule defined elsewhere | ||
include :: a -> HuddleM a | ||
|
||
instance Includable Rule where | ||
include r = | ||
modify (field @"items" %~ (OMap.|> (r ^. field @"name", HIRule r))) | ||
>> pure r | ||
|
||
instance Includable (Named Group) where | ||
include r = | ||
modify | ||
( (field @"items") | ||
%~ (OMap.|> (r ^. field @"name", HIGroup r)) | ||
) | ||
>> pure r | ||
|
||
instance (IsType0 t0) => Includable (t0 -> GRuleCall) where | ||
include gr = | ||
let fakeT0 = error "Attempting to unwrap fake value in generic call" | ||
grDef = callToDef <$> gr fakeT0 | ||
n = grDef ^. field @"name" | ||
in do | ||
modify (field @"items" %~ (OMap.|> (n, HIGRule grDef))) | ||
pure gr | ||
|
||
instance Includable HuddleItem where | ||
include x@(HIRule r) = include r >> pure x | ||
include x@(HIGroup g) = include g >> pure x | ||
include x@(HIGRule g) = | ||
let n = g ^. field @"name" | ||
in do | ||
modify (field @"items" %~ (OMap.|> (n, x))) | ||
pure x | ||
|
||
unsafeIncludeFromHuddle :: | ||
Huddle -> | ||
T.Text -> | ||
HuddleM HuddleItem | ||
unsafeIncludeFromHuddle h name = | ||
let items = h ^. field @"items" | ||
in case OMap.lookup name items of | ||
Just v -> include v | ||
Nothing -> error $ show name <> " was not found in Huddle spec" |
Oops, something went wrong.