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:  Re: \x -> x < 0.5 && x > -0.5 (Brent Yorgey)
   2. Re:  new locale? (Robert Wills)
   3. Re:  \x -> x < 0.5 && x > -0.5 (Carl Cravens)
   4. Re:  \x -> x < 0.5 && x > -0.5 (Michael Mossey)
   5. Re:  \x -> x < 0.5 && x > -0.5 (Isaac Dupree)
   6. Re:  \x -> x < 0.5 && x > -0.5 (Daniel Fischer)
   7.  Stack overflow, but hard to understand (Michael Mossey)
   8.  Is "step by step" the most natural style of      thought?
      (Michael Mossey)
   9. Re:  \x -> x < 0.5 && x > -0.5 (Bas van Dijk)


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

Message: 1
Date: Mon, 19 Oct 2009 16:18:32 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Re: \x -> x < 0.5 && x > -0.5
To: beginners@haskell.org
Message-ID: <20091019201832.ga5...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, Oct 19, 2009 at 12:09:02PM -0700, Michael Mossey wrote:
>
> Note also there's no need for runReader or evalReader (at least not that 
> I'm aware of) because unlike other monads, the reader monad is itself a 
> function that takes the state to be read.

Note that little-r 'reader' is just an informal name for the ((->) e)
monad, which is what your code was using.  Control.Monad.Reader also
provides the big-R 'Reader' type, which is just a newtype wrapper
around a little-r reader, and does indeed have a 'runReader' method
(which just removes the newtype constructor).  That is,

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

C.M.Reader also provides ReaderT, a monad transformer version of Reader.

-Brent


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

Message: 2
Date: Mon, 19 Oct 2009 23:17:05 +0100
From: Robert Wills <wrwi...@gmail.com>
Subject: Re: [Haskell-beginners] new locale?
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID: <4adce561.1050...@gmail.com>
Content-Type: text/plain; charset=UTF-8; format=flowed

Hi,

Sorry for not replying earlier.  I didn't see this until Friday and 
didn't get much time on my computer this weekend.

I asked this question because I was hoping to find 
System.Locale.defaultTimeLocale doesn't seem to be returning a time 
locale that matches what's on my system.  It returns  dateFmt = 
"%m/%d/%y" while my machine is set to  EN_GB and so presumably it should 
return %d/%m/%y. 

In Python on my machine I get:
 >>> import  locale
 >>> locale.getdefaultlocale()
('en_GB', 'UTF8')

So anyway, I was wondering whether there was a new locale library that 
fixed this problem.

-Rob

Brent Yorgey wrote:
> On Wed, Oct 14, 2009 at 05:44:34AM +0100, Robert Wills wrote:
>   
>> Hello,
>>
>> http://hackage.haskell.org/package/old-locale-1.0.0.1
>>
>> says "This package provides the old locale library. For new code, the new 
>> locale library is recommended."
>>
>> Does anyone know where I would find the new library?
>>     
>
> What locale functions are you trying to use?  As far as I can tell,
> there actually is no "new locale library" and functions for working
> with the locale have been spread across various other libraries as
> appropriate.
>
> -Brent
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>   



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

Message: 3
Date: Mon, 19 Oct 2009 21:19:41 -0500
From: Carl Cravens <ra...@phoenyx.net>
Subject: Re: [Haskell-beginners] \x -> x < 0.5 && x > -0.5
To: beginners@haskell.org
Message-ID: <4add1e3d.5090...@phoenyx.net>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Michael Mossey wrote:
> Is there a nifty way to write
> 
> filter (\x -> x < 0.5 && x > -0.5) xs
> 
> without explicitly using x?

I'm pretty new to Haskell... are you looking for a *better* way to write this, 
or is this an exercise in exploring alternatives for the sake of understanding?

I'm not seeing any of the proposed alternatives as being as clear as the lambda 
function, and I'd be surprised (in my ignorance) if any of them were more 
efficient.

-- 
Carl D Cravens (ra...@phoenyx.net)
Bad Command! Bad, Bad Command! Sit! Staaaaay...


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

Message: 4
Date: Mon, 19 Oct 2009 19:48:50 -0700
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: Re: [Haskell-beginners] \x -> x < 0.5 && x > -0.5
To: beginners@haskell.org
Message-ID: <4add2512.8090...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed



Carl Cravens wrote:
> Michael Mossey wrote:
>> Is there a nifty way to write
>>
>> filter (\x -> x < 0.5 && x > -0.5) xs
>>
>> without explicitly using x?
> 
> I'm pretty new to Haskell... are you looking for a *better* way to write 
> this, or is this an exercise in exploring alternatives for the sake of 
> understanding?
> 

Hi Carl,

Either one.

