[Haskell-cafe] Delaling with State StateT and IO in the same function

Alfonso Acosta alfonso.acosta at gmail.com
Mon Feb 26 18:13:51 EST 2007


Hello,

I know StateT is exactly aimed at dealing with a state and an inner
monad but I have an example in which I have to mix State and IO and in
which I didn't get to an elegant solution using StateT.


I have a higher order function which gets some State processing
functions as input, makes some internal operations with IO and has to
return a State as output.


My (ugly) function interface is

netlist :: DT.Traversable f =>
           (State s (S HDPrimSignal) -> State s  v ) -> -- new
           (State s (Type,v) -> S v -> State s ())   -> -- define
           State s (f HDPrimSignal) ->                  -- the graph
           StateT s IO ()


The returned type is a StateT and the only way in which I succesfully
managed to internally work with both State and StateT is converting
from the former to the later one using this function (not elegant at
all)

state2StateT :: Monad m => State s a -> StateT s m a
state2StateT f  = StateT (return.runState f)

I tried avoiding to use state2StateT by changing the interface to

netlist :: DT.Traversable f =>
           (State s (S HDPrimSignal) -> State s  v ) -> -- new
           (State s (Type,v) -> S v -> State s ())   -> -- define
           State s (f HDPrimSignal) ->                  -- the graph
           State s (IO ())


but the function ended up being even uglier and I had to be care full
about all the internal IO actions being executed (it is aesy to
formget about it), let me show a (quite stupid) example

myState :: State () (IO ())
myState = (return $ putStrLn "first line") >> (return $ putStrLn "second line")

> eval myState ()
second line

The first line is obviously lost


Here is the full code of my function (many type definitions are
missing but I hope it is understandable anyway)

import qualified Data.Traversable as DT (Traversable(mapM))
import qualified Control.Monad.Trans
import Language.Haskell.TH(Type)


netlist :: DT.Traversable f =>
           (State s (S HDPrimSignal) -> State s  v ) -> -- new
           (State s (Type,v) -> S v -> State s ())   -> -- define
           State s (f HDPrimSignal) ->                  -- the graph
           StateT s IO ()
-- Generates a netlist given:
--  new: generates the new (and normally unique) tag of every node given
--       the iteration state which is updated as well.
--  define: given the tag of a node,
--          current iteration state, its type, and the tag of its children,
--          generates the netlist of that node, updating the iteration state
--  pSignals: the graph itself, a traversable collection of root
--            signals including the initial state of the iteration

-- It returns the final iteration state and the tags of outputs
-- (root primitivesignals)
netlist new define pSignals =
  do f   <-  state2StateT pSignals
     tab <-  lift table
     let -- gather :: State s HDPrimSignal  -> StateT s IO v
         gather sm =
            do HDPrimSignal t node <- sm
               visited <- lift (find tab node)
               case visited of
                 Just v  -> return v
                 Nothing -> do let sP = deref node
                               v'  <- state2StateT (new (return sP))
                               lift (extend tab node v')
                               sV <- DT.mapM (gather.return) sP
                               state2StateT (define (return (t,v')) sV)
                               return v'

      in DT.mapM (gather.return) f >> return()

----
just in case it helps

table :: IO (Table a b)
find :: Table a b -> Ref a -> IO (Maybe b)
extend :: Table a b -> Ref a -> b -> IO ()

----

Maybe is asking too much but would anyone be able to provide a more
elegant netlist function which ...

option a) returns StateT but doesn't make use of state2StateT?

or

option b) returns State but doesnt end up being messy?

Thanks in advance,

Alfonso Acosta


More information about the Haskell-Cafe mailing list