Created
August 30, 2019 15:30
-
-
Save jjant/d00a04c43f219995ed47152a969353a0 to your computer and use it in GitHub Desktop.
mutate leaves of tree
This file contains hidden or 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
{-# LANGUAGE ScopedTypeVariables, DeriveFunctor, DeriveTraversable, | |
DeriveFoldable #-} | |
import Data.Foldable (traverse_) | |
import qualified Data.IORef as IORef | |
import Data.IORef (IORef) | |
data AST ident | |
= Var ident | |
| Lam ident | |
(AST ident) | |
| App (AST ident) | |
(AST ident) | |
deriving (Functor, Traversable, Foldable, Show) | |
idExpr :: AST String | |
idExpr = Lam "x" (Var "x") | |
toMut :: AST ident -> IO (AST (IORef ident)) | |
toMut (Var ident) = Var <$> IORef.newIORef ident | |
toMut (Lam ident rest) = Lam <$> IORef.newIORef ident <*> toMut rest | |
toMut (App ast1 ast2) = App <$> (toMut ast1) <*> (toMut ast2) | |
renameStuff :: (String -> String) -> AST (IORef String) -> IO () | |
renameStuff f ast = traverse_ (flip IORef.modifyIORef f) ast | |
main :: IO () | |
main = do | |
mutAst <- toMut idExpr | |
renameStuff ("Sup_" ++) mutAst | |
pureAst <- traverse IORef.readIORef mutAst | |
putStrLn $ show $ pureAst | |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment