
I've tried to solve this but I am failing. I can do this: p0<-panel nb [] e0<-textCtrl p [text:=my_list!!0] but I want to do this on all of my_list, so I tried: let es = map (\x-> textCtrl (panel nb []) [text:=x]) my_list Now, this won't work because the panel nb [] is IO (Panel()) and the parameter to textCtrl needs to be a Panel() How do I get out of IO? Thanks.

On Friday 07 January 2011 17:09:11, b1g3ar5 wrote:
I've tried to solve this but I am failing.
I can do this:
p0<-panel nb [] e0<-textCtrl p [text:=my_list!!0]
but I want to do this on all of my_list, so I tried:
let es = map (\x-> textCtrl (panel nb []) [text:=x]) my_list
Now, this won't work because the panel nb [] is IO (Panel()) and the parameter to textCtrl needs to be a Panel()
How do I get out of IO?
What you need is mapM: es <- mapM (\x -> textCtrl (panel nb []) [text:=x]) my_list mapM :: (Monad m) => (a -> m b) -> [a] -> m [b] applies the function to each list element, runs the resulting action and collects the results. If you don't need the results but only the effects of running the actions (common in IO), use mapM_ :: (Monad m) => (a -> m b) -> [a] -> m () mapM and mapM_ are compositions of sequence :: (Monad m) => [m a] -> m [a] resp. sequence_ :: (Monad m) => [m a] -> m () with map (mapM f list === sequence (map f list)), those are useful on their own too.
Thanks.

