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:  Random animals (aditya siram)
   2.  Heterogeneous Lists (John Smith)
   3. Re:  Heterogeneous Lists (Michael Snoyman)
   4.  Re: Random animals (Amy de Buitl?ir)
   5.  Re: Random animals (Amy de Buitl?ir)
   6.  Cost center annotations - where/let difference (Daniel Seidel)
   7. Re:  Cost center annotations - where/let difference
      (Daniel Fischer)
   8. Re:  Cost center annotations - where/let difference
      (Daniel Seidel)
   9.  arrow type signature question (MH)
  10. Re:  arrow type signature question (Daniel Fischer)


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

Message: 1
Date: Wed, 17 Nov 2010 12:15:53 -0600
From: aditya siram <aditya.si...@gmail.com>
Subject: Re: [Haskell-beginners] Random animals
To: Amy de Buitl?ir <a...@nualeargais.ie>
Cc: beginners@haskell.org
Message-ID:
        <aanlktin+flo-kjpy6bfu_-fpruwi5uj8dtg7gkcc_...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Does this help?
http://www.haskell.org/haskellwiki/99_questions/Solutions/24
-deech

On Tue, Nov 16, 2010 at 6:13 PM, Amy de Buitléir <a...@nualeargais.ie> wrote:
> I have this function:
>
> -- | Choose an element at random from a list and return the element and its 
> index
> -- Ex: runState (randomListSelection ['a', 'b', 'c', 'd', 'e']) (mkStdGen 1)
> randomListSelection :: (RandomGen s) => [a] -> State s (Int, a)
> randomListSelection xs = do
>  i <- State $ randomR (0,length xs - 1)
>  return (i, xs !! i)
>
> I want to repeatedly select random elements from a list. I know the code 
> below is
> totally wrong, but it's the closest I've gotten so far. When I run it in 
> ghci, I
> get the SAME random element each time, until I reload the module. I guess 
> that's
> because g is always the same. I'm still struggling with monads, and would
> appreciate any advice on how to fix this.
>
> chooseCreatur = do
>  g <- getStdGen
>  return (evalState (randomListSelection ["cat", "dog", "lion", "mouse"]) g)
>
> FWIW, I'll be calling it from a loop within the IO monad. The real list will 
> be
> growing and shrinking in size.
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


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

Message: 2
Date: Wed, 17 Nov 2010 21:35:32 +0200
From: John Smith <volderm...@hotmail.com>
Subject: [Haskell-beginners] Heterogeneous Lists
To: beginners@haskell.org
Message-ID: <ic1aq6$k6...@dough.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

My program needs a list such as [IO 3, IO "f", IO 'z'] :: Show s => [IO s]. Is 
there any way to achieve this without 
wrapping all the values in existentially quantified types?



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

Message: 3
Date: Wed, 17 Nov 2010 21:39:46 +0200
From: Michael Snoyman <mich...@snoyman.com>
Subject: Re: [Haskell-beginners] Heterogeneous Lists
To: John Smith <volderm...@hotmail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlkti=dwlga0u3bwifmw3xqavcwufrb9foo9yfs4...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Wed, Nov 17, 2010 at 9:35 PM, John Smith <volderm...@hotmail.com> wrote:
> My program needs a list such as [IO 3, IO "f", IO 'z'] :: Show s => [IO s].
> Is there any way to achieve this without wrapping all the values in
> existentially quantified types?

Short answer: no. Slightly longer answer: you could just apply "show"
to each element in the list and get a list of Strings.

Michael


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

Message: 4
Date: Wed, 17 Nov 2010 21:48:41 +0000 (UTC)
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: [Haskell-beginners] Re: Random animals
To: beginners@haskell.org
Message-ID: <loom.20101117t224646-...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

aditya siram <aditya.siram <at> gmail.com> writes:

> 
> Does this help?
> http://www.haskell.org/haskellwiki/99_questions/Solutions/24
> -deech

Indeed it does, thank you deech. For the benefit of anyone who googles this, 
here's a solution that works.

import "mtl" Control.Monad.State
import System.Random

-- | Choose an element at random from a list and return the element and its 
index
randomListSelection :: [a] -> IO (Int, a)
randomListSelection xs = do
  i <- randomRIO (0,(length xs)-1)
  return (i, xs !! i)

