You signed in with another tab or window. Reload to refresh your session.You signed out in another tab or window. Reload to refresh your session.You switched accounts on another tab or window. Reload to refresh your session.Dismiss alert
If RFML was v1 of this little DSL of ours, and the current Directive-based formulation is v2, then moving recursion schemes would be our v3. Luckily, our current architecture isn't far off from RSs already. If you squint, you can see them there (i.e. directives are part of an Algebra, and evaluation is just a catamorphism. Functions like Interpreter.naive build the Algebra officially).
Before breaking MAML out, we had lamented that making ASTs handle multiple return types would be a nightmare. That wasn't actually true, all we needed was an ADT of possible return types which would then be matched upon at each Algebra step. This is the purpose of the Result ADT in MAML, and we can see a hint of this idea in the original RDD interpreter where Either was being returned.
So given these tools - Recursion Schemes and a Result return type - we can achieve our multityped AST with very little "type shenanigans". Here's a prototype in Haskell:
{-# LANGUAGE DeriveFunctor #-}
moduleRSwhereimportData.Foldable (foldlM)
importData.Functor.Foldable-----| A "pattern functor" for a MAML expression tree.dataExprFat=Leafa | Add [t] | Mul [t] deriving (Show, Functor)
--| A handy alias.typeExpra=Fix (ExprFa)
--| "Smart constructors".leaf::a->Expra
leaf =Fix.Leafadd::Expra->Expra->Expra
add e0 e1 =Fix$Add [e0, e1]
mul::Expra->Expra->Expra
mul e0 e1 =Fix$Mul [e0, e1]
--------------------- TILE INTERPRETER---------------------| GeoTrellis types.newtypeTilea=Tile [a] deriving (Show, Functor)
newtypeMultibandTilea=MultibandTile [Tilea] deriving (Show, Functor)
--| ADT of possible values that nodes can handle.dataMaml=LitInt | Single (TileInt) | Banded (MultibandTileInt) deriving (Show)
algebra::ExprFMaml (MaybeMaml) ->MaybeMaml
algebra (Leaf m) =Just m
algebra (Add ms) =sequence ms >>= foldlM (resolve (+)) (Lit0)
algebra (Mul ms) =sequence ms >>= foldlM (resolve (*)) (Lit1)
--| Resolve a binary operation between two `Maml` values.resolve:: (Int->Int->Int) ->Maml->Maml->MaybeMaml
resolve f (Lit n) (Lit m) =Just.Lit$ f n m
resolve f (Lit n) (Single t) =Just.Single$fmap (f n) t
resolve f t@(Single _) n@(Lit _) = resolve f n t
resolve f (Lit n) (Banded t) =Just.Banded$fmap (f n) t
resolve f t@(Banded _) n@(Lit _) = resolve f n t
resolve _ _ _ =Nothingeval::ExprMaml->MaybeMaml
eval = cata algebra
Notes:
Maml is a convenient fusion of MamlKind and Result
The individual directives have been merged back into a single algebra, with fine-grained pattern matching on the child return values handled by some plumbing function (resolve here)
Maybe Maml in ExprF Maml (Maybe Maml) is the "carrier type" we're used to from recursion schemes
The final return type being Maybe Maml was just for convenience of prototyping. It could easily be Validated to collect all errors found along the tree.
The text was updated successfully, but these errors were encountered:
The PR above is a simple use case with simple (co)algebras implemented for unrelated (via subtyping) datatypes. It also shows the fold of a DSL tree into the result, unfolding and folding it into / from JSON and getting an ability to parse json and evaluate query via hylo (basically for free, since at this point we'll have both algebra to fold query and coalgebra to construct it from the JSON).
If RFML was v1 of this little DSL of ours, and the current Directive-based formulation is v2, then moving recursion schemes would be our v3. Luckily, our current architecture isn't far off from RSs already. If you squint, you can see them there (i.e. directives are part of an Algebra, and evaluation is just a catamorphism. Functions like
Interpreter.naive
build the Algebra officially).Before breaking MAML out, we had lamented that making ASTs handle multiple return types would be a nightmare. That wasn't actually true, all we needed was an ADT of possible return types which would then be matched upon at each
Algebra
step. This is the purpose of theResult
ADT in MAML, and we can see a hint of this idea in the original RDD interpreter whereEither
was being returned.So given these tools - Recursion Schemes and a
Result
return type - we can achieve our multityped AST with very little "type shenanigans". Here's a prototype in Haskell:Notes:
Maml
is a convenient fusion ofMamlKind
andResult
algebra
, with fine-grained pattern matching on the child return values handled by some plumbing function (resolve
here)Maybe Maml
inExprF Maml (Maybe Maml)
is the "carrier type" we're used to from recursion schemesMaybe Maml
was just for convenience of prototyping. It could easily beValidated
to collect all errors found along the tree.The text was updated successfully, but these errors were encountered: