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: parsing upto n items with parsec (Christian Maeder)
   2. Re:  is there a best os to easily install external        libraries
      ? (david hodgetts)
   3.  Re: map question (Will Ness)
   4. Re:  Re: map question (Deniz Dogan)
   5. Re:  Re: map question (Brent Yorgey)
   6. Re:  new locale? (Brent Yorgey)
   7.  Re: map question (Will Ness)
   8.  I/O (John Moore)
   9. Re:  I/O (Daniel Fischer)
  10. Re:  Re: map question (Daniel Fischer)


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

Message: 1
Date: Sat, 17 Oct 2009 11:15:40 +0200
From: Christian Maeder <christian.mae...@dfki.de>
Subject: [Haskell-beginners] Re: parsing upto n items with parsec
To: Ashish Agarwal <agarwal1...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4ad98b3c.7080...@dfki.de>
Content-Type: text/plain; charset=ISO-8859-1

Ashish Agarwal schrieb:
> Hi. I'm just learning Parsec and Haskell. It is a great library, and I
> see how "many" lets you parse 0 or more items, "many1" parses 1 or more
> items, and "count" parses exactly n items. However, there is no
> combinator that parses between m and n items. What would be the best
> implementation for this?

I would write an "upTo" parser with the same type as "count" that parses
not exactly but at most n items. Your desired parser is than the
concatenated results of "count m p" and "upTo (n - m) p" (achieved by
"liftM2 (++)").

For "upTo" a recursive definition seems best (other may come up with
tricky combinator application.) "upTo 0 p" (or something less than 0)
returns "[]" and "upTo n p" is an "option [] ..." parser of one "p"
result followed by the "upTo (n - 1) p" result:

"option [] (liftM2 (:) p (upTo (n - 1) p))"

HTH Christian

Another possibility is to use "many" and check if the resulting list has
the desired length (if not fail), but that may consume too many tokens
that subsequent parsers are supposed to consume.


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

Message: 2
Date: Sat, 17 Oct 2009 12:00:23 +0200
From: david hodgetts <david.demainlal...@gmail.com>
Subject: Re: [Haskell-beginners] is there a best os to easily install
        external        libraries ?
To: beginners@haskell.org
Message-ID:
        <42a5d61a0910170300nffb73co2ff69725c9f00...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Thank you very much for the long and very informative answer. I was going to
try Ubuntu, but since I have a spare machine, I think I will rather "plunge
deep" and try to get arch linux running.

Also, thanks for mentioning andLinux, I will certainly check it out.

best regards

david hodgetts
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091017/4bf4d21f/attachment-0001.html

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

Message: 3
Date: Sat, 17 Oct 2009 18:29:39 +0000 (UTC)
From: Will Ness <will_...@yahoo.com>
Subject: [Haskell-beginners] Re: map question
To: beginners@haskell.org
Message-ID: <loom.20091017t202435-...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

Brent Yorgey <byorgey <at> seas.upenn.edu> writes:

> 
> By the way, the reason
> 
>   map (+1) [1,2,3,4]
> 
> works but
> 
>   map (-1) [1,2,3,4]
> 
> doesn't is because of an ugly corner of Haskell syntax: -1 here is
> parsed as negative one, rather than an operator section with
> subtraction.  The 'subtract' function is provided exactly for this
> purpose, so that you can write
> 
>   map (subtract 1) [1,2,3,4]
> 

Then why wouldn't (`-`1) parse at at all? And not even (`(-)`1) ?

I know this doesn't parse, my question is, why wouldn't it be made valid 
syntax? It seems consistent. (`mod`2) parses, why not (`-`2) ?






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

Message: 4
Date: Sat, 17 Oct 2009 20:41:30 +0200
From: Deniz Dogan <deniz.a.m.do...@gmail.com>
Subject: Re: [Haskell-beginners] Re: map question
To: Will Ness <will_...@yahoo.com>
Cc: beginners@haskell.org
Message-ID:
        <7b501d5c0910171141y56be9da3wa70658d090097...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

