Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Selecting single result of function application  to list
      (Hugo Ferreira)
   2. Re:  Selecting single result of function application to list
      (Michael Xavier)
   3. Re:  Selecting single result of function  application to list
      (Daniel Schoepe)
   4. Re:  Selecting single result of function application to list
      (Hugo Ferreira)
   5. Re:  Selecting single result of function  application to list
      (Daniel Fischer)
   6.  Haskell wants the type,  but I only know the class.
      (Amy de Buitl?ir)
   7. Re:  Selecting single result of function application to list
      (Markus L?ll)
   8. Re:  Haskell wants the type,      but I only know the class.
      (David McBride)


----------------------------------------------------------------------

Message: 1
Date: Thu, 03 Nov 2011 16:07:01 +0000
From: Hugo Ferreira <h...@inescporto.pt>
Subject: [Haskell-beginners] Selecting single result of function
        application     to list
To: beginners@haskell.org
Message-ID: <4eb2bc25.5040...@inescporto.pt>
Content-Type: text/plain; charset=ISO-8859-15; format=flowed

Hello,

Apologies the simpleton question but I would like to
know how it is done in Haskell. I have a list of values,
and I am applying a function to each of these elements.
The result is a Maybe. I would like to return the first
occurrence which is not a Nothing.

I am considering something like:

selectOne f = take 1 . filter (\e -> case e of
                                        Just _ -> True
                                        _ -> False ) . map f

I this how it is done?

TIA,
Hugo F.





------------------------------

Message: 2
Date: Thu, 3 Nov 2011 09:26:40 -0700
From: Michael Xavier <nemesisdes...@gmail.com>
Subject: Re: [Haskell-beginners] Selecting single result of function
        application to list
To: Hugo Ferreira <h...@inescporto.pt>
Cc: beginners@haskell.org
Message-ID:
        <CANk=zmg81qa5whh03uv2z3rhecysvv+mqjvfvk0gvgnkndg...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Here's how I'd do it:

import Data.Maybe (catMaybes)

list = ["hi", "blah", "foo"]

firstJust = head . catMaybes

selectOne f = firstJust . map f

myFunction :: String -> Maybe Int
myFunction = undefined

main = print $ selectOne myFunction list

catMaybes will take a list of Maybe a and reduce it to a list of a,
throwing out all the Nothings.

As you'll learn from working with Maybe a lot, if you're casing off of a
maybe value, there's probably a better way to do it. Functions like
"catMaybes" and "maybe" and especially the Monad instance of Maybe are
really helpful for avoiding this ugly branching logic.

On Thu, Nov 3, 2011 at 9:07 AM, Hugo Ferreira <h...@inescporto.pt> wrote:
>
>
> I am considering something like:
>
> selectOne f = take 1 . filter (\e -> case e of
>                                       Just _ -> True
>                                       _ -> False ) . map f
>


-- 
Michael Xavier
http://www.michaelxavier.net
LinkedIn <http://www.linkedin.com/pub/michael-xavier/13/b02/a26>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111103/30b5a8d3/attachment-0001.htm>

------------------------------

Message: 3
Date: Thu, 03 Nov 2011 17:30:48 +0100
From: Daniel Schoepe <dan...@schoepe.org>
Subject: Re: [Haskell-beginners] Selecting single result of function
        application to list
To: Hugo Ferreira <h...@inescporto.pt>, beginners@haskell.org
Message-ID: <87obwt183r.fsf@gilead.invalid>
Content-Type: text/plain; charset="us-ascii"

On Thu, 03 Nov 2011 16:07:01 +0000, Hugo Ferreira <h...@inescporto.pt> wrote:
> Hello,
> 
> Apologies the simpleton question but I would like to
> know how it is done in Haskell. I have a list of values,
> and I am applying a function to each of these elements.
> The result is a Maybe. I would like to return the first
> occurrence which is not a Nothing.

