Send Beginners mailing list submissions to
        [email protected]

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
        [email protected]

You can reach the person managing the list at
        [email protected]

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


Today's Topics:

   1. Re:  Choosing a function randomly... (Tom Murphy)
   2. Re:  Choosing a function randomly... (edgar klerks)
   3.  [x] and (x:_) for lists -- did you ever think that odd? (AntC)
   4. Re:  [x] and (x:_) for lists -- did you ever think that odd?
      (Brandon Allbery)
   5.  Missing some functions in Hoogle (Ken Kawamoto)
   6. Re:  [x] and (x:_) for lists -- did you ever      think that odd?
      (Ertugrul S?ylemez)
   7. Re:  [x] and (x:_) for lists -- did you ever think that odd?
      (Tom Murphy)


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

Message: 1
Date: Sun, 20 May 2012 15:45:01 -0400
From: Tom Murphy <[email protected]>
Subject: Re: [Haskell-beginners] Choosing a function randomly...
To: Ertugrul S?ylemez <[email protected]>
Cc: [email protected]
Message-ID:
        <cao9q0tuj++nml-n7dukw_gujb0n8ttcrfboqpaenj_6vlt5...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Why not just construct a list of the functions, and randomly select an
element from the list?

Tom
On May 20, 2012 5:14 AM, "Ertugrul S?ylemez" <[email protected]> wrote:

> Stuart Hungerford <[email protected]> wrote:
>
> > This is kind-of related to my earlier question on looking up functions
> > by name.  Suppose I have a module with a number of functions with the
> > same signature:
> >
> > [...]
> >
> > I'd like to choose and run one of these functions randomly at run
> > time. [...]
>
> Again the lookup approach seems most reasonable.  The cleanest way is to
> define a simple name type for your functions:
>
>    data FuncIx = FuncA | FuncB deriving (Ord)
>
>    instance Random FuncIx where
>        ...
>
>    funcA :: A -> B
>    funcB :: A -> B
>
>    funcs :: Map FuncIx (A -> B)
>    funcs = M.fromList (zip [FuncA, FuncB] [funcA, funcB])
>
> If you want to go for maximum speed instead:
>
>    import qualified Data.Vector as V
>
>    type FuncIx = Int
>
>    ...
>
>    funcs :: V.Vector (A -> B)
>    funcs = V.fromList [funcA, funcB]
>
>    randFunc :: (RandomGen g) => g -> (A -> B, g)
>    randFunc = first (funcs V.!) . randomR (0, 1)
>
>
> Greets,
> Ertugrul
>
> --
> nightmare = unsafePerformIO (getWrongWife >>= sex)
> http://ertes.de/
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120520/6e7faed9/attachment-0001.htm>

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

Message: 2
Date: Sun, 20 May 2012 22:23:42 +0200
From: edgar klerks <[email protected]>
Subject: Re: [Haskell-beginners] Choosing a function randomly...
To: Stuart Hungerford <[email protected]>
Cc: [email protected]
Message-ID:
        <cagauytm6q+02r8d3r5s2et2_3uzbmy7vzx81ixfqbnb4gzx...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I think the MonadRandom package has a elegant solution for your problem:

fromList :: 
MonadRandom<http://hackage.haskell.org/packages/archive/MonadRandom/0.1.6/doc/html/Control-Monad-Random-Class.html#t:MonadRandom>m
=> [(a,
Rational<http://hackage.haskell.org/packages/archive/base/4.4.1.0/doc/html/Prelude.html#t:Rational>)]
-> m a

Example:

fromList [(add, 1), (scale, 1), (rareFunction, 0.1)]

On Sun, May 20, 2012 at 8:42 AM, Stuart Hungerford <
[email protected]> wrote:

> Hi,
>
> This is kind-of related to my earlier question on looking up functions
> by name.  Suppose I have a module with a number of functions with the
> same signature:
>
> scale :: Int -> Int -> Int
>
> scale s x = s * x
>
> add :: Int -> Int -> Int
>
> add a x = a + x
>
> ...
>
> I'd like to choose and run one of these functions randomly at run
> time. I can see I could use some kind of case expression:
>
> op :: Int -> Int -> Int
>
> op p x = case random(1,2) of
>   1 -> scale p x
>   2 -> add p x
>
> Or some kind of pattern guards:
>
> op p x
>  | random(1,2) == 1 = scale p x
>  | otherwise  = add p x
>
> Although that method won't work as is for more than two choices.  Are
> these methods the most idiomatic way of randomly choosing a function?
>  How hard would it be to use the machinery of the QuickCheck library
> for this, given it must be doing something similar in test suites?
>
> Thanks,
>
> Stu
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120520/d23fe16e/attachment-0001.htm>

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

Message: 3
Date: Sun, 20 May 2012 21:14:15 +0000 (UTC)
From: AntC <[email protected]>
Subject: [Haskell-beginners] [x] and (x:_) for lists -- did you ever
        think that odd?
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii

Think back to when you first came across Haskell ...

This, for example (from page 4 of the Gentle Intro -- my comments added):

    length      :: [a] -> Integer         -- [ ] means list
    length      [] = 0                    -- [] means list
    length      (x: xs) = 1 + length xs   -- list, but no [ ]

Usually, showing a list uses square brackets and comma separators.

So list literals use square brackets and comma separators.

Type decls for a list uses square brackets.

List builders use square brackets and commas -- such as [1, 3 .. 9] or [0 ..]

Pattern matching for finite length lists use square brackets and commas:
     f   [] = ...
     f   [x] = ...
     f   [x, y] = ...

But pattern matching for unknown-length lists uses round brackets and colon -- 
such as that last binding for `length` above. And (nearly) every list-handling 
function has a pattern for unknown-length lists.

Would this pattern matching seem less odd?:

     head       [x ..] = x
     length     [x, xs@..] = 1 + length xs


Experienced Haskellers need not answer: you've got too used to ( : ) ;-)

AntC




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

Message: 4
Date: Sun, 20 May 2012 17:33:38 -0400
From: Brandon Allbery <[email protected]>
Subject: Re: [Haskell-beginners] [x] and (x:_) for lists -- did you
        ever think that odd?
To: AntC <[email protected]>
Cc: [email protected]
Message-ID:
        <cakfcl4x2coqcex5mmce-fba+e2mgkjfnvnqagwryssbpbac...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Sun, May 20, 2012 at 5:14 PM, AntC <[email protected]> wrote:

> Would this pattern matching seem less odd?:
>
>     head       [x ..] = x
>     length     [x, xs@..] = 1 + length xs
>
>
> Experienced Haskellers need not answer: you've got too used to ( : ) ;-)
>

You missed experienced Lispers, who are likewise entirely comfortable with
cons-like notation.

I would want to very carefully check the implications of your suggestion:
 it might not integrate well with the rest of pattern matching syntax, in
particular some uses of it might turn out to be impossible to distinguish
from existing constructs.  Some parts of Haskell's syntax are rather, how
shall I put it?  tightly reasoned, with less room for expansion than is
immediately obvious.

(Please note, I am not trying to say "don't bother", I am saying that the
syntax questions really are tricky and you need to work carefully.  This
syntax might end up being fine, or it might need to be worked somewhat
differently.)

-- 
brandon s allbery                                      [email protected]
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/20120520/246d2e57/attachment-0001.htm>

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

Message: 5
Date: Mon, 21 May 2012 08:55:51 +0900
From: Ken Kawamoto <[email protected]>
Subject: [Haskell-beginners] Missing some functions in Hoogle
To: [email protected]
Message-ID:
        <cagbyekmgyabqsum4bqjm63wh-uehjlb7vhg5ys3h6appuy+...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi,

I'm looking for a way to search Hoogle for Yesod related functions,
say, renderRoute in Yesod.Routes.Class.

First I confirmed the Hoogle site doesn't have it in index.
http://www.haskell.org/hoogle/?hoogle=renderRoute

Then, after installing hoogle via cabal, I built index over all
packages that I have by "hoogle data -l -v all".
Below is an excerpt of the output, looks like yesod-routes is imported
to database, or indexed, correctly.
However, local Hoogle still doesn't return any entry when I searched
for "renderRoute".

---- "hoogle data -l -v all" output
Starting yesod
Starting yesod-auth
Starting yesod-core
Starting yesod-routes
Skipped 1 warnings in yesod-routes
Parse error 11:48: Parse error: family
Converting yesod-routes... done
Finished yesod-routes
Skipped 4 warnings in yesod-core
Parse error 683:77: Parse error in expression: _
Parse error 710:48: Parse error: family
Parse error 803:1: Can't translate
Parse error 806:1: Can't translate
Converting yesod-core... done
Finished yesod-core


Now I'm wondering if I'm missing something, or Hoogle supports only a
predefined set of functions.
Any advise would be appreciated.

-- Ken



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

Message: 6
Date: Mon, 21 May 2012 01:58:23 +0200
From: Ertugrul S?ylemez <[email protected]>
Subject: Re: [Haskell-beginners] [x] and (x:_) for lists -- did you
        ever    think that odd?
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset="us-ascii"

AntC <[email protected]> wrote:

> Would this pattern matching seem less odd?:
>
>      head       [x ..] = x
>      length     [x, xs@..] = 1 + length xs

No, it seems and is more odd.  Why hide the list constructors behind
weird notation?  Why require syntactic peculiarities and special cases
for pattern-matching lists?  In particular, what does pattern-matching
against "enumFrom x" mean?  Oh, it means something different here?

Your proposed syntax is very arbitrary and helps to confuse everybody.
Haskell has very simple syntactic rules, and I'm sure I'm speaking for
most of the Haskell community when I say that we would like to keep it
that way.  We have access to the two list constructors (:) and []
directly and they are very convenient, so there is no need for weird
syntax just to enforce a set of ASCII characters in source code.


> Experienced Haskellers need not answer: you've got too used to ( :  )
> ;-)

Sorry, but this statement is very infantile.  Even if meant as a joke,
it's at best offensive and at worst insulting.  There is good reasoning
behind (:) and [], and just because you don't see it there is no reason
to imply that experienced Haskell programmers are stubborn.  Haskell
programmers are about as open-minded as programmers can get.

If you want people to take your proposals seriously, you shouldn't
offend the very persons who evaluate them.


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120521/f7bdf9a4/attachment-0001.pgp>

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

Message: 7
Date: Sun, 20 May 2012 21:03:07 -0400
From: Tom Murphy <[email protected]>
Subject: Re: [Haskell-beginners] [x] and (x:_) for lists -- did you
        ever think that odd?
To: Ertugrul S?ylemez <[email protected]>
Cc: [email protected]
Message-ID:
        <CAO9Q0tVphHr0yXLoku942BS=B2NXeYr0_s=spn46y8_j1vy...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

On May 20, 2012 7:59 PM, "Ertugrul S?ylemez" <[email protected]> wrote:
>
> AntC <[email protected]> wrote:
>
> > Would this pattern matching seem less odd?:
> >
> >      head       [x ..] = x
> >      length     [x, xs@..] = 1 + length xs
>
> No, it seems and is more odd.  Why hide the list constructors behind
> weird notation?  Why require syntactic peculiarities and special cases
> for pattern-matching lists?  In particular, what does pattern-matching
> against "enumFrom x" mean?  Oh, it means something different here?
>
> Your proposed syntax is very arbitrary and helps to confuse everybody.
> Haskell has very simple syntactic rules, and I'm sure I'm speaking for
> most of the Haskell community when I say that we would like to keep it
> that way.  We have access to the two list constructors (:) and []
> directly and they are very convenient, so there is no need for weird
> syntax just to enforce a set of ASCII characters in source code.
>
>
> > Experienced Haskellers need not answer: you've got too used to ( :  )
> > ;-)
>
> Sorry, but this statement is very infantile.  Even if meant as a joke,
> it's at best offensive and at worst insulting.  There is good reasoning
> behind (:) and [], and just because you don't see it there is no reason
> to imply that experienced Haskell programmers are stubborn.  Haskell
> programmers are about as open-minded as programmers can get.
>

I think it was just a joke.

> If you want people to take your proposals seriously, you shouldn't
> offend the very persons who evaluate them.
>
>
> Greets,
> Ertugrul
>
> --
> nightmare = unsafePerformIO (getWrongWife >>= sex)
> http://ertes.de/
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120520/ef63bfd4/attachment.htm>

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

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 47, Issue 14
*****************************************

Reply via email to