[Haskell-cafe] State & nested structures
Dupont Corentin
corentin.dupont at gmail.com
Fri Oct 29 10:05:54 EDT 2010
Hello the list,
I have another silly question.
In my software I have a very common pattern:
--in file A.hs
module A where
data A = A {b :: B, i :: Int}
type SA x = State A x
-- many functions with SA x
--in file B.hs
data B = B {r :: Int}
type SB x = State B x
-- many functions with SB x
Of course in module A I'm calling some functions of module B.
I'd like to know if it's possible, in a function of type SA, to call a
function of type SB,
without actually executing the State SB.
I just wanna tell him "Hey look, you can construct a SA from a SB like
this!"
For now I have this:
bToA:: (B -> B) -> A -> A
bToA bb = (λa -> a{b = bb (b a)})
useB :: SB () -> SA ()
useB = modify . bToA . execState
Can I get rid of the execState?
Also, I can't manage to write the more generic function SB x -> SA x.
Cheers,
Corentin
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20101029/0591d932/attachment.html
More information about the Haskell-Cafe
mailing list