2009/10/17 Will Ness <will_...@yahoo.com>:
> Brent Yorgey <byorgey <at> seas.upenn.edu> writes:
>
>>
>> By the way, the reason
>>
>>   map (+1) [1,2,3,4]
>>
>> works but
>>
>>   map (-1) [1,2,3,4]
>>
>> doesn't is because of an ugly corner of Haskell syntax: -1 here is
>> parsed as negative one, rather than an operator section with
>> subtraction.  The 'subtract' function is provided exactly for this
>> purpose, so that you can write
>>
>>   map (subtract 1) [1,2,3,4]
>>
>
> Then why wouldn't (`-`1) parse at at all? And not even (`(-)`1) ?
>
> I know this doesn't parse, my question is, why wouldn't it be made valid
> syntax? It seems consistent. (`mod`2) parses, why not (`-`2) ?
>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>

`This` syntax is used to make functions work infix, whereas operators
already are infix. For this reason, it wouldn't make much sense to use
`this` syntax (what's that called anyways?) on an operator.

`(-)` would in some sense be the same thing as just "-", since () is
used to make operators prefix and `` is used to make functions infix.

-- 
Deniz Dogan


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

Message: 5
Date: Sat, 17 Oct 2009 14:43:36 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Re: map question
To: beginners@haskell.org
Message-ID: <20091017184336.ga18...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Sat, Oct 17, 2009 at 06:29:39PM +0000, Will Ness wrote:
> Brent Yorgey <byorgey <at> seas.upenn.edu> writes:
> 
> > 
> > By the way, the reason
> > 
> >   map (+1) [1,2,3,4]
> > 
> > works but
> > 
> >   map (-1) [1,2,3,4]
> > 
> > doesn't is because of an ugly corner of Haskell syntax: -1 here is
> > parsed as negative one, rather than an operator section with
> > subtraction.  The 'subtract' function is provided exactly for this
> > purpose, so that you can write
> > 
> >   map (subtract 1) [1,2,3,4]
> > 
> 
> Then why wouldn't (`-`1) parse at at all? And not even (`(-)`1) ?
> 
> I know this doesn't parse, my question is, why wouldn't it be made valid 
> syntax? It seems consistent. (`mod`2) parses, why not (`-`2) ?

`backticks` are only for making (prefix) functions into (infix)
operators.  - is already an infix operator, so putting it in backticks
would be redundant.  As for `(-)`, arbitrary expressions cannot go
inside backticks, and for good reason: what would `(2 `mod`)` parse
as?  

However, certainly different choices might have been possible.

-Brent


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

Message: 6
Date: Sat, 17 Oct 2009 14:45:22 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] new locale?
To: beginners@haskell.org
Message-ID: <20091017184522.ga19...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

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


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

Message: 7
Date: Sun, 18 Oct 2009 11:11:07 +0000 (UTC)
From: Will Ness <will_...@yahoo.com>
Subject: [Haskell-beginners] Re: map question
To: beginners@haskell.org
Message-ID: <loom.20091018t125911...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

Brent Yorgey <byorgey <at> seas.upenn.edu> writes:

> 
> On Sat, Oct 17, 2009 at 06:29:39PM +0000, Will Ness wrote:
> > 
> > Then why wouldn't (`-`1) parse at at all? And not even (`(-)`1) ?
> > 
> > I know this doesn't parse, my question is, why wouldn't it be made valid 
> > syntax? It seems consistent. (`mod`2) parses, why not (`-`2) ?
> 
> `backticks` are only for making (prefix) functions into (infix)
> operators.  - is already an infix operator, so putting it in backticks
> would be redundant.  As for `(-)`, arbitrary expressions cannot go
> inside backticks, and for good reason: what would `(2 `mod`)` parse
> as?  
> 
> However, certainly different choices might have been possible.
> 
> -Brent
> 


backticks could've been made no-op for operators. What's so wrong with (`:`[])? 
It'd just be the same as (:[]).

Except for `-`, where it would finally provide us with possibility to write a 
shortcut for the ugly (flip (-) 1) as (`-`1).

(2`mod`) is a unary operation :: (Integral a) => a -> a. Putting it inside 
backticks would require it be a binary infix op, causing a type mis-match.

For (-) it could choose the binary version over the unary. 

Or it could stay illegal for the parenthesised expressions, and just made legal 
syntax for operators, as (`:`[]). 

I don't know how easy or even possible it is to implement; I'm just saying it 
makes sense, for me.




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

Message: 8
Date: Sun, 18 Oct 2009 14:42:35 +0100
From: John Moore <john.moor...@gmail.com>
Subject: [Haskell-beginners] I/O
To: beginners@haskell.org
Message-ID:
        <4f7ad1ad0910180642u687317edu64d3eb86a377e...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi,
