Re: [Haskell-cafe] [Haskell] mapM with Traversables

2011-09-30 Thread Ryan Ingram
You can use Data.Sequence.fromList to go [a] - Seq a, though.

So given

f :: Monad m = a - m b

you have

import Data.Traversable as T
import Data.Sequence as S

g :: Monad m = [a] - m (S.Seq b)
g = T.mapM f . S.fromList

  - ryan

On Wed, Sep 28, 2011 at 6:20 PM, Marc Ziegert co...@gmx.de wrote:

 Hi Thomas,
 this should be on the haskell-cafe or haskell-beginners mailing list.
 Haskell@... is mainly for announcements.


 You have:
  f :: Monad m =
   a - m b
  Data.Traversable.mapM :: (Monad m, Traversable t) =
   (a - m b) - t a - m (t b)

 So, if you define g with
  g a = do Data.Traversable.mapM f a
  or in short
  g = Data.Traversable.mapM f
 , then the type will be
  g :: (Monad m, Traversable t) =
   t a - m (t b)
 instead of
  g :: [a] - m (Seq b)
 .

 Try using ghci to find these things out. It helps to get not confused with
 the types.


 Besides the missing Monad context, g misses a generic way to convert
 between different Traversables, which does not exist. You can only convert
 from any Traversable (imagine a Tree) toList; not all Traversables have a
 fromList function.
 For conversion, you might want to use Foldable and Monoid, fold to untangle
 and mappend to recombine; but any specific fromList function will surely
  be more efficient.

 Regards
 - Marc



  Original-Nachricht 
  Datum: Wed, 28 Sep 2011 17:27:58 -0600
  Von: thomas burt thedwa...@gmail.com
  An: hask...@haskell.org
  Betreff: [Haskell] mapM with Traversables

  Hi -
 
  I have a function, f :: Monad m = a - m b, as well as a list of a's.
  I'd
  like to produce a sequence (Data.Sequence) of b's, given the a's:
 
  g :: [a] - m (Seq b)
  g a = do Data.Traversable.mapM f a   -- type error!
 
  I see that Data.Traversable.mapM f a doesn't work... is this like
 asking
  the compiler to infer the cons/append operation from the type signature
 of
  g?
 
  Do I need to write my own function that explicitly calls the append
  functions from Data.Sequence or can I do something else that would work
  for
  any g :: Traversable t, Traversable u = t a - m (u b) given f :: a
 -
  m
  b?
 
  Thanks for any comments!
  Thomas

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] mapM with Traversables

2011-09-28 Thread Marc Ziegert
Hi Thomas,
this should be on the haskell-cafe or haskell-beginners mailing list. 
Haskell@... is mainly for announcements.


You have:
 f :: Monad m =
  a - m b
 Data.Traversable.mapM :: (Monad m, Traversable t) =
  (a - m b) - t a - m (t b)

So, if you define g with
 g a = do Data.Traversable.mapM f a
 or in short
 g = Data.Traversable.mapM f
, then the type will be
 g :: (Monad m, Traversable t) =
  t a - m (t b)
instead of
 g :: [a] - m (Seq b)
.

Try using ghci to find these things out. It helps to get not confused with the 
types.


Besides the missing Monad context, g misses a generic way to convert between 
different Traversables, which does not exist. You can only convert from any 
Traversable (imagine a Tree) toList; not all Traversables have a fromList 
function.
For conversion, you might want to use Foldable and Monoid, fold to untangle and 
mappend to recombine; but any specific fromList function will surely  be more 
efficient.

Regards
- Marc



 Original-Nachricht 
 Datum: Wed, 28 Sep 2011 17:27:58 -0600
 Von: thomas burt thedwa...@gmail.com
 An: hask...@haskell.org
 Betreff: [Haskell] mapM with Traversables

 Hi -
 
 I have a function, f :: Monad m = a - m b, as well as a list of a's.
 I'd
 like to produce a sequence (Data.Sequence) of b's, given the a's:
 
 g :: [a] - m (Seq b)
 g a = do Data.Traversable.mapM f a   -- type error!
 
 I see that Data.Traversable.mapM f a doesn't work... is this like asking
 the compiler to infer the cons/append operation from the type signature of
 g?
 
 Do I need to write my own function that explicitly calls the append
 functions from Data.Sequence or can I do something else that would work
 for
 any g :: Traversable t, Traversable u = t a - m (u b) given f :: a -
 m
 b?
 
 Thanks for any comments!
 Thomas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe