Skip to content

Instantly share code, notes, and snippets.

@yingtai
Last active December 28, 2015 10:09
Show Gist options
  • Save yingtai/7484195 to your computer and use it in GitHub Desktop.
Save yingtai/7484195 to your computer and use it in GitHub Desktop.
test of Data.Thorn
{-# LANGUAGE TemplateHaskell, DeriveFunctor, DeriveFoldable #-}
import Prelude hiding (foldr)
import Data.Foldable
import Data.Thorn
data Rose a = Leaf | Rose a (Forest a)
deriving (Functor, Show, Foldable)
data Forest a = Forest [Rose a]
deriving (Functor, Show, Foldable)
r = Rose
l = Leaf
f = Forest
t = r 1 (f [l, l, r 2 (f [l])])
main = print $ foldr (+) 0 t -- OK
{-# LANGUAGE TemplateHaskell, DeriveFunctor, DeriveFoldable #-}
import Prelude hiding (foldr)
import Data.Foldable
import Data.Thorn
data Tree a = Leaf a | Branch a a (Tree a) (Tree a) (Tree a)
-- deriving Show
deriving (Functor, Show, Foldable)
l = Leaf
b = Branch
t = b 1 2 (l 3) (l 4) (b 5 6 (l 7) (l 8) (l 9)) :: Tree Int
fmap' = $(autofmap $[t|Tree|])
-- main = print $ fmap' (+10) t -- OK
-- main = print $ fmap (+10) t -- OK
main = print $ foldr (+) 0 t -- OK
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment