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:  \x -> x < 0.5 && x > -0.5 (Daniel Fischer)
   2. Re:  Haskell Output Help (Jan Jakubuv)
   3. Re:  Caching evaluation of lazy lists (Daniel Fischer)
   4. Re:  \x -> x < 0.5 && x > -0.5 (Darrin Thompson)
   5. Re: [Haskell-cafe] Re: [Haskell-beginners] using quickcheck
      for       blackbox testing for 3rd party apps. (Srikanth K)
   6.  random (John Moore)
   7. Re:  random (Brent Yorgey)
   8. Re:  random (Tom Davie)
   9. Re:  random (aditya siram)


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

Message: 1
Date: Fri, 23 Oct 2009 17:32:29 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] \x -> x < 0.5 && x > -0.5
To: beginners@haskell.org
Message-ID: <200910231732.29850.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Freitag 23 Oktober 2009 17:25:57 schrieb Darrin Thompson:
> On Fri, Oct 23, 2009 at 10:25 AM, pl <pl.lis...@gmail.com> wrote:
> >    filter ((<=0.5) . abs) xs
>
> pure (&&) <*> (< 0.5) <*> (> -0.5)
>
> liftM2 (&&) (< 0.5) (> -0.5)
>
> Someone suggested that this was an example of the reader monad but I
> don't get that.

It's because ((->) r) *is* the reader monad.
Control.Monad.Reader's Reader r a is just that wrapped in a newtype:

newtype Reader r a = Reader { runReader :: r -> a }

>
> > :i (->)
>
> data (->) a b   -- Defined in GHC.Prim
> instance Monad ((->) r) -- Defined in Control.Monad.Instances
> instance Functor ((->) r) -- Defined in Control.Monad.Instances
> instance Applicative ((->) a) -- Defined in Control.Applicative
>
> That's what I see working here.
>
> --
> Darrin



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

Message: 2
Date: Fri, 23 Oct 2009 16:42:48 +0100
From: Jan Jakubuv <jaku...@gmail.com>
Subject: Re: [Haskell-beginners] Haskell Output Help
To: Chandni Navani <chandni...@yahoo.com>
Cc: beginners@haskell.org
Message-ID: <20091023154248.ga8...@lxultra2.macs.hw.ac.uk>
Content-Type: text/plain; charset=iso-8859-1

Hi,

seems to me like a job for `Text.PrettyPrint`:

    import Text.PrettyPrint
    
    ppString :: String -> Doc
    ppString = doubleQuotes . text

    ppList :: [Doc] -> Doc
    ppList = brackets . vcat . punctuate (text ",")

    pretty = ppList . map (ppList . map ppString)

The code is hopefully almost self-explaining (`vcat` does the line
breaking). The result looks as follows:

    *Main> pretty [["abc", "cde"], ["fgh", "ghi"]]
    [["abc",
      "cde"],
     ["fgh",
      "ghi"]]

Sincerely,
    jan.

On Thu, Oct 22, 2009 at 12:11:07PM -0700, Chandni Navani wrote:
> I have a list of lists which all contain strings.  [[String]].  I need to 
> figure out how to print them so that after each individual string, there is a 
> new line.
> 
> If this is the initial list [["abc", "cde"] ["fgh", "ghi"]]
> [["abc"
>   "cde"]
>  ["fgh",
>   "ghi"]]
> 
> Can anyone help me figure this out? Thanks.


-- 
Heriot-Watt University is a Scottish charity
registered under charity number SC000278.



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

Message: 3
Date: Fri, 23 Oct 2009 19:34:44 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Caching evaluation of lazy lists
To: Philip Scott <psc...@foo.me.uk>
Cc: beginners@haskell.org
Message-ID: <200910231934.44610.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Freitag 23 Oktober 2009 18:30:53 schrieb Philip Scott:
> Hello again,
>
> > then, barring memory pressure forcing it out, it will be computed only
> > once (each list element will be computed only once, when it's first
> > needed).
>
> Thanks Daniel, that was what I was after. Is there any way of
> investigating these things without using the profiler? E.g. is there any
> way to stick a debug print statement inside a function without moving
> over to sideeffects and IO Monads etc.. I know printing is a side
> effect, but it would be nice to say 'I can has itsy sneeky side effect
> plz Haskell, just for little testing while'
>
> Cheers,
>
> Philip

import Debug.Trace

infixl 0 `debug`

debug = flip trace

dfib :: Int -> Integer
dfib =
    let fib 0 = 0
        fib 1 = 1
        fib n = dfib (n-2) + dfib (n-1) `debug` "eval fib " ++ show n
    in (map fib [0 .. ] !!)

Ok, modules loaded: MFib.
*MFib> dfib 4
eval fib 4
eval fib 2
eval fib 3
3
*MFib> dfib 7
eval fib 7
eval fib 5
eval fib 6
13
*MFib> dfib 15
eval fib 15
eval fib 13
eval fib 11
eval fib 9
eval fib 8
eval fib 10
eval fib 12
eval fib 14
610
*MFib>

The trick with debug = flip trace makes commenting out the debug-code easier:

fun x = trace ("fun " ++ show x) $ body x

~>

fun x = {- trace ("fun " ++ show x) $ -} body x

vs.

fun x = body x `debug` "fun " ++ show x

~>

fun x = body x -- `debug` "fun " ++ show x

But beware, including the argument in the trace message can lead to 
recalculation of 
values which would be cached without it, it's a hairy issue.


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

Message: 4
Date: Fri, 23 Oct 2009 16:24:38 -0400
From: Darrin Thompson <darri...@gmail.com>
Subject: Re: [Haskell-beginners] \x -> x < 0.5 && x > -0.5
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID:
        <a2e649c70910231324k19d05902i84736033891da...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Fri, Oct 23, 2009 at 11:32 AM, Daniel Fischer
