Delaling with State StateT and IO in the same function

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

On 2/26/07, Alfonso Acosta
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)
I may be missing something, but why are you using both State and StateT? Maybe I don't understand your code, but it seems like you could be using StateT everywhere you're currently using State. Also, your type signatures would be easier to read if you defined a type synonym for your instantiation of StateT, e.g.: type AlfonsoM s = StateT s IO () and then everywhere you write (StateT s IO ()) now, you could write (AlfonsoM s) instead. Cheers, Kirsten -- Kirsten Chevalier* chevalier@alum.wellesley.edu *Often in error, never in doubt "...People who mind their own business die of boredom at thirty."--Robertson Davies

On 2/27/07, Kirsten Chevalier
I may be missing something, but why are you using both State and StateT? Maybe I don't understand your code, but it seems like you could be using StateT everywhere you're currently using State.
Well, as far as I know using "StateT s IO a" for the input functions would force the state and value of their monad to stay within IO. That restriction dissapears by using barely "State s a"
Also, your type signatures would be easier to read if you defined a type synonym for your instantiation of StateT, e.g.:
type AlfonsoM s = StateT s IO ()
and then everywhere you write (StateT s IO ()) now, you could write (AlfonsoM s) instead.
Thanks for the suggestion, I'll make use of it :)

On 2/26/07, Alfonso Acosta
On 2/27/07, Kirsten Chevalier
wrote: I may be missing something, but why are you using both State and StateT? Maybe I don't understand your code, but it seems like you could be using StateT everywhere you're currently using State.
Well, as far as I know using "StateT s IO a" for the input functions would force the state and value of their monad to stay within IO. That restriction dissapears by using barely "State s a"
Ah, ok. So what if you changed your netlist function so that the type sig would be: 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 IO (State s ()) I didn't follow your code well enough to be sure that this would help, but I think it might. Or why not: 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 IO s which seems to me like it would be even simpler, unless you're planning on composing calls to netlist together (and from the code you gave, I can't tell whether you are.) If your code is such that refactoring it to have either of those types wouldn't make sense, stating the reasons why should clarify things for the rest of us. Cheers, Kirsten -- Kirsten Chevalier* chevalier@alum.wellesley.edu *Often in error, never in doubt "Aw, honey, you can keep what's in my pockets, but send me back my pants." --Greg Brown

On 2/27/07, Kirsten Chevalier
So what if you changed your netlist function so that the type sig would be:
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 IO (State s ())
Or why not:
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 IO s
Uhm, this looks better, I'll try with this one and see what I get, I anyway suspect I'll have a hard time because of the nested monads

I don't know if this will help or not, but there's a basic StateT
example on the haskell wiki that you could look at, to see how to deal
with State in general. The code is at
http://www.haskell.org/haskellwiki/Simple_StateT_use and is thanks to
Don Stewart. Maybe I'll just paste the code with a few more comments
(with the warning that I'm a newbie as well):
import Control.Monad.State
main :: IO ()
main = runStateT code [1..] >> return ()
-- Here, the state is just a simple stack of integers. runStateT is
the equivalent
-- in the StateT monad of runState in the State monad
code :: StateT [Integer] IO ()
code = do
x <- pop -- pop an item out of the stack
io $ print x -- now in the INNER monad, perform an action
return ()
--
-- pop the next unique off the stack
--
pop :: StateT [Integer] IO Integer
-- This type signature is correct, but it's the reason you have to be
-- careful with StateT. pop really has nothing to do with IO, but it has
-- been 'tainted' by IO because it's being done together with it
pop = do
(x:xs) <- get -- get the list that's currently in the stack
put xs -- put back all but the first
return x -- return the first
io :: IO a -> StateT [Integer] IO a
-- transform an action from being in the inner monad (in this case IO), to
-- being in the outer monad. since IO is so familiar, it's been written already
-- and it's called liftIO
io = liftIO
Gurus, please check my comments to be sure I haven't said something stupid!
Hope this helps.
Andrew
On 2/26/07, Alfonso Acosta
On 2/27/07, Kirsten Chevalier
wrote: So what if you changed your netlist function so that the type sig would be:
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 IO (State s ())
Or why not:
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 IO s
Uhm, this looks better, I'll try with this one and see what I get, I anyway suspect I'll have a hard time because of the nested monads _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Alfonso Acosta
-
Andrew Wagner
-
Kirsten Chevalier