IO Monad/ haskelldb strange error?

line << 39 works fine line 56 doesn't. Why? Isn't both a IO monad (because of the print statements) After commenting out 56 it compiles fine Any suggestion appreciated.. I'm struggling for some hours now.. module Modules.ObjectTree where import Debug.Trace import Data.FunctorM import DBUtils import qualified DB.VT.Ezcontentobject_tree as EOT import qualified DB.VT.Ezcontentobject as CO import Database.HaskellDB.HDBRec import Database.HaskellDB import Database.HaskellDB.Query as Q import Data.Tree import Monad import Control.Monad.Trans import Maybe import qualified List instance FunctorM Tree where fmapM f (Node a forest) = do a' <- f a forest' <- mapM (fmapM f) forest return $ Node a' forest' type ObjectTree a = Tree (Record a) truncTree 1 (Node a _) = Node a [] truncTree x (Node a forest) = Node a $ map (truncTree (x-1)) forest oT con = do print "blah" -- because of this we should have a simple IO Monad ? lookupField con (CO.name) (CO.ezcontentobject) (CO.xid) (constant (1 :: Int)) >>= print :: IO () -- <<<<<<<<<<<<<<<<<<<<<<<<< 39 return "blah" -- printObjectsAsTree :: MonadIO m => ((Database -> m a) -> m a) -> Int -> IO () printObjectsAsTree con startid= do print "test" root <- liftM head $ lRS (EOT.parent_node_id) (constant (startid :: Int)) print root --showRS root >>= putStrLn node <- po root node_show <- fmapM showRS node return $ drawTree node_show -- return "end" where lRS = lookupFieldRS con (EOT.ezcontentobject_tree) po root = let root_id = (root!(EOT.node_id) :: Int) in do print "dumm" -- IO Monad too ? print (root!(EOT.node_id)) lookupField con (CO.name) (CO.ezcontentobject) (CO.xid) (constant (1 :: Int)) >>= print -- <<<<<<<<<<<<<< 56 return $ Node root [] --childs <- lRS (EOT.parent_node_id) (constant root_id) --mapM_ (\r -> r!(EOT.node_id)) childs >>= print showRS r = do -- name <- lookupField con (CO.name) (CO.ezcontentobject) (CO.xid) (constant 1) >>= print return "ab" :: IO String --return $ (show $ r!node_id) ++ " (" ++ (fromJust name) ++ " )" ----------------------------------------------- || Preprocessing executables for dbez-0.0... || Building dbez-0.0... || Chasing modules from: db_ez.hs || [1 of 6] Skipping DBUtils ( DBUtils.hs, dist/build/db_ez/db_ez-tmp/DBUtils.o ) || [2 of 6] Skipping DB.VT.Ezcontentobject_tree ( DB/VT/Ezcontentobject_tree.hs, dist/build/db_ez/db_ez-tmp/DB/VT/Ezcontentobject_tree.o ) || [3 of 6] Skipping DB.VT.Ezcontentobject ( DB/VT/Ezcontentobject.hs, dist/build/db_ez/db_ez-tmp/DB/VT/Ezcontentobject.o ) || [4 of 6] Compiling Modules.ObjectTree ( Modules/ObjectTree.hs, dist/build/db_ez/db_ez-tmp/Modules/ObjectTree.o ) || Modules/ObjectTree.hs|43| 0: || Couldn't match `DB.VT.Ezcontentobject_tree.Contentobject_id' || against `DB.VT.Ezcontentobject.Contentclass_id' || Expected type: RecCons DB.VT.Ezcontentobject_tree.Contentobject_id || (Maybe Int) || vr || Inferred type: RecCons DB.VT.Ezcontentobject.Contentclass_id || Int || vr1 || When using functional dependencies to combine || Database.HaskellDB.Database.GetRec (RecCons f (Expr a) er) || (RecCons f a vr), || arising from the instance declaration at Imported from Database.HaskellDB.Database || Database.HaskellDB.Database.GetRec (RecCons DB.VT.Ezcontentobject_tree.Contentobject_id || (Expr (Maybe Int)) [...] || (RecCons DB.VT.Ezcontentobject_tree.Sort_order || (Expr (Maybe Int)) || RecNil)))))))))))))))) || (RecCons DB.VT.Ezcontentobject.Contentclass_id Int vr), arising from use of `lookupFieldRS' at Modules/ObjectTree.hs|52| 14-26 || When generalising the type(s) for `printObjectsAsTree'

Hi I've tried as an exercise to learn how to use the state monad to create a tree this way: module Main where import Control.Monad.State import Data.Tree import Random createTree :: Int -> Int -> (Tree Int, Int) createTree 4 = runState $ State $ \s -> (Node s [] , s+1) -- stop at level 4 createTree level = runState (do item <- State $ (\s -> (s,s+1)) forest <- State $ (\s -> foldr (\_ (for, n) -> let (l, n') = (createTree (level + 1) n) in (l:for,n')) ([], s) (replicate level ()) ) return $ Node item (reverse forest) ) main = do putStrLn $ drawTree $ fmap show $ fst $ createTree 2 0 ---- output ---------- 0 | +- 1 -- features: auto numbering and level n exists of n Nodes | | | +- 2 | | | +- 3 | | | `- 4 | `- 5 | +- 6 | +- 7 | `- 8 | | 2 3 ... Nodes per level I think this line is not very easy to understand.. the (replecate part is just a dummy to count the iterations) forest <- State $ (\s -> foldr (\_ (for, n) -> let (l, n') = (createTree (level + 1) n) in (l:for,n')) ([], s) (replicate level ()) ) Is there a better way to do this? This problem is similar to adding numbers to each tree item Marc