<daniel.is.fisc...@web.de> wrote:
> It's because ((->) r) *is* the reader monad.
> Control.Monad.Reader's Reader r a is just that wrapped in a newtype:
>
> newtype Reader r a = Reader { runReader :: r -> a }
>

So I was thinking:

:t runReader $ liftM2 (&&) (Reader (< 0.5)) (Reader (> -0.5))

Thanks.

--
Darrin


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

Message: 5
Date: Sat, 24 Oct 2009 21:25:10 +0530
From: Srikanth K <k.srikanth.opensou...@gmail.com>
Subject: Re: [Haskell-cafe] Re: [Haskell-beginners] using quickcheck
        for     blackbox testing for 3rd party apps.
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org, haskell-c...@haskell.org
Message-ID:
        <a469481f0910240855m28517abag3ac261e618f10...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Thanks.  unsafePerformIO seems to suffice me for the moment...
However, I am ignorant about what would happen when multiple such
unsafePerformIO are done inside one function.

On Tue, Oct 13, 2009 at 11:04 PM, Daniel Fischer
<daniel.is.fisc...@web.de>wrote:

> Am Dienstag 13 Oktober 2009 18:04:52 schrieb Brent Yorgey:
> > Brent
> >
> > * Some smart-alecks might pipe up with something about unsafePerformIO
> >   here.  But that's not a cure, it's more like performing an emergency
> >   tracheotomy with a ballpoint pen.
>
> Quote of the month!
> _______________________________________________
> Haskell-Cafe mailing list
> haskell-c...@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091024/2031466d/attachment-0001.html

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

Message: 6
Date: Sat, 24 Oct 2009 17:59:35 +0100
From: John Moore <john.moor...@gmail.com>
Subject: [Haskell-beginners] random
To: beginners@haskell.org
Message-ID:
        <4f7ad1ad0910240959v67c47bd3h2162230c1770e...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi All,
           Can anyone help me I want to produce a list of three random
numbers for e.g. [7,8,1]
I tried using x <- getStdRandom $ randomR (1,10) but don't really understand
this and it only generates one number. Any help greatly appreciated.

Regards


John
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091024/6bd55d58/attachment-0001.html

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

Message: 7
Date: Sat, 24 Oct 2009 20:05:40 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] random
To: beginners@haskell.org
Message-ID: <20091025000539.ga27...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Sat, Oct 24, 2009 at 05:59:35PM +0100, John Moore wrote:
> Hi All,
>            Can anyone help me I want to produce a list of three random
> numbers for e.g. [7,8,1]
> I tried using x <- getStdRandom $ randomR (1,10) but don't really understand
> this and it only generates one number. Any help greatly appreciated.

replicateM is your friend:
  
  replicateM :: (Monad m) => Int -> m a -> m [a]

so if 'foo' produces a single random number, then 'replicateM 3 foo'
produces a list of three.

-Brent


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

Message: 8
Date: Sun, 25 Oct 2009 02:25:58 +0200
From: Tom Davie <tom.da...@gmail.com>
Subject: Re: [Haskell-beginners] random
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID:
        <8b70a98a0910241725x554717cfld3151a89b628b...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Or just randomRs :: (Random a, RandomGen g) => (a,a) -> g -> [a]

Bob

On Sun, Oct 25, 2009 at 2:05 AM, Brent Yorgey <byor...@seas.upenn.edu>wrote:

> On Sat, Oct 24, 2009 at 05:59:35PM +0100, John Moore wrote:
> > Hi All,
> >            Can anyone help me I want to produce a list of three random
> > numbers for e.g. [7,8,1]
> > I tried using x <- getStdRandom $ randomR (1,10) but don't really
> understand
> > this and it only generates one number. Any help greatly appreciated.
>
> replicateM is your friend:
>
>  replicateM :: (Monad m) => Int -> m a -> m [a]
>
> so if 'foo' produces a single random number, then 'replicateM 3 foo'
> produces a list of three.
>
> -Brent
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091024/105066e0/attachment-0001.html

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

Message: 9
Date: Sat, 24 Oct 2009 20:04:08 -0500
From: aditya siram <aditya.si...@gmail.com>
Subject: Re: [Haskell-beginners] random
Cc: beginners@haskell.org
Message-ID:
        <594f78210910241804u696d8506pebf53b69ebb05...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi John,
When I was first encountered replicateM I found it really hard to
understand. So,of course, I am audacious enough to assume that it is hard
for you too!

The code suggested by Brent ,  'replicateM 3 foo' is a nicer way of writing
the following:

foo = do
  x <- getStdRandom $ randomR (1,10)
  y <- getStdRandom $ randomR (1,10)
  z <- getStdRandom $ randomR (1,10)
  return [x,y,z]

Hope this helped.
-deech

On Sat, Oct 24, 2009 at 7:05 PM, Brent Yorgey <byor...@seas.upenn.edu>wrote:

> On Sat, Oct 24, 2009 at 05:59:35PM +0100, John Moore wrote:
> > Hi All,
> >            Can anyone help me I want to produce a list of three random
> > numbers for e.g. [7,8,1]
> > I tried using x <- getStdRandom $ randomR (1,10) but don't really
> understand
> > this and it only generates one number. Any help greatly appreciated.
>
> replicateM is your friend:
>
>  replicateM :: (Monad m) => Int -> m a -> m [a]
>
> so if 'foo' produces a single random number, then 'replicateM 3 foo'
> produces a list of three.
>
> -Brent
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091024/39a39e70/attachment.html

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

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


End of Beginners Digest, Vol 16, Issue 19
*****************************************

Reply via email to