Let me chime in with some observations from a few months of studying 
Haskell. (Brent and Apfelmus can probably elaborate on this.)

Eliminating variables and working with function combinations has benefits. 
The one suggestion I've seen here that seems to be right on the money is

liftM2 (&&) (< 0.5) (> -0.5)

Although that might seem less clear to a beginner, it is actually _more_ 
clear than the lambda function in some ways. It's easier to work with proof 
at a more abstract level like this, and strange as it may seem, what I seem 
to observe in expert users of Haskell is that their brains will pick up 
what this is doing faster than the lambda function.

Or maybe this example is too small to be meaningful, but this kind of 
abstraction is the direction I want to move in, for there are benefits 
waiting for me when I arrive.

The Parsec library is an example of how concise and elegant code can get 
when you choose your abstractions carefully.



-Mike



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

Message: 5
Date: Mon, 19 Oct 2009 23:06:43 -0400
From: Isaac Dupree <m...@isaac.cedarswampstudios.org>
Subject: Re: [Haskell-beginners] \x -> x < 0.5 && x > -0.5
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: beginners@haskell.org
Message-ID: <4add2943.1080...@isaac.cedarswampstudios.org>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Michael Mossey wrote:
> Eliminating variables and working with function combinations has 
> benefits. The one suggestion I've seen here that seems to be right on 
> the money is
> 
> liftM2 (&&) (< 0.5) (> -0.5)

yep, I might not write it myself, but it's definitely the only one 
straightforward enough to perhaps justify itself.

now for a completely different suggestion; you write

> filter (\x -> x < 0.5 && x > -0.5) xs

but as a reader I would find it clearer to switch the order to numerical:
filter (\x -> x > -0.5 && x < 0.5) xs

(in this particular instance, we can observe numerical properties and 
even change to (\x -> abs x < 0.5) if we so desire.  Which can be 
written point-free as ((< 0.5) . abs), if you want to.)

-Isaac


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

Message: 6
Date: Tue, 20 Oct 2009 05:28:45 +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: <200910200528.45372.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Dienstag 20 Oktober 2009 04:48:50 schrieb Michael Mossey:
> Carl Cravens wrote:
> > Michael Mossey wrote:
> >> Is there a nifty way to write
> >>
> >> filter (\x -> x < 0.5 && x > -0.5) xs
> >>
> >> without explicitly using x?
> >
> > I'm pretty new to Haskell... are you looking for a *better* way to write
> > this, or is this an exercise in exploring alternatives for the sake of
> > understanding?
>
> Hi Carl,
>
> Either one.
>
> Let me chime in with some observations from a few months of studying
> Haskell. (Brent and Apfelmus can probably elaborate on this.)
>
> Eliminating variables and working with function combinations has benefits.

But it's not unconditionally a good thing. If you exaggerate it, it's pure 
obfuscation.
Nevertheless, playing around with eliminating variables and using combinators 
even beyond the border of obfuscation is a good exercise.
You gain understanding and a feeling of when it's better to stop by that.

> The one suggestion I've seen here that seems to be right on the money is
>
> liftM2 (&&) (< 0.5) (> -0.5)

May I offer

(&&) <$> (< 0.5) <*> (> -0.5)

? It works on Applicative Functors (doesn't need the full force of Monads).

>
> Although that might seem less clear to a beginner, it is actually _more_
> clear than the lambda function in some ways. It's easier to work with proof
> at a more abstract level like this, and strange as it may seem, what I seem
> to observe in expert users of Haskell is that their brains will pick up
> what this is doing faster than the lambda function.

In this small example, both are immediately clear, you need more complicated 
lambda 
expressions to get a measurable difference :)




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

Message: 7
Date: Mon, 19 Oct 2009 21:33:37 -0700
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: [Haskell-beginners] Stack overflow, but hard to understand
To: beginners@haskell.org
Message-ID: <4add3da1.2080...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Okay, beginner encountering first major bug.

I'm getting a stack overflow on a program that uses a lot of laziness to 
construct and modify lists---but the overflow happens even if I take just 
one element from the final list! The overflow seems to have started when I 
added the functions 'gauss' and 'gaussList' below, but I am at a loss to 
know why---these functions work perfectly in test cases and can even 
generate a long list.

The following program is distilled (with a lot of work!) down to the 
essence of what triggers the problem.

import Control.Monad
import Control.Monad.Random
import Data.List

-- Here I put a moderate-sized list of filenames which just generic
-- text or code. The longer the list,
-- the more likely to overflow stack. Which is curious, because if IO were
-- lazy here, it shouldn't be reading more than the first character of the
-- first file. Methinks a hint to the problem.
fileList =  ...

data TextGroup = Single Char Float
                deriving (Show)