Is there a better way to do this? This problem is similar to adding numbers to each tree item
Marc
Yes. The feature you wanted is "replicateM". The point of a State monad is you probably never have to touch the State data constructor:
module Main where
import Control.Monad.State import Data.Tree
type Supply = State Int unique :: Supply Int unique = do value <- get put (succ value) return value
createTree :: Int -> Supply (Tree Int) createTree 4 = do me <- unique return (Node me []) createTree level = do me <- unique children <- replicateM level (createTree (succ level)) return (Node me children)
main = do putStrLn $ drawTree $ fmap show $ evalState (createTree 2) 0
Or even more tersely:
import Control.Monad
createTree :: Int -> Supply (Tree Int) createTree 4 = liftM (`Node` []) unique createTree level = liftM2 Node unique (replicateM level (createTree (succ level)))

Marc Weber wrote:
I've tried as an exercise to learn how to use the state monad to create a tree this way:
createTree :: Int -> Int -> (Tree Int, Int) createTree 4 = runState $ State $ \s -> (Node s [] , s+1) -- stop at level 4 createTree level = runState (do item <- State $ (\s -> (s,s+1)) forest <- State $ (\s -> foldr (\_ (for, n) -> let (l, n') = (createTree (level + 1) n) in (l:for,n')) ([], s) (replicate level ()) ) return $ Node item (reverse forest) )
Isn't the whole point of the State Monad *not* to thread the state through every function explicitly? It should probably look like this (untested code): createTree :: Int -> Int -> (Tree Int, Int) createTree = runState . createTree' bump :: State Int Int bump = do s <- get ; put $! s+1 ; return s createTree' :: Int -> State (Tree Int) createTree' 4 = do s <- bump ; return $ Node s [] createTree' level = do item <- bump forest <- replicateM (createTree' $ level+1) level return $ Node item forest or even createTree' level = liftM2 Node bump (replicateM (createTree' $ level+1) level) Udo. -- Two rules get you through life: If it's stuck and it's not supposed to be, WD-40 it. If it's not stuck and it's supposed to be, duct tape it. -- The Duct Tape Guys' book "WD-40"

On Tue, Aug 08, 2006 at 02:30:39PM +0200, Marc Weber wrote:
Is there a better way to do this?
In this case it is quite easy to separate the task into two smaller ones: - creating the tree with a desired shape - numbering the nodes in post-order The first task is naturally expressed without monads. Best regards Tomasz
participants (4)
-
Chris Kuklewicz
-
Marc Weber
-
Tomasz Zielonka
-
Udo Stenzel