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. Re:  QuickCheck with monadic IO (Daniel Seidel)
   2.  a simple little problem (Dennis Raddle)
   3. Re:  a simple little problem (Mihai Maruseac)
   4. Re:  a simple little problem (Ertugrul Soeylemez)
   5. Re:  a simple little problem (Ertugrul Soeylemez)
   6. Re:  a simple little problem (Mihai Maruseac)
   7. Re:  a simple little problem (Daniel Fischer)
   8. Re:  a simple little problem (Brandon Allbery)


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

Message: 1
Date: Sat, 13 Aug 2011 19:59:12 +0200
From: Daniel Seidel <d...@iai.uni-bonn.de>
Subject: Re: [Haskell-beginners] QuickCheck with monadic IO
To: Hartmut <hartmut0...@googlemail.com>
Cc: beginners@haskell.org
Message-ID: <1313258352.16090.22.ca...@entwood.iai.uni-bonn.de>
Content-Type: text/plain

Hi Hartmut,

if I just copy,paste and compile your example it takes less than 0.01s
to run the tests. So, probably the problem is not in the code.
BTW, I use GHC 7.0.1.

Cheers,

Daniel.

On Fri, 2011-08-12 at 23:31 +0200, Hartmut wrote:
> Everyone,
> 
> I want to run an QuickCheck on "a most simple" IO monad.
> When I compile and run :main, it says:
> ....................................................................................................+++
>  OK, passed 100 tests.
> Well, thats fine, since *1 mapped on any Int gives the same Int back.
> But it lasts 10 seconds (!) for doing those 100 Tests.
> Something must be wrong?!
> I'd appreciate your ideas.
> 
> Hartmut
> 
> 
> module MonadicQuickCheck where
> 
> import IO
> import Random
> import Test.QuickCheck
> import Test.QuickCheck.Monadic
> 
> main = do
>   quickCheck x
>   
> x :: Property
> x = monadicIO $ do 
>   a <- pick arbitrary
>   pre $ not(null a)
>   b <- run $ testfunction a
>   assert $ b == a
> 
> testfunction :: [Int] -> IO [Int]
> testfunction x = do
>   putStr "."
>   return $ map (*1) x
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners




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

Message: 2
Date: Sat, 13 Aug 2011 11:04:57 -0700
From: Dennis Raddle <dennis.rad...@gmail.com>
Subject: [Haskell-beginners] a simple little problem
To: Haskell Beginners <beginners@haskell.org>
Message-ID:
        <CAKxLvoqV+0X4pftq89RP6-V=fzfqdr20ra+ddyc6gwa6y94...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Can someone suggest an elegant way to write the following?

fn :: [Maybe Float] -> Maybe Float

in which, if the input list has all Nothing, then the result is Nothing
if the input list has one or more Just x, then the result is Just x
(in which the x is picked arbitrarily, could be the first one or last
one)

I have something like

import Data.Maybe
fn list = case catMaybes list of
  [] -> Nothing
  [x:_] -> fromJust x

Next, an augmentation of this idea (or similar idea).

fn2 :: [Maybe Float] -> Map Int Float

When a Just x appears at position n in the list, then put (key=n,
value=x) into the map.

I have:

import qualified Data.Map as M
f2 list = M.fromList [(n,x) | (n,Just x) <- zip [0..] list]



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

Message: 3
Date: Sat, 13 Aug 2011 21:11:11 +0300
From: Mihai Maruseac <mihai.marus...@gmail.com>
Subject: Re: [Haskell-beginners] a simple little problem
To: Dennis Raddle <dennis.rad...@gmail.com>
Cc: Haskell Beginners <beginners@haskell.org>
Message-ID:
        <caomsum+3iswdmc2dan7peynje+t_acjjmrm8pb7eapnx+h+...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Sat, Aug 13, 2011 at 9:04 PM, Dennis Raddle <dennis.rad...@gmail.com> wrote:
> Can someone suggest an elegant way to write the following?
>
> fn :: [Maybe Float] -> Maybe Float
>
> in which, if the input list has all Nothing, then the result is Nothing
> if the input list has one or more Just x, then the result is Just x
> (in which the x is picked arbitrarily, could be the first one or last
> one)

I'd go by:

fn l = let l' = filter (/= Nothing) l in if l' == [] then Nothing else head l'

-- 
Mihai



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

Message: 4
Date: Sat, 13 Aug 2011 20:11:54 +0200
From: Ertugrul Soeylemez <e...@ertes.de>
Subject: Re: [Haskell-beginners] a simple little problem
To: beginners@haskell.org
Message-ID: <20110813201154.15f2d...@angst.streitmacht.eu>
Content-Type: text/plain; charset=US-ASCII

Dennis Raddle <dennis.rad...@gmail.com> wrote:

> Can someone suggest an elegant way to write the following?
>
> fn :: [Maybe Float] -> Maybe Float
>
> in which, if the input list has all Nothing, then the result is
> Nothing if the input list has one or more Just x, then the result is
> Just x (in which the x is picked arbitrarily, could be the first one
> or last one)

Either of:

    fnFirst :: [Maybe a] -> Maybe a
    fnFirst = getFirst . mconcat . map First

    fnLast :: [Maybe a] -> Maybe a
    fnLast = getLast . mconcat . map Last


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/





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

Message: 5
Date: Sat, 13 Aug 2011 20:23:16 +0200
From: Ertugrul Soeylemez <e...@ertes.de>
Subject: Re: [Haskell-beginners] a simple little problem
To: beginners@haskell.org
Message-ID: <20110813202316.30805...@angst.streitmacht.eu>
Content-Type: text/plain; charset=US-ASCII

Mihai Maruseac <mihai.marus...@gmail.com> wrote:

> I'd go by:
>
> fn l = let l' = filter (/= Nothing) l in if l' == [] then Nothing else head l'

If you want to disregard the useful Monoid instance of Maybe, then here
is a nicer way to express this:

    fn :: [Maybe a] -> Maybe a
    fn = listToMaybe . catMaybes


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/





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

Message: 6
Date: Sat, 13 Aug 2011 21:41:39 +0300
From: Mihai Maruseac <mihai.marus...@gmail.com>
Subject: Re: [Haskell-beginners] a simple little problem
To: Ertugrul Soeylemez <e...@ertes.de>
Cc: beginners@haskell.org
Message-ID:
        <caomsumkfa5stqxeoj_cgmrj5a-7kx_47edr+3xfkj13z9jd...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Sat, Aug 13, 2011 at 9:23 PM, Ertugrul Soeylemez <e...@ertes.de> wrote:
> Mihai Maruseac <mihai.marus...@gmail.com> wrote:
>
>> I'd go by:
>>
>> fn l = let l' = filter (/= Nothing) l in if l' == [] then Nothing else head 
>> l'
>
> If you want to disregard the useful Monoid instance of Maybe, then here
> is a nicer way to express this:
>
> ? ?fn :: [Maybe a] -> Maybe a
> ? ?fn = listToMaybe . catMaybes
>

I stand corrected. I only wanted a simple solution but the Monoid
instance is more expressive :)



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

Message: 7
Date: Sat, 13 Aug 2011 20:45:57 +0200
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] a simple little problem
To: beginners@haskell.org
Message-ID: <201108132045.57934.daniel.is.fisc...@googlemail.com>
Content-Type: Text/Plain;  charset="iso-8859-1"

On Saturday 13 August 2011, 20:04:57, Dennis Raddle wrote:
> Can someone suggest an elegant way to write the following?
> 
> fn :: [Maybe Float] -> Maybe Float
> 
> in which, if the input list has all Nothing, then the result is Nothing
> if the input list has one or more Just x, then the result is Just x
> (in which the x is picked arbitrarily, could be the first one or last
> one)

import Control.Monad

fn = msum

(or, with only imports from Data.Maybe: listToMaybe . catMaybes)

> 
> I have something like
> 
> import Data.Maybe
> fn list = case catMaybes list of
>   [] -> Nothing
>   [x:_] -> fromJust x
> 
> Next, an augmentation of this idea (or similar idea).
> 
> fn2 :: [Maybe Float] -> Map Int Float
> 
> When a Just x appears at position n in the list, then put (key=n,
> value=x) into the map.
> 
> I have:
> 
> import qualified Data.Map as M
> f2 list = M.fromList [(n,x) | (n,Just x) <- zip [0..] list]
> 

That's fine.




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

Message: 8
Date: Sat, 13 Aug 2011 14:47:04 -0400
From: Brandon Allbery <allber...@gmail.com>
Subject: Re: [Haskell-beginners] a simple little problem
To: Dennis Raddle <dennis.rad...@gmail.com>
Cc: Haskell Beginners <beginners@haskell.org>
Message-ID:
        <cakfcl4whguqt_fwjjyzetouq+uy__g6max9brqfwdhl4-me...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Sat, Aug 13, 2011 at 14:04, Dennis Raddle <dennis.rad...@gmail.com>wrote:

> Can someone suggest an elegant way to write the following?
>
> fn :: [Maybe Float] -> Maybe Float
>
> in which, if the input list has all Nothing, then the result is Nothing
> if the input list has one or more Just x, then the result is Just x
> (in which the x is picked arbitrarily, could be the first one or last
> one)
>

Isn't this just mconcat?

-- 
brandon s allbery                                      allber...@gmail.com
wandering unix systems administrator (available)     (412) 475-9364 vm/sms
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110813/51456ae6/attachment-0001.htm>

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

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


End of Beginners Digest, Vol 38, Issue 29
*****************************************

Reply via email to