State separation/combination pattern question

I'm looking for a pattern to use for "state separation" in my application. I need to write two "stateful libraries". One is a partitioned in- memory store, the other a disk based store with an in-memory cache fronting it. Both store modules need the IO and State monad. My aim is to write the libraries independently from one another in such a way that they are not aware of the context they will be used in. Both stores are called from a breadth first search loop. The example below extracts the essence of my current approach. foo is function in one of the store modules, bar is from the other type of store. Both manipulate their type of state (StateA, StateB). They extract their slice of the "global" application level state (AppStateRec). What I don't like is that the code in foo and bar know about the AppStateRec and that they need to get the "a", or "b" slot respectively. The store modules should not have such coupling with their client code. I've tried to thread the two states (StateA and StateB) using a chain of StateT ... StateT ..., but couldn't really make that work. It seems rather arbitrary in this case which state to make the inner/ outer one and depending on this ordering the "lifts" have to go with one or the other set of store calls. What I'm really looking for is not so much the chaining of StateT compositions, but rather the isolation of StateA from StateB while they both flow from the search loop into the respective library calls (foo, bar) transparently to the application programmer. I'm hoping there's a way to have the loop be in a State monad whose content is the sum of the two states that are needed for the foo and bar call made to the stores from inside the loop. The calls sites for foo and bar should then extract the right component of the global state and thread only that state through into the modules. Sounds like magic, but how close can I get? I've been unable to find a pattern on the WIKI or the web that refers to this type of "state composition" (or I may not have recognized the match). I trust many of you have run into this and there's an obvious and straight forward best way to address this type of state handling. Thanks, - Reto -------------------------- -- ghci -fglasgow-exts ... -- type StateA = [Integer] type StateB = [Integer] data AppStateRec = AppStateRec { a :: StateA, b :: StateB } deriving Show foo :: MonadState AppStateRec m => m () foo = do st <- get put $ st { a = 1:(a st) } bar :: MonadState AppStateRec m => m () bar = do st <- get put $ st { b = 2:(b st) } type Eval a = StateT AppStateRec Identity a exec :: Eval () exec = do foo bar foo foo bar go = runIdentity $ runStateT exec AppStateRec { a = [], b = [] } Prints: ((),AppStateRec {a = [1,1,1], b = [2,2]})

Reto Kramer wrote:
What I'm really looking for is not so much the chaining of StateT compositions, but rather the isolation of StateA from StateB while they both flow from the search loop into the respective library calls (foo, bar) transparently to the application programmer.
How about this? -- these two should be defined in two separate library modules, of course trueFoo :: MonadState StateA m => m () trueBar :: MonadState StateB m => m () data AppStateRec = AppStateRec { a :: StateA, b :: StateB } type Eval a = StateT AppStateRec Identity a exec :: Eval () exec = do foo bar foo foo bar where -- you might want to define combinators for the following pattern, -- but for just two functions this is good enough foo = do AppStateRec a b <- get a' <- runStateT trueFoo a put $ AppStateRec a' b bar = do AppStateRec a b <- get b' <- runStateT trueBar b put $ AppStateRec a b' -Udo -- "In the software business there are many enterprises for which it is not clear that science can help them; that science should try is not clear either." -- E. W. Dijkstra

On 12/22/06, Reto Kramer
What I'm really looking for is not so much the chaining of StateT compositions, but rather the isolation of StateA from StateB while they both flow from the search loop into the respective library calls (foo, bar) transparently to the application programmer. I'm hoping there's a way to have the loop be in a State monad whose content is the sum of the two states that are needed for the foo and bar call made to the stores from inside the loop. The calls sites for foo and bar should then extract the right component of the global state and thread only that state through into the modules. Sounds like magic, but how close can I get?
My first impulse would be to define classes for each type of state and have a top-level monad which is instances of each of those. Using your example: (your code is > quoted, mine < quoted)
-- ghci -fglasgow-exts ... -- type StateA = [Integer]
At this point, I would add: < class Monad m => MonadStateA m < where getA :: m StateA < modifyA :: (StateA -> StateA) -> m () < < putA :: MonadStateA m => StateA -> m () < putA = modifyA . const
type StateB = [Integer]
And, similarly here: < class Monad m => MonadStateB m < where getB :: m StateB < modifyB :: (StateB -> StateB) -> m () < < putB :: MonadStateB m => StateB -> m () < putB = modifyB . const
data AppStateRec = AppStateRec { a :: StateA, b :: StateB } deriving Show
These functions change in two ways: first, their type signatures now use the new classes I defiend above. Second, by including the modify functions, I can make the function bodies somewhat shorter.
foo :: MonadState AppStateRec m => m () foo = do st <- get put $ st { a = 1:(a st) }
< foo :: MonadStateA m => m () < foo = modifyA (1:)
bar :: MonadState AppStateRec m => m () bar = do st <- get put $ st { b = 2:(b st) }
< bar :: MonadStateB m => m () < bar = modifyB (2:) At this point, you have several options. If you're willing to allow undecidable instances, you can write instances like: < instance MonadState AppStateRec m => MonadStateA m < where getA = get >>= return . a < modifyA f = do st <- get < put (st { a = f (a st) }) < < instance MonadState AppStateRec m => MonadStateB m < where getB = get >>= return . b < modifyB f = do st <- get < put (st { b = f (b st) }) And the remainder of your code will run as you wrote it. An alternative without using undecidable instances is to write the instances manually. However, in that case, I believe you will have to write your monad as a newtype instead of a type, and then rely on either GHC's ability to derive instances of MonadState etc. or else write those instances yourself as well. Hope that helps. /g
type Eval a = StateT AppStateRec Identity a
exec :: Eval () exec = do foo bar foo foo bar
go = runIdentity $ runStateT exec AppStateRec { a = [], b = [] }
Prints: ((),AppStateRec {a = [1,1,1], b = [2,2]}) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- It is myself I have never met, whose face is pasted on the underside of my mind.

Another option is to use the HList library (though this can involve a learning curve). Essentially your monad is a state monad and its state is a big tuple constrained to contain at least whichever types you ask of it. Consider
foo :: (HOccurs StateA st, ...other HList properties..., MonadState st m) => m () foo = do st <- gets hOccurs -- note the gets hOccurs put $ st { a = 1:(a st) }
bar :: (HOccurs StateB st, ...other HList properties..., MonadState st m) => m () bar = do st <- gets hOccurs put $ st { b = 2:(b st) }
When you use foo and bar together, the constraints the state of your
monad must satisfy accumulate, i.e. exec would require both HOccurs
properties of its monad's state.
This approach would stretch the type checker more than the others. And
I can't say I've ever used it on a large scale, but it has worked on
smaller examples. Also, "too much polymorphism" can cause some issues
with all of the library's type machinery.
But I think it's an attractive option if it fits your needs.
Good luck,
Nick
On 12/23/06, J. Garrett Morris
On 12/22/06, Reto Kramer
wrote: What I'm really looking for is not so much the chaining of StateT compositions, but rather the isolation of StateA from StateB while they both flow from the search loop into the respective library calls (foo, bar) transparently to the application programmer. I'm hoping there's a way to have the loop be in a State monad whose content is the sum of the two states that are needed for the foo and bar call made to the stores from inside the loop. The calls sites for foo and bar should then extract the right component of the global state and thread only that state through into the modules. Sounds like magic, but how close can I get?
My first impulse would be to define classes for each type of state and have a top-level monad which is instances of each of those. Using your example: (your code is > quoted, mine < quoted)
-- ghci -fglasgow-exts ... -- type StateA = [Integer]
At this point, I would add:
< class Monad m => MonadStateA m < where getA :: m StateA < modifyA :: (StateA -> StateA) -> m () < < putA :: MonadStateA m => StateA -> m () < putA = modifyA . const
type StateB = [Integer]
And, similarly here:
< class Monad m => MonadStateB m < where getB :: m StateB < modifyB :: (StateB -> StateB) -> m () < < putB :: MonadStateB m => StateB -> m () < putB = modifyB . const
data AppStateRec = AppStateRec { a :: StateA, b :: StateB } deriving Show
These functions change in two ways: first, their type signatures now use the new classes I defiend above. Second, by including the modify functions, I can make the function bodies somewhat shorter.
foo :: MonadState AppStateRec m => m () foo = do st <- get put $ st { a = 1:(a st) }
< foo :: MonadStateA m => m () < foo = modifyA (1:)
bar :: MonadState AppStateRec m => m () bar = do st <- get put $ st { b = 2:(b st) }
< bar :: MonadStateB m => m () < bar = modifyB (2:)
At this point, you have several options. If you're willing to allow undecidable instances, you can write instances like:
< instance MonadState AppStateRec m => MonadStateA m < where getA = get >>= return . a < modifyA f = do st <- get < put (st { a = f (a st) }) < < instance MonadState AppStateRec m => MonadStateB m < where getB = get >>= return . b < modifyB f = do st <- get < put (st { b = f (b st) })
And the remainder of your code will run as you wrote it. An alternative without using undecidable instances is to write the instances manually. However, in that case, I believe you will have to write your monad as a newtype instead of a type, and then rely on either GHC's ability to derive instances of MonadState etc. or else write those instances yourself as well.
Hope that helps.
/g
type Eval a = StateT AppStateRec Identity a
exec :: Eval () exec = do foo bar foo foo bar
go = runIdentity $ runStateT exec AppStateRec { a = [], b = [] }
Prints: ((),AppStateRec {a = [1,1,1], b = [2,2]}) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- It is myself I have never met, whose face is pasted on the underside of my mind. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Reto, On Thu, Dec 21, 2006 at 10:11:22PM -0800, Reto Kramer wrote:
I've tried to thread the two states (StateA and StateB) using a chain of StateT ... StateT ..., but couldn't really make that work.
That is how I would write it; I have attached code for your example.
It seems rather arbitrary in this case which state to make the inner/ outer one
The choice is indeed arbitrary.
and depending on this ordering the "lifts" have to go with one or the other set of store calls.
If you don't mind turning on overlapping and undecidable instances then you don't need to manually lift things at all. Thanks Ian
participants (5)
-
Ian Lynagh
-
J. Garrett Morris
-
Nicolas Frisby
-
Reto Kramer
-
Udo Stenzel