[Haskell-beginners] Applicative on Tree

mike h mike_k_houghton at yahoo.co.uk
Tue Sep 8 13:47:36 UTC 2015


Thanks I'll work through it.
 


     On Tuesday, 8 September 2015, 0:39, Imants Cekusins <imantc at gmail.com> wrote:
   

 > data Tree a = Node a [Tree a]

well here is something that builds and runs. Not sure if the monad laws apply.
watch out for indents!


{-# LANGUAGE InstanceSigs #-}
module TreeApp where

import Debug.Trace
import Data.Char

data Tree a = Node a [Tree a]  deriving (Show)


instance Functor Tree where
  fmap::(a -> b) -> Tree a -> Tree b
  fmap f (Node x l0) = Node (f x) (fmap f <$> l0)


instance Applicative Tree where
  pure::a -> Tree a
  pure a =  Node a []

  (<*>)::Tree (a -> b) -> Tree a -> Tree b
  (<*>) (Node f _) tra = f <$> tra


instance Monad Tree where
  return::a -> Tree a
  return a = pure a

  (>>=)::Tree a -> (a -> Tree b) -> Tree b
  (>>=) (Node x []) amb = amb x
  (>>=) (Node x l0) amb = Node b (m1 <$> l0)
        where (Node b _) = amb x
              m1 ta = ta >>= amb


f::Char->Int
f = digitToInt

mb::Char->Tree Int
mb c = f <$> (pure c)

main::Char -> Char -> IO ()
main a b = print $ tc4 >>= mb
{-
  do
      print ti2
      print ta3
      tm4 <- tc4
-}
  where tc1 = pure a
        ti2 = f <$> tc1
        ta3 = (Node f []) <*> tc1
        tc4 = Node b [tc1]
_______________________________________________
Beginners mailing list
Beginners at haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


  
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20150908/2643ae89/attachment.html>


More information about the Beginners mailing list