chooseCreatur :: IO (Int, [Char])
chooseCreatur = randomListSelection ["cat", "dog", "lion", "mouse"]



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

Message: 5
Date: Wed, 17 Nov 2010 22:34:21 +0000 (UTC)
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: [Haskell-beginners] Re: Random animals
To: beginners@haskell.org
Message-ID: <loom.20101117t232620-...@post.gmane.org>
Content-Type: text/plain; charset=utf-8

Amy de Buitléir <amy <at> nualeargais.ie> writes:

I realised that that approach leads to a small problem for me. I have written a
couple of modules with dozens of functions that work with randomness, and 
they're
all in the State monad. I don't want to rewrite them all to be in the IO monad
instead, because I think that design approach would be less clean. But I did 
some
more searching, and discovered that if I use newStdGen instead of getStdGen, my
original design works just fine. So for posterity, here's another working 
solution.


import "mtl" Control.Monad.State
import System.Random

-- | Choose an element at random from a list and return the element and its 
index
-- Ex: runState (randomListSelection ['a', 'b', 'c', 'd', 'e']) (mkStdGen 1)
randomListSelection :: (RandomGen s) => [a] -> State s (Int, a)
randomListSelection xs = do
  i <- State $ randomR (0,length xs - 1)
  return (i, xs !! i)

chooseCreatur = do
  g <- newStdGen
  return (evalState (randomListSelection ["cat", "dog", "lion", "mouse"]) g)




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

Message: 6
Date: Thu, 18 Nov 2010 11:24:24 +0100
From: Daniel Seidel <d...@iai.uni-bonn.de>
Subject: [Haskell-beginners] Cost center annotations - where/let
        difference
To: beginners@haskell.org
Message-ID: <1290075863.30078.41.ca...@entwood.iai.uni-bonn.de>
Content-Type: text/plain

Hi,

I was doing some heap profiles and ran into the following issue.

Consider the program fib.hs:

module Main where

fib i | i == 0 || i == 1 = 1
      | i > 1            = fib (i-1) + fib (i-2)
      | otherwise        = 0