Could someone please tell me how to check this program. The problem is where
do I find the output? I laod this into ghc and it comes up OK modules
loaded: Main
gchi>

How do I now check if it works or see the result.

Program below (taken from real world haskell)
-- file: ch07/toupper-imp.hs
import System.IO
import Data.Char(toUpper)

main :: IO ()
main = do
       inh <- openFile "quux.txt" ReadMode
       outh <- openFile "output.txt" WriteMode
       mainloop inh outh
       hClose inh
       hClose outh
mainloop :: Handle -> Handle -> IO ()
mainloop inh outh =
    do ineof <- hIsEOF inh
       if ineof
           then return ()
           else do inpStr <- hGetLine inh
                   hPutStrLn outh (map toUpper inpStr)
                   mainloop inh outh
John
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091018/470b6ecc/attachment-0001.html

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

Message: 9
Date: Sun, 18 Oct 2009 15:56:32 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] I/O
To: beginners@haskell.org
Message-ID: <200910181556.33520.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-15"

Am Sonntag 18 Oktober 2009 15:42:35 schrieb John Moore:
> Hi,
> Could someone please tell me how to check this program. The problem is
> where do I find the output? I laod this into ghc and it comes up OK modules
> loaded: Main
> gchi>
>
> How do I now check if it works or see the result.
>
> Program below (taken from real world haskell)
> -- file: ch07/toupper-imp.hs
> import System.IO
> import Data.Char(toUpper)
>
> main :: IO ()
> main = do
>        inh <- openFile "quux.txt" ReadMode
>        outh <- openFile "output.txt" WriteMode
>        mainloop inh outh
>        hClose inh
>        hClose outh
> mainloop :: Handle -> Handle -> IO ()
> mainloop inh outh =
>     do ineof <- hIsEOF inh
>        if ineof
>            then return ()
>            else do inpStr <- hGetLine inh
>                    hPutStrLn outh (map toUpper inpStr)
>                    mainloop inh outh
> John

Make sure you have a file quux.txt in your directory, but no valuable file 
output.txt.
Load the module, type ":main" or just "main" at the ghci prompt and compare the 
then 
present file output.txt (if it isn't present, that's bad) to quux.txt (open 
both in an 
editor). It should be the uppercase version of that.

Or compile it (ghc --make toupper-imp.hs) and run the binary.


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

Message: 10
Date: Sun, 18 Oct 2009 16:12:56 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Re: map question
To: beginners@haskell.org
Cc: Will Ness <will_...@yahoo.com>
Message-ID: <200910181612.57167.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Sonntag 18 Oktober 2009 13:11:07 schrieb Will Ness:
> Brent Yorgey <byorgey <at> seas.upenn.edu> writes:
> > On Sat, Oct 17, 2009 at 06:29:39PM +0000, Will Ness wrote:
> > > Then why wouldn't (`-`1) parse at at all? And not even (`(-)`1) ?
> > >
> > > I know this doesn't parse, my question is, why wouldn't it be made
> > > valid syntax? It seems consistent. (`mod`2) parses, why not (`-`2) ?
> >
> > `backticks` are only for making (prefix) functions into (infix)
> > operators.  - is already an infix operator, so putting it in backticks
> > would be redundant.  As for `(-)`, arbitrary expressions cannot go
> > inside backticks, and for good reason: what would `(2 `mod`)` parse
> > as?
> >
> > However, certainly different choices might have been possible.
> >
> > -Brent
>
> backticks could've been made no-op for operators. What's so wrong with
> (`:`[])? It'd just be the same as (:[]).

Makes writing the parser more complicated.
Makes reading code more irritating.

>
> Except for `-`, where it would finally provide us with possibility to write
> a shortcut for the ugly (flip (-) 1) as (`-`1).

That's ugly too.
My favourite is subtract 1.

>
> (2`mod`) is a unary operation :: (Integral a) => a -> a. Putting it inside
> backticks would require it be a binary infix op, causing a type mis-match.

instance (Integral a) => Integral (b -> a) where ...

Evil, yes, but then f `(2 `mod`)` x would type-check.

But anyway, there are operators where a backticked section would type-check:

f `(g `.`)` x

That's not good.

>
> For (-) it could choose the binary version over the unary.
>
> Or it could stay illegal for the parenthesised expressions, and just made
> legal syntax for operators, as (`:`[]).
>
> I don't know how easy or even possible it is to implement; I'm just saying
> it makes sense, for me.

But it has downsides.




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

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


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

Reply via email to