[Haskell-beginners] list of integers to list of nats

kane96 at gmx.de kane96 at gmx.de
Sat Feb 20 13:18:57 EST 2010


the function should produce Nothing if there is a negative Int in the input list and otherwise Just with the list of the corresponding Nats

mapM looks like the right function for that, so I tried some examples that work like I need it. But in case of my exercise: 

mapM toEnum [1,2,3,4] :: Nat

doesn't work.


-------- Original-Nachricht --------
> Datum: Sat, 20 Feb 2010 13:19:32 +0100
> Von: "Jonas Almström Duregård" <jonas.duregard at gmail.com>
> An: kane96 at gmx.de
> Betreff: Re: [Haskell-beginners] list of integers to list of nats

> Homework?
> 
> Should mapIntsToNats [-1] be Nothing?
> 
> One way to to do this is to check if any integer in the list is
> negative (for instance using the any function) and if so return
> Nothing, otherwise Just map an Int-to-Nat function across the values
> in the list (there is already such a function in your code).
> 
> A slightly more elegant solution uses the fact that Maybe is a Monad,
> so the function
> 
> mapM  :: Monad m => (a -> m b) -> [a] -> m [b]
> 
> is also mapM :: (Int -> Maybe Nat) -> [Int] -> Maybe [Nat].
> 
> so mapIntsToNats = mapM  f, for some function f :: Int -> Maybe Nat
> 
> Hope this helps
> /Jonas Duregård
> 
> 
> On 20 February 2010 12:39,  <kane96 at gmx.de> wrote:
> > Hi,
> > I have to write a function which maps a list of integers to a list of
> the corresponding nats. The following code is already there:
> >
> > data Nat = Z | S Nat deriving (Eq,Ord,Show)
> >
> > instance Enum Nat where
> >    toEnum i | i < 0        = error "Enum_Nat.toEnum: Negative
> integer"
> >             | i == 0       = Z
> >             | otherwise    = S (toEnum (i-1))
> >
> > the function should be: mapIntsToNats :: [Int] -> Maybe [Nat]
> > so for example: [2,0,1,3] should make: [S (S Z), Z, S Z, S (S (S Z))]
> >
> > how can I do that?
> >
> >
> >
> > --
> > NEU: Mit GMX DSL über 1000,- ¿ sparen!
> > http://portal.gmx.net/de/go/dsl02
> > _______________________________________________
> > Beginners mailing list
> > Beginners at haskell.org
> > http://www.haskell.org/mailman/listinfo/beginners
> >

-- 
NEU: Mit GMX DSL über 1000,- ¿ sparen!
http://portal.gmx.net/de/go/dsl02


More information about the Beginners mailing list