You can use catMaybes from Data.Maybe:

import Data.Maybe

selectOne f = head . catMaybes . map f

Note that is a partial function; it will crash if f returns Nothing for
each element.

Cheers,
Daniel
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 835 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111103/b041ef51/attachment-0001.pgp>

------------------------------

Message: 4
Date: Thu, 03 Nov 2011 16:33:15 +0000
From: Hugo Ferreira <h...@inescporto.pt>
Subject: Re: [Haskell-beginners] Selecting single result of function
        application to list
To: Michael Xavier <nemesisdes...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4eb2c24b.5030...@inescporto.pt>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

On 11/03/2011 04:26 PM, Michael Xavier wrote:
> Here's how I'd do it:
>
> import Data.Maybe (catMaybes)
>
> list = ["hi", "blah", "foo"]
>
> firstJust = head . catMaybes
>
> selectOne f = firstJust . map f
>
> myFunction :: String -> Maybe Int
> myFunction = undefined
>
> main = print $ selectOne myFunction list
>
> catMaybes will take a list of Maybe a and reduce it to a list of a,
> throwing out all the Nothings.
>
> As you'll learn from working with Maybe a lot, if you're casing off of a
> maybe value, there's probably a better way to do it. Functions like
> "catMaybes" and "maybe" and especially the Monad instance of Maybe are
> really helpful for avoiding this ugly branching logic.
>

Thanks Michael. I am planning to compose functions that return Maybe
so I will, as you pointed out, be looking at the Maybe Monad.

Rgards,
Hugo F.

> On Thu, Nov 3, 2011 at 9:07 AM, Hugo Ferreira <h...@inescporto.pt
> <mailto:h...@inescporto.pt>> wrote:
>
>
>     I am considering something like:
>
>     selectOne f = take 1 . filter (\e -> case e of
>                                            Just _ -> True
>                                            _ -> False ) . map f
>
>
>
> --
> Michael Xavier
> http://www.michaelxavier.net
> LinkedIn <http://www.linkedin.com/pub/michael-xavier/13/b02/a26>
>




------------------------------

Message: 5
Date: Thu, 3 Nov 2011 17:34:24 +0100
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] Selecting single result of function
        application to list
To: beginners@haskell.org
Message-ID: <201111031734.24253.daniel.is.fisc...@googlemail.com>
Content-Type: Text/Plain;  charset="iso-8859-1"

On Thursday 03 November 2011, 17:07:01, Hugo Ferreira wrote:
> Hello,
> 
> Apologies the simpleton question but I would like to
> know how it is done in Haskell. I have a list of values,
> and I am applying a function to each of these elements.
> The result is a Maybe. I would like to return the first
> occurrence which is not a Nothing.
> 
> I am considering something like:
> 
> selectOne f = take 1 . filter (\e -> case e of
>                                         Just _ -> True
>                                         _ -> False ) . map f
> 
> I this how it is done?

In Data.Maybe, there's

catMaybes :: [Maybe a] -> [a]
mapMaybe :: (a -> Maybe b) -> [a] -> [b]
listToMaybe :: [a] -> Maybe a
maybeToList :: Maybe a -> [a]

Your selectOne f is 
take 1 . catMaybes . map f
or
take 1 . mapMaybe f

Alternatively, you could use the MonadPlus class from Control.Monad, which 
provides mzero, mplus and msum, with Maybe's MonadPlus instance

selectOne f = maybeToList . msum . map f




------------------------------

Message: 6
Date: Thu, 3 Nov 2011 16:55:32 +0000 (UTC)
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: [Haskell-beginners] Haskell wants the type,    but I only know
        the class.
To: beginners@haskell.org
Message-ID: <loom.20111103t174034-...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

I'm trying to read something from a file, do something with it, and then write
it out again. I don't know, or care about, the type of the object I'm reading,
but I do know its class. Here's my code:

----------
import Data.Binary ( Binary, encode, decode )
import Data.ByteString.Lazy as B ( readFile, writeFile )
import Codec.Compression.GZip ( compress, decompress )

class ( Binary a, Show a, Eq a ) => Thing a where
  doSomething :: a -> IO a

readThing :: ( Thing a ) => FilePath -> IO a
readThing f =
    return . decode . decompress =<< B.readFile f

writeThing :: ( Thing a ) => FilePath -> a -> IO ()
writeThing f = B.writeFile f . compress . encode

main = do
  a <- readThing "file1.txt"
  a' <- doSomething a
  writeThing "file2.txt" a'
----------

And here's the compiler error I get. 

Amy.hs:18:3:
    Ambiguous type variable `a0' in the constraint:
      (Thing a0) arising from a use of `writeThing'
    Probable fix: add a type signature that fixes these type variable(s)
    In the expression: writeThing "file2.txt" a'
    In the expression:
      do { a <- readThing "file1.txt";
           a' <- doSomething a;
           writeThing "file2.txt" a' }
    In an equation for `main':
        main
          = do { a <- readThing "file1.txt";
                 a' <- doSomething a;
                 writeThing "file2.txt" a' }

Is there a way to fix my code? I tried adding a type signature, e.g.,

  a <- readThing "file1.txt" :: (Thing t) => IO t
  a' <- doSomething a :: (Thing t) => IO t

but then it says...

    Couldn't match type `t0' with `t'
      because type variable `t' would escape its scope
    This (rigid, skolem) type variable is bound by
      an expression type signature: Thing t => IO t
    The following variables have types that mention t0
      a :: t0 (bound at Amy.hs:16:3)
    In a stmt of a 'do' expression:
        a' <- doSomething a :: Thing t => IO t
    In the expression:
      do { a <- readThing "file1.txt" :: Thing t => IO t;
           a' <- doSomething a :: Thing t => IO t;
           writeThing "file2.txt" a' }
    In an equation for `main':
        main
          = do { a <- readThing "file1.txt" :: Thing t => IO t;
                 a' <- doSomething a :: Thing t => IO t;
                 writeThing "file2.txt" a' }




------------------------------

Message: 7
Date: Thu, 3 Nov 2011 19:27:57 +0200
From: Markus L?ll <markus.l...@gmail.com>
Subject: Re: [Haskell-beginners] Selecting single result of function
        application to list
To: Hugo Ferreira <h...@inescporto.pt>, beginners@haskell.org
Message-ID:
        <CALdaiuDbCitBxk7vecz+1Ci4i05jXisNxqain6=5kdnrtvq...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

There's also newtype First wraping a Maybe in Data.Monoid, in which
you can wrap your Maybes, mconcat them and get the first Just value.
Like:

> mconcat $ map First [Nothing, Just "first", Nohing, Just "last", Nothing]
First {getFirst = Just "first"}


On Thu, Nov 3, 2011 at 6:07 PM, Hugo Ferreira <h...@inescporto.pt> wrote:
> Hello,
>
> Apologies the simpleton question but I would like to
> know how it is done in Haskell. I have a list of values,
> and I am applying a function to each of these elements.
> The result is a Maybe. I would like to return the first
> occurrence which is not a Nothing.
>
> I am considering something like:
>
> selectOne f = take 1 . filter (\e -> case e of
> ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? Just _ -> True
> ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? _ -> False ) . map f
>
> I this how it is done?
>
> TIA,
> Hugo F.
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
Markus L?ll



------------------------------

Message: 8
Date: Thu, 3 Nov 2011 13:33:21 -0400
From: David McBride <toa...@gmail.com>
Subject: Re: [Haskell-beginners] Haskell wants the type,        but I only
        know the class.
To: Amy de Buitl?ir <a...@nualeargais.ie>
Cc: beginners@haskell.org
Message-ID:
        <can+tr43q4sk6a1ldfmixqzmtbau5+8dvrry7mhm8thzpwnt...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Thing a means a could be anything, but by the time your program
compiles, a must be something.  readThing "file1.txt" returns
something that is a Thing, but what?  Int?  String?  doSomething could
do wildly different things depending what a is, and so you have to
tell it what you want it to be, or it has to infer it by the way it is
being used.  Unfortunately, it can't tell what a was supposed to be by
the way you used it so it said it was ambiguous.  So, find what data
types are instances of Thing, choose whichever is most appropriate and
then:

 a <- readThing "file1.txt" :: IO Whichever
 a' <- doSomething a

where Whichever is your chosen instance of Thing.

On Thu, Nov 3, 2011 at 12:55 PM, Amy de Buitl?ir <a...@nualeargais.ie> wrote:
> I'm trying to read something from a file, do something with it, and then write
> it out again. I don't know, or care about, the type of the object I'm reading,
> but I do know its class. Here's my code:
>
> ----------
> import Data.Binary ( Binary, encode, decode )
> import Data.ByteString.Lazy as B ( readFile, writeFile )
> import Codec.Compression.GZip ( compress, decompress )
>
> class ( Binary a, Show a, Eq a ) => Thing a where
> ?doSomething :: a -> IO a
>
> readThing :: ( Thing a ) => FilePath -> IO a
> readThing f =
> ? ?return . decode . decompress =<< B.readFile f
>
> writeThing :: ( Thing a ) => FilePath -> a -> IO ()
> writeThing f = B.writeFile f . compress . encode
>
> main = do
> ?a <- readThing "file1.txt"
> ?a' <- doSomething a
> ?writeThing "file2.txt" a'
> ----------
>
> And here's the compiler error I get.
>
> Amy.hs:18:3:
> ? ?Ambiguous type variable `a0' in the constraint:
> ? ? ?(Thing a0) arising from a use of `writeThing'
> ? ?Probable fix: add a type signature that fixes these type variable(s)
> ? ?In the expression: writeThing "file2.txt" a'
> ? ?In the expression:
> ? ? ?do { a <- readThing "file1.txt";
> ? ? ? ? ? a' <- doSomething a;
> ? ? ? ? ? writeThing "file2.txt" a' }
> ? ?In an equation for `main':
> ? ? ? ?main
> ? ? ? ? ?= do { a <- readThing "file1.txt";
> ? ? ? ? ? ? ? ? a' <- doSomething a;
> ? ? ? ? ? ? ? ? writeThing "file2.txt" a' }
>
> Is there a way to fix my code? I tried adding a type signature, e.g.,
>
> ?a <- readThing "file1.txt" :: (Thing t) => IO t
> ?a' <- doSomething a :: (Thing t) => IO t
>
> but then it says...
>
> ? ?Couldn't match type `t0' with `t'
> ? ? ?because type variable `t' would escape its scope
> ? ?This (rigid, skolem) type variable is bound by
> ? ? ?an expression type signature: Thing t => IO t
> ? ?The following variables have types that mention t0
> ? ? ?a :: t0 (bound at Amy.hs:16:3)
> ? ?In a stmt of a 'do' expression:
> ? ? ? ?a' <- doSomething a :: Thing t => IO t
> ? ?In the expression:
> ? ? ?do { a <- readThing "file1.txt" :: Thing t => IO t;
> ? ? ? ? ? a' <- doSomething a :: Thing t => IO t;
> ? ? ? ? ? writeThing "file2.txt" a' }
> ? ?In an equation for `main':
> ? ? ? ?main
> ? ? ? ? ?= do { a <- readThing "file1.txt" :: Thing t => IO t;
> ? ? ? ? ? ? ? ? a' <- doSomething a :: Thing t => IO t;
> ? ? ? ? ? ? ? ? writeThing "file2.txt" a' }
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 41, Issue 3
****************************************

Reply via email to