Skip to content

Commit

Permalink
refactor: Add Anoma Node in Tree language
Browse files Browse the repository at this point in the history
Similarly to how the Cairo operations are handled we add a separate Tree
language Node for Anoma operations instead of handling then as an Unop
Node.
  • Loading branch information
paulcadman committed May 15, 2024
1 parent 52f8afd commit 66420f2
Show file tree
Hide file tree
Showing 18 changed files with 126 additions and 40 deletions.
4 changes: 1 addition & 3 deletions src/Juvix/Compiler/Asm/Translation/FromTree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ genCode fi =
Tree.Binop x -> goBinop isTail x
Tree.Unop x -> goUnop isTail x
Tree.Cairo x -> goCairo isTail x
Tree.Anoma {} -> error "Anoma instructions are not supported in the Asm backend"
Tree.Constant x -> goConstant isTail x
Tree.MemRef x -> goMemRef isTail x
Tree.AllocConstr x -> goAllocConstr isTail x
Expand Down Expand Up @@ -233,9 +234,6 @@ genCode fi =
Tree.PrimUnop op' -> mkUnop op'
Tree.OpTrace -> mkInstr Trace
Tree.OpFail -> mkInstr Failure
Tree.OpAnomaGet -> impossible
Tree.OpAnomaEncode -> impossible
Tree.OpAnomaDecode -> impossible

snocReturn :: Bool -> Code' -> Code'
snocReturn True code = DL.snoc code (mkInstr Return)
Expand Down
3 changes: 3 additions & 0 deletions src/Juvix/Compiler/Core/Language/Builtins.hs
Original file line number Diff line number Diff line change
Expand Up @@ -121,6 +121,9 @@ builtinIsFoldable = \case
builtinIsCairo :: BuiltinOp -> Bool
builtinIsCairo op = op `elem` builtinsCairo

builtinIsAnoma :: BuiltinOp -> Bool
builtinIsAnoma op = op `elem` builtinsAnoma

builtinsString :: [BuiltinOp]
builtinsString = [OpStrConcat, OpStrToInt, OpShow]

Expand Down
24 changes: 15 additions & 9 deletions src/Juvix/Compiler/Nockma/Translation/FromTree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -330,6 +330,7 @@ compile = \case
Tree.Binop b -> goBinop b
Tree.Unop b -> goUnop b
Tree.Cairo {} -> cairoErr
Tree.Anoma b -> goAnomaOp b
Tree.Constant c -> return (goConstant (c ^. Tree.nodeConstant))
Tree.MemRef c -> goMemRef (c ^. Tree.nodeMemRef)
Tree.AllocConstr c -> goAllocConstr c
Expand Down Expand Up @@ -418,16 +419,21 @@ compile = \case
iffalse <- compile _nodeBranchFalse
return (branch arg iftrue iffalse)

goAnomaOp :: Tree.NodeAnoma -> Sem r (Term Natural)
goAnomaOp Tree.NodeAnoma {..} = do
args <- mapM compile _nodeAnomaArgs
case _nodeAnomaOpcode of
Tree.OpAnomaGet -> goAnomaGet args
Tree.OpAnomaEncode -> goAnomaEncode args
Tree.OpAnomaDecode -> goAnomaDecode args

goUnop :: Tree.NodeUnop -> Sem r (Term Natural)
goUnop Tree.NodeUnop {..} = do
arg <- compile _nodeUnopArg
case _nodeUnopOpcode of
Tree.PrimUnop op -> return $ goPrimUnop op arg
Tree.OpFail -> return crash
Tree.OpTrace -> goTrace arg
Tree.OpAnomaGet -> goAnomaGet arg
Tree.OpAnomaEncode -> goAnomaEncode arg
Tree.OpAnomaDecode -> goAnomaDecode arg

goPrimUnop :: Tree.UnaryOp -> Term Natural -> Term Natural
goPrimUnop op arg = case op of
Expand All @@ -439,16 +445,16 @@ compile = \case
Tree.OpIntToField -> fieldErr
Tree.OpFieldToInt -> fieldErr

goAnomaGet :: Term Natural -> Sem r (Term Natural)
goAnomaGet :: [Term Natural] -> Sem r (Term Natural)
goAnomaGet key = do
let arg = remakeList [getFieldInSubject AnomaGetOrder, key]
let arg = remakeList [getFieldInSubject AnomaGetOrder, foldTermsOrNil key]
return (OpScry # (OpQuote # nockNilTagged "OpScry-typehint") # arg)

goAnomaEncode :: Term Natural -> Sem r (Term Natural)
goAnomaEncode arg = return (callStdlib StdlibEncode [arg])
goAnomaEncode :: [Term Natural] -> Sem r (Term Natural)
goAnomaEncode args = return (callStdlib StdlibEncode args)

goAnomaDecode :: Term Natural -> Sem r (Term Natural)
goAnomaDecode arg = return (callStdlib StdlibDecode [arg])
goAnomaDecode :: [Term Natural] -> Sem r (Term Natural)
goAnomaDecode args = return (callStdlib StdlibDecode args)

goTrace :: Term Natural -> Sem r (Term Natural)
goTrace arg = do
Expand Down
4 changes: 1 addition & 3 deletions src/Juvix/Compiler/Tree/Evaluator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ hEval hout tab = eval' [] mempty
eval' args temps node = case node of
Binop x -> goBinop x
Unop x -> goUnop x
Anoma {} -> evalError "unsupported: Anoma builtin"
Cairo {} -> evalError "unsupported: Cairo builtin"
Constant c -> goConstant c
MemRef x -> goMemRef x
Expand Down Expand Up @@ -74,9 +75,6 @@ hEval hout tab = eval' [] mempty
PrimUnop op -> eitherToError $ evalUnop tab op v
OpTrace -> goTrace v
OpFail -> goFail v
OpAnomaGet -> evalError "Unsupported op: OpAnomaGet"
OpAnomaEncode -> evalError "Unsupported op: OpAnomaEncode"
OpAnomaDecode -> evalError "Unsupported op: OpAnomaDecode"

goFail :: Value -> Value
goFail v = evalError ("failure: " <> printValue tab v)
Expand Down
4 changes: 1 addition & 3 deletions src/Juvix/Compiler/Tree/EvaluatorEff.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ eval tab = runReader emptyEvalCtx . eval'
eval' node = case node of
Binop x -> goBinop x
Unop x -> goUnop x
Anoma {} -> evalError "unsupported: Anoma builtins"
Cairo {} -> evalError "unsupported: Cairo builtins"
Constant c -> return (goConstant c)
MemRef x -> goMemRef x
Expand Down Expand Up @@ -69,9 +70,6 @@ eval tab = runReader emptyEvalCtx . eval'
PrimUnop op -> eitherToError $ evalUnop tab op v
OpTrace -> goTrace v
OpFail -> goFail v
OpAnomaGet -> evalError "Unsupported op: OpAnomaGet"
OpAnomaEncode -> evalError "Unsupported op: OpAnomaEncode"
OpAnomaDecode -> evalError "Unsupported op: OpAnomaDecode"

goFail :: Value -> Sem r' Value
goFail v = evalError ("failure: " <> printValue tab v)
Expand Down
12 changes: 12 additions & 0 deletions src/Juvix/Compiler/Tree/Extra/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ getNodeInfo = \case
Binop NodeBinop {..} -> _nodeBinopInfo
Unop NodeUnop {..} -> _nodeUnopInfo
Cairo NodeCairo {..} -> _nodeCairoInfo
Anoma NodeAnoma {..} -> _nodeAnomaInfo
Constant NodeConstant {..} -> _nodeConstantInfo
MemRef NodeMemRef {..} -> _nodeMemRefInfo
AllocConstr NodeAllocConstr {..} -> _nodeAllocConstrInfo
Expand Down Expand Up @@ -152,6 +153,17 @@ destruct = \case
_nodeCairoInfo
}
}
Anoma NodeAnoma {..} ->
NodeDetails
{ _nodeChildren = map noTempVar _nodeAnomaArgs,
_nodeReassemble = manyChildren $ \args ->
Anoma
NodeAnoma
{ _nodeAnomaArgs = args,
_nodeAnomaOpcode,
_nodeAnomaInfo
}
}
Constant c ->
NodeDetails
{ _nodeChildren = [],
Expand Down
4 changes: 4 additions & 0 deletions src/Juvix/Compiler/Tree/Keywords.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,8 @@ import Juvix.Compiler.Tree.Keywords.Base
import Juvix.Data.Keyword.All
( kwAdd_,
kwAlloc,
kwAnomaDecode,
kwAnomaEncode,
kwAnomaGet,
kwArgsNum,
kwAtoi,
Expand Down Expand Up @@ -74,6 +76,8 @@ allKeywords =
kwCase,
kwSave,
kwAnomaGet,
kwAnomaDecode,
kwAnomaEncode,
kwPoseidon,
kwEcOp,
kwRandomEcPoint
Expand Down
13 changes: 7 additions & 6 deletions src/Juvix/Compiler/Tree/Language.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ data Node
= Binop NodeBinop
| Unop NodeUnop
| Cairo NodeCairo
| Anoma NodeAnoma
| -- | A constant value.
Constant NodeConstant
| -- | A memory reference.
Expand Down Expand Up @@ -67,12 +68,6 @@ data UnaryOpcode
OpTrace
| -- | Interrupt execution with a runtime error printing the argument.
OpFail
| -- | Get a value by key from Anoma storage
OpAnomaGet
| -- | Encode a value to an Anoma atom
OpAnomaEncode
| -- | Decode a value from an Anoma atom
OpAnomaDecode

data NodeBinop = NodeBinop
{ _nodeBinopInfo :: NodeInfo,
Expand All @@ -93,6 +88,12 @@ data NodeCairo = NodeCairo
_nodeCairoArgs :: [Node]
}

data NodeAnoma = NodeAnoma
{ _nodeAnomaInfo :: NodeInfo,
_nodeAnomaOpcode :: AnomaOp,
_nodeAnomaArgs :: [Node]
}

data NodeConstant = NodeConstant
{ _nodeConstantInfo :: NodeInfo,
_nodeConstant :: Constant
Expand Down
10 changes: 10 additions & 0 deletions src/Juvix/Compiler/Tree/Language/Builtins.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,3 +47,13 @@ cairoOpArgsNum = \case
OpCairoPoseidon -> 1
OpCairoEc -> 3
OpCairoRandomEcPoint -> 0

-- | Builtin Anoma operations. Implemented only in the Anoma backend.
data AnomaOp
= -- | Get a value by key from Anoma storage
OpAnomaGet
| -- | Encode a value to an Anoma atom
OpAnomaEncode
| -- | Decode a value from an Anoma atom
OpAnomaDecode
deriving stock (Eq)
9 changes: 6 additions & 3 deletions src/Juvix/Compiler/Tree/Pretty/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -240,14 +240,17 @@ instance PrettyCode CairoOp where
OpCairoEc -> Str.instrEcOp
OpCairoRandomEcPoint -> Str.cairoRandomEcPoint

instance PrettyCode AnomaOp where
ppCode op = return . primitive $ case op of
OpAnomaGet -> Str.anomaGet
OpAnomaEncode -> Str.anomaEncode
OpAnomaDecode -> Str.anomaDecode

instance PrettyCode UnaryOpcode where
ppCode = \case
PrimUnop x -> ppCode x
OpTrace -> return $ primitive Str.instrTrace
OpFail -> return $ primitive Str.instrFailure
OpAnomaGet -> return $ primitive Str.anomaGet
OpAnomaEncode -> return $ primitive Str.anomaEncode
OpAnomaDecode -> return $ primitive Str.anomaDecode

instance PrettyCode NodeUnop where
ppCode NodeUnop {..} = do
Expand Down
7 changes: 2 additions & 5 deletions src/Juvix/Compiler/Tree/Transformation/CheckNoAnoma.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,19 +10,16 @@ checkNoAnoma = walkT checkNode
where
checkNode :: Symbol -> Node -> Sem r ()
checkNode _ = \case
Unop NodeUnop {..} -> case _nodeUnopOpcode of
Anoma NodeAnoma {..} -> case _nodeAnomaOpcode of
OpAnomaGet -> unsupportedErr "OpAnomaGet"
OpAnomaEncode -> unsupportedErr "OpAnomaEncode"
OpAnomaDecode -> unsupportedErr "OpAnomaDecode"
OpFail -> return ()
OpTrace -> return ()
PrimUnop {} -> return ()
where
unsupportedErr :: Text -> Sem r ()
unsupportedErr opName =
throw
TreeError
{ _treeErrorMsg = opName <> " is unsupported",
_treeErrorLoc = _nodeUnopInfo ^. nodeInfoLocation
_treeErrorLoc = _nodeAnomaInfo ^. nodeInfoLocation
}
_ -> return ()
9 changes: 6 additions & 3 deletions src/Juvix/Compiler/Tree/Transformation/Validate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ inferType tab funInfo = goInfer mempty
Binop x -> goBinop bl x
Unop x -> goUnop bl x
Cairo x -> goCairo bl x
Anoma x -> goAnoma bl x
Constant x -> goConst bl x
MemRef x -> goMemRef bl x
AllocConstr x -> goAllocConstr bl x
Expand Down Expand Up @@ -65,9 +66,6 @@ inferType tab funInfo = goInfer mempty
PrimUnop x -> checkPrimUnop x
OpTrace -> goInfer bl _nodeUnopArg
OpFail -> checkUnop TyDynamic TyDynamic
OpAnomaGet -> checkUnop TyDynamic TyDynamic
OpAnomaEncode -> checkUnop TyDynamic TyDynamic
OpAnomaDecode -> checkUnop TyDynamic TyDynamic
where
loc = _nodeUnopInfo ^. nodeInfoLocation

Expand All @@ -90,6 +88,11 @@ inferType tab funInfo = goInfer mempty
mapM_ (\arg -> checkType bl arg TyDynamic) _nodeCairoArgs
return TyDynamic

goAnoma :: BinderList Type -> NodeAnoma -> Sem r Type
goAnoma bl NodeAnoma {..} = do
mapM_ (\arg -> checkType bl arg TyDynamic) _nodeAnomaArgs
return TyDynamic

goConst :: BinderList Type -> NodeConstant -> Sem r Type
goConst _ NodeConstant {..} = case _nodeConstant of
ConstInt {} -> return mkTypeInteger
Expand Down
17 changes: 14 additions & 3 deletions src/Juvix/Compiler/Tree/Translation/FromCore.hs
Original file line number Diff line number Diff line change
Expand Up @@ -145,6 +145,13 @@ genCode infoTable fi =
_nodeCairoOpcode = genCairoOp _builtinAppOp,
_nodeCairoArgs = args
}
| Core.builtinIsAnoma _builtinAppOp =
Anoma $
NodeAnoma
{ _nodeAnomaInfo = mempty,
_nodeAnomaOpcode = genAnomaOp _builtinAppOp,
_nodeAnomaArgs = args
}
| otherwise =
case args of
[arg] ->
Expand Down Expand Up @@ -295,9 +302,6 @@ genCode infoTable fi =
Core.OpFieldToInt -> PrimUnop OpFieldToInt
Core.OpTrace -> OpTrace
Core.OpFail -> OpFail
Core.OpAnomaGet -> OpAnomaGet
Core.OpAnomaEncode -> OpAnomaEncode
Core.OpAnomaDecode -> OpAnomaDecode
_ -> impossible

genCairoOp :: Core.BuiltinOp -> CairoOp
Expand All @@ -307,6 +311,13 @@ genCode infoTable fi =
Core.OpRandomEcPoint -> OpCairoRandomEcPoint
_ -> impossible

genAnomaOp :: Core.BuiltinOp -> AnomaOp
genAnomaOp = \case
Core.OpAnomaGet -> OpAnomaGet
Core.OpAnomaEncode -> OpAnomaEncode
Core.OpAnomaDecode -> OpAnomaDecode
_ -> impossible

getArgsNum :: Symbol -> Int
getArgsNum sym =
fromMaybe
Expand Down
20 changes: 19 additions & 1 deletion src/Juvix/Compiler/Tree/Translation/FromSource.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,7 @@ parseNode ::
parseNode =
(Binop <$> parseBinop)
<|> (Unop <$> parseUnop)
<|> (Anoma <$> parseAnoma)
<|> (Cairo <$> parseCairo)
<|> (Constant <$> parseConst)
<|> (AllocConstr <$> parseAlloc)
Expand Down Expand Up @@ -107,7 +108,6 @@ parseUnop =
<|> parseUnaryOp kwTrace OpTrace
<|> parseUnaryOp kwFail OpFail
<|> parseUnaryOp kwArgsNum (PrimUnop OpArgsNum)
<|> parseUnaryOp kwAnomaGet (OpAnomaGet)

parseUnaryOp ::
(Members '[Reader ParserSig, InfoTableBuilder, State LocalParams] r) =>
Expand All @@ -119,6 +119,24 @@ parseUnaryOp kwd op = do
arg <- parens parseNode
return $ NodeUnop (NodeInfo (Just loc)) op arg

parseAnoma ::
(Members '[Reader ParserSig, InfoTableBuilder, State LocalParams] r) =>
ParsecS r NodeAnoma
parseAnoma =
parseAnoma' kwAnomaGet OpAnomaGet
<|> parseAnoma' kwAnomaDecode OpAnomaDecode
<|> parseAnoma' kwAnomaEncode OpAnomaEncode

parseAnoma' ::
(Members '[Reader ParserSig, InfoTableBuilder, State LocalParams] r) =>
Keyword ->
AnomaOp ->
ParsecS r NodeAnoma
parseAnoma' kwd op = do
loc <- onlyInterval (kw kwd)
args <- parseArgs
return $ NodeAnoma (NodeInfo (Just loc)) op args

parseCairo ::
(Members '[Reader ParserSig, InfoTableBuilder, State LocalParams] r) =>
ParsecS r NodeCairo
Expand Down
6 changes: 6 additions & 0 deletions src/Juvix/Data/Keyword/All.hs
Original file line number Diff line number Diff line change
Expand Up @@ -445,6 +445,12 @@ kwLive = asciiKw Str.live
kwAnomaGet :: Keyword
kwAnomaGet = asciiKw Str.anomaGet

kwAnomaDecode :: Keyword
kwAnomaDecode = asciiKw Str.anomaDecode

kwAnomaEncode :: Keyword
kwAnomaEncode = asciiKw Str.anomaEncode

delimBraceL :: Keyword
delimBraceL = mkDelim Str.braceL

Expand Down
10 changes: 9 additions & 1 deletion test/Tree/Transformation/CheckNoAnoma.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,5 +63,13 @@ tests =
[ Eval.NegTest
"anomaGet"
$(mkRelDir ".")
$(mkRelFile "test009.jvt")
$(mkRelFile "test009.jvt"),
Eval.NegTest
"anomaDecode"
$(mkRelDir ".")
$(mkRelFile "test010.jvt"),
Eval.NegTest
"anomaEncode"
$(mkRelDir ".")
$(mkRelFile "test011.jvt")
]
5 changes: 5 additions & 0 deletions tests/Tree/negative/test010.jvt
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
-- calling unsupported anoma-decode

function main() : * {
anoma-decode(1)
}
Loading

0 comments on commit 66420f2

Please sign in to comment.