textGroup_addDelay :: TextGroup -> Float -> TextGroup
textGroup_addDelay (Single c del) del2 = Single c (del+del2)

mkTextGroup :: Char -> Rand StdGen TextGroup
mkTextGroup c = liftM (Single c) gauss

-- Here's the kinda weird thing I'm doing with Rand. I want to
-- use fromList as the first computation to randomly choose
-- a second Rand computation. It turns out if you replace
-- this funkiness with
--   gauss = getRandomR (0,1)
-- the whole thing works.

gaussList :: Rand StdGen (Rand StdGen Float)
gaussList =
     fromList  [ (getRandomR( -1.0       ,-0.8 ),  2)
               , (getRandomR( -0.8       ,-0.6 ),  2)
               , (getRandomR( -0.6       ,-0.4 ),  4)
               , (getRandomR( -0.4       ,-0.2 ),  8)
               , (getRandomR( -0.2       , 0.0 ), 12)
               , (getRandomR(  0.0       , 0.2 ), 12)
               , (getRandomR(  0.2       , 0.4 ),  8)
               , (getRandomR(  0.4       , 0.6 ),  4)
               , (getRandomR(  0.6       , 0.8 ),  2)
               , (getRandomR(  0.8       , 1.0 ),  2)
               ]

gauss :: Rand StdGen Float
gauss = do
   m <- gaussList
   m

main = do
   gen0 <- newStdGen
   bufs <- mapM readFile fileList
   let buf = concat bufs
   let tgs = evalRand (do orig <- mapM mkTextGroup buf
                          addBreaks orig) gen0
   writeFile "output.ank" (show $ take 1 tgs)



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

Message: 8
Date: Tue, 20 Oct 2009 01:52:31 -0700
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: [Haskell-beginners] Is "step by step" the most natural style
        of      thought?
To: beginners <beginners@haskell.org>
Message-ID: <4add7a4f.6000...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed



Daniel Fischer wrote:
> Am Dienstag 20 Oktober 2009 04:48:50 schrieb Michael Mossey:
>>
>> Eliminating variables and working with function combinations has benefits.
> 
> But it's not unconditionally a good thing. If you exaggerate it, it's pure 
> obfuscation.
> Nevertheless, playing around with eliminating variables and using combinators 
> even beyond the border of obfuscation is a good exercise.
> You gain understanding and a feeling of when it's better to stop by that.
> 

I think I understand.

Another way to put my point is that learning Haskell has trained my eye to 
notice when a particular variable is flopping around in six different 
places. I programmed for twenty years or more in imperative languages (in a 
business setting, not academia) and no one ever said, "Hey we've got too 
many repetitions of x! Let's see what the underlying abstraction REALLY is."


>> The one suggestion I've seen here that seems to be right on the money is
>>
>> liftM2 (&&) (< 0.5) (> -0.5)
> 
> May I offer
> 
> (&&) <$> (< 0.5) <*> (> -0.5)
> 
> ? It works on Applicative Functors (doesn't need the full force of Monads).
> 
>> Although that might seem less clear to a beginner, it is actually _more_
>> clear than the lambda function in some ways. It's easier to work with proof
>> at a more abstract level like this, and strange as it may seem, what I seem
>> to observe in expert users of Haskell is that their brains will pick up
>> what this is doing faster than the lambda function.
> 
> In this small example, both are immediately clear, you need more complicated 
> lambda 
> expressions to get a measurable difference :)

Yeah, pretty small example, but based on what I've read in "Real World 
Haskell" and "Craft of Functional Programming," the authors find a lot of 
"strange-looking" (to the imperative programmer's eye) function combinators 
to be the most natural way of expressing the solution, and from time to 
time I find my thoughts aligning with them, and I realize how much less 
thought it takes.

This raises the question: is "step by step" thinking the "most natural" way 
to think about a mathematical problem? My hunch is "no." There are multiple 
modes of thought, and no reason to eliminate cognitive models that involve 
imagery, imaginary things moving and sliding through space... or analogies 
to the more common physical world... or the list is endless. I like the way 
Haskell resonates with a larger set of thinking styles.

Mike


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

Message: 9
Date: Tue, 20 Oct 2009 12:01:58 +0200
From: Bas van Dijk <v.dijk....@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:
        <f73f66150910200301j6da5e0ddhd716f3c49bb0...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Tue, Oct 20, 2009 at 5:28 AM, Daniel Fischer
<daniel.is.fisc...@web.de> wrote:
> May I offer
>
> (&&) <$> (< 0.5) <*> (> -0.5)

or:

import Control.Applicative.Infix

between l h = (> l) <^ (&&) ^> (< h)

Bas

You can find Control.Applicative.Infix in InfixApplicative:
http://hackage.haskell.org/package/InfixApplicative


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

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


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

Reply via email to