Thanks for your reply but it doesn't quite solve the problem. This:
plist <- mapM (\x-> (panel nb [])) my_list
returns [Panel()] and works as you say, but:
elist <- mapM (\x-> (textCtrl (panel nb []) [text := contents x]))
my_list
still won't work because the function panel returns a IO (Panel()) and
so won't do as a parameter to textCtrl.
I can get round this by applying mapM to a list of the indices (of
my_list and plist:
elist <- mapM (\ix-> (textCtrl (plist!!ix) [text := contents (my_list!!
ix)])) [1..4]
but this seems a bit crap. There must be a neat way of doing this.
N
On Jan 7, 4:21 pm, Daniel Fischer
On Friday 07 January 2011 17:09:11, b1g3ar5 wrote:
I've tried to solve this but I am failing.
I can do this:
p0<-panel nb [] e0<-textCtrl p [text:=my_list!!0]
but I want to do this on all of my_list, so I tried:
let es = map (\x-> textCtrl (panel nb []) [text:=x]) my_list
Now, this won't work because the panel nb [] is IO (Panel()) and the parameter to textCtrl needs to be a Panel()
How do I get out of IO?
What you need is mapM:
es <- mapM (\x -> textCtrl (panel nb []) [text:=x]) my_list
mapM :: (Monad m) => (a -> m b) -> [a] -> m [b]
applies the function to each list element, runs the resulting action and collects the results. If you don't need the results but only the effects of running the actions (common in IO), use
mapM_ :: (Monad m) => (a -> m b) -> [a] -> m ()
mapM and mapM_ are compositions of
sequence :: (Monad m) => [m a] -> m [a]
resp.
sequence_ :: (Monad m) => [m a] -> m ()
with map (mapM f list === sequence (map f list)), those are useful on their own too.
Thanks.
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

On Friday 07 January 2011 19:01:43, b1g3ar5 wrote:
Thanks for your reply but it doesn't quite solve the problem. This:
plist <- mapM (\x-> (panel nb [])) my_list
returns [Panel()] and works as you say, but:
elist <- mapM (\x-> (textCtrl (panel nb []) [text := contents x])) my_list
still won't work because the function panel returns a IO (Panel()) and so won't do as a parameter to textCtrl.
I can get round this by applying mapM to a list of the indices (of my_list and plist:
elist <- mapM (\ix-> (textCtrl (plist!!ix) [text := contents (my_list!! ix)])) [1..4]
but this seems a bit crap. There must be a neat way of doing this.
Depends on the semantics of panel, maybe do whatever p <- panel nb [] es <- mapM (\x -> textCtrl p [text := contents x]) my_list moreWith es does what you want. If panel has side effects you need for every item in the list, do whatever es <- mapM (\x -> panel nb [] >>= \p -> textCtrl p [text:=contents x]) my_list moreWith es ought to do it.

Nearly - the first suggestion doesn't work because each es needs a new
panel I can't use the same one each time.
The second suggestion doesn't quite work because the x in [text :=
contents x] is not in scope of the \p function.
Thanks.
N
On Jan 7, 6:29 pm, Daniel Fischer
On Friday 07 January 2011 19:01:43, b1g3ar5 wrote:
Thanks for your reply but it doesn't quite solve the problem. This:
plist <- mapM (\x-> (panel nb [])) my_list
returns [Panel()] and works as you say, but:
elist <- mapM (\x-> (textCtrl (panel nb []) [text := contents x])) my_list
still won't work because the function panel returns a IO (Panel()) and so won't do as a parameter to textCtrl.
I can get round this by applying mapM to a list of the indices (of my_list and plist:
elist <- mapM (\ix-> (textCtrl (plist!!ix) [text := contents (my_list!! ix)])) [1..4]
but this seems a bit crap. There must be a neat way of doing this.
Depends on the semantics of panel, maybe
do whatever p <- panel nb [] es <- mapM (\x -> textCtrl p [text := contents x]) my_list moreWith es
does what you want. If panel has side effects you need for every item in the list,
do whatever es <- mapM (\x -> panel nb [] >>= \p -> textCtrl p [text:=contents x]) my_list moreWith es
ought to do it.
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

On Friday 07 January 2011 19:45:26, b1g3ar5 wrote:
Nearly - the first suggestion doesn't work because each es needs a new panel I can't use the same one each time.
The second suggestion doesn't quite work because the x in [text := contents x] is not in scope of the \p function.
Hmm, Prelude Graphics.UI.WX> :t \w -> mapM (\x -> panel w [] >>= \p -> textCtrl p [text := x]) \w -> mapM (\x -> panel w [] >>= \p -> textCtrl p [text := x]) :: Window a -> [String] -> IO [TextCtrl ()] x is in scope as far as I can tell, the mapM'd lambda is mapM (\x -> (panel nb [] >>= \p -> textCtrl p [text := contents x])) my_list or mapM foo my_list where foo x = do p <- panel nb [] textCtrl p [text := contents x] x is bound in a scope enclosing p's scope, so it is (or should be) available. What does the compiler say exactly?

Yes you're right I had brackets wrong (and the 'where' version is easier to read), thanks. I think the where style works best - or maybe flip and a dangling \x-
.
I maybe slow but I'm learning.
N
On Jan 7, 7:21 pm, Daniel Fischer
On Friday 07 January 2011 19:45:26, b1g3ar5 wrote:
Nearly - the first suggestion doesn't work because each es needs a new panel I can't use the same one each time.
The second suggestion doesn't quite work because the x in [text := contents x] is not in scope of the \p function.
Hmm,
Prelude Graphics.UI.WX> :t \w -> mapM (\x -> panel w [] >>= \p -> textCtrl p [text := x]) \w -> mapM (\x -> panel w [] >>= \p -> textCtrl p [text := x]) :: Window a -> [String] -> IO [TextCtrl ()]
x is in scope as far as I can tell, the mapM'd lambda is
mapM (\x -> (panel nb [] >>= \p -> textCtrl p [text := contents x])) my_list
or
mapM foo my_list where foo x = do p <- panel nb [] textCtrl p [text := contents x]
x is bound in a scope enclosing p's scope, so it is (or should be) available.
What does the compiler say exactly?
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
b1g3ar5
-
Daniel Fischer