testWhere = {-# SCC "Where" #-} res
  where res = fib 35

testLet = {-# SCC "Let" #-}
          let res = fib 35
          in res

If I choose 

main = print testLet

compile with: ghc --make -prof -auto-all -caf-all -O2 fib.hs
and run:      ./fib +RTS -hc -hCLet -L60

the fib.hp file will contain entries as expected.

If I choose

main = print testWhere

compile with: ghc --make -prof -auto-all -caf-all -O2 fib.hs
and run:      ./fib +RTS -hc -hCWhere -L60

the fib.hp file will contain the timestamps, but entries for measured
heap consumption.

Can anyone please tell me, if this is the expected behavior? I'm not
very experienced in benchmarking and was a bit irritated by that
difference.

Cheers, Daniel.




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

Message: 7
Date: Thu, 18 Nov 2010 14:29:55 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Cost center annotations - where/let
        difference
To: beginners@haskell.org
Message-ID: <201011181429.55512.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Thursday 18 November 2010 11:24:24, Daniel Seidel wrote:
> Hi,
>
> I was doing some heap profiles and ran into the following issue.
>
> Consider the program fib.hs:
>
> module Main where
>
> fib i | i == 0 || i == 1 = 1
>
>       | i > 1            = fib (i-1) + fib (i-2)
>       | otherwise        = 0
>
> testWhere = {-# SCC "Where" #-} res
>   where res = fib 35
>
> testLet = {-# SCC "Let" #-}
>           let res = fib 35
>           in res
>

>
> Can anyone please tell me, if this is the expected behavior?

I think so.
testWhere is equivalent to

testLet2 = let res = fib35 in {-# SCC "Where" #-} res

so the cost centre covers only the result, not the computation.
To get the computation into the cost centre, use

testWhere = res
  where
    res = {-# SCC "Where" #-} fib 35

which corresponds to

let res = {-# SCC "Whatever" #-} fib 35 in res

> I'm not
> very experienced in benchmarking and was a bit irritated by that
> difference.
>
> Cheers, Daniel.

Ditto ;)


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

Message: 8
Date: Thu, 18 Nov 2010 15:02:43 +0100
From: Daniel Seidel <d...@iai.uni-bonn.de>
Subject: Re: [Haskell-beginners] Cost center annotations - where/let
        difference
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID: <1290088963.30078.108.ca...@entwood.iai.uni-bonn.de>
Content-Type: text/plain

Thanks for the explanation :).

Cheers, Daniel.

On Thu, 2010-11-18 at 14:29 +0100, Daniel Fischer wrote:
> On Thursday 18 November 2010 11:24:24, Daniel Seidel wrote:
> > Hi,
> >
> > I was doing some heap profiles and ran into the following issue.
> >
> > Consider the program fib.hs:
> >
> > module Main where
> >
> > fib i | i == 0 || i == 1 = 1
> >
> >       | i > 1            = fib (i-1) + fib (i-2)
> >       | otherwise        = 0
> >
> > testWhere = {-# SCC "Where" #-} res
> >   where res = fib 35
> >
> > testLet = {-# SCC "Let" #-}
> >           let res = fib 35
> >           in res
> >
> 
> >
> > Can anyone please tell me, if this is the expected behavior?
> 
> I think so.
> testWhere is equivalent to
> 
> testLet2 = let res = fib35 in {-# SCC "Where" #-} res
> 
> so the cost centre covers only the result, not the computation.
> To get the computation into the cost centre, use
> 
> testWhere = res
>   where
>     res = {-# SCC "Where" #-} fib 35
> 
> which corresponds to
> 
> let res = {-# SCC "Whatever" #-} fib 35 in res
> 
> > I'm not
> > very experienced in benchmarking and was a bit irritated by that
> > difference.
> >
> > Cheers, Daniel.
> 
> Ditto ;)



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

Message: 9
Date: Thu, 18 Nov 2010 10:07:34 -0500
From: MH <mha...@gmail.com>
Subject: [Haskell-beginners] arrow type signature question
To: beginners@haskell.org
Message-ID:
        <aanlkti=kw9qebv3nz=yq5acv+h=z-gxx9ch-kze9l...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I am looking at signatures for Arrow and Composable classes and I cannot
understand some of them. Could you please explain me the following:
Let's take for example the following:

class FunAble h => FunDble h where
  resultFun   :: (h b -> h b') -> (h (a->b) -> h (a->b'))

class FunAble h where
  secondFun :: (h b -> h b') -> (h (a,b) -> h (a,b')) -- for 'second'


in the signatures:
resultFun   :: (h b -> h b') -> (h (a->b) -> h (a->b'))
secondFun :: (h b -> h b') -> (h (a,b) -> h (a,b'))

if (h b -> h b') is the input of these functions where does 'a' comes from
in the output?

Thanks,
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20101118/09a58b2a/attachment-0001.html

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

Message: 10
Date: Thu, 18 Nov 2010 16:52:59 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] arrow type signature question
To: beginners@haskell.org
Cc: MH <mha...@gmail.com>
Message-ID: <201011181652.59889.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Thursday 18 November 2010 16:07:34, MH wrote:
> I am looking at signatures for Arrow and Composable classes and I cannot
> understand some of them. Could you please explain me the following:
> Let's take for example the following:
>
> class FunAble h => FunDble h where
>   resultFun   :: (h b -> h b') -> (h (a->b) -> h (a->b'))
>
> class FunAble h where
>   secondFun :: (h b -> h b') -> (h (a,b) -> h (a,b')) -- for 'second'
>
>
> in the signatures:
> resultFun   :: (h b -> h b') -> (h (a->b) -> h (a->b'))
> secondFun :: (h b -> h b') -> (h (a,b) -> h (a,b'))
>
> if (h b -> h b') is the input of these functions where does 'a' comes
> from in the output?

'a' is arbitrary, so it works for all 'a'. The result of resultFun foo, 
resp. secondFun foo is a function of type

h (a -> b) -> h (a -> b')

resp.

h (a,b) -> h (a,b')

where the types b and b' have been determined by foo (not necessarily 
completely, if foo is id, all that has been determined is that b' = b) and 
'a' is still arbitrary. The type variable 'a' is fixed or restricted when 
xxxFun gets its second argument, bar in

resultFun foo bar

resp.

secondFun foo bar.

>
> Thanks,

HTH,
Daniel



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

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


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

Reply via email to