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:  Utter Newbie - simple problems, output -     GHC     vs GHCi
      (Nigel Rantor)
   2. Re:  Utter Newbie - simple problems,      output - GHC vs GHCi
      (Daniel Fischer)
   3. Re:  Re: Type Class Woes .. (Chadda? Fouch?)
   4.  Re: pretty-printing data (Christian Maeder)
   5. Re:  Utter Newbie - simple problems, output -     GHC vs GHCi
      (Nigel Rantor)
   6.  Parsec newbie question (Patrick LeBoutillier)
   7. Re:  Parsec newbie question (Daniel Fischer)
   8. Re:  Re: Type Class Woes .. (Tom Poliquin)


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

Message: 1
Date: Sun, 30 Aug 2009 23:32:14 +0100
From: Nigel Rantor <wig...@wiggly.org>
Subject: Re: [Haskell-beginners] Utter Newbie - simple problems,
        output -        GHC     vs GHCi
To: Magnus Therning <mag...@therning.org>
Cc: beginners@haskell.org
Message-ID: <4a9afdee.30...@wiggly.org>
Content-Type: text/plain; charset=UTF-8

Magnus Therning wrote:
> On Sun, Aug 30, 2009 at 11:09 PM, Nigel Rantor<wig...@wiggly.org> wrote:
>>
>> length( filter( Char.isLower "LoweR" ) )
> 
> try this instead
> 
> length (filter Char.isLower "LoweR")
> 
> `filter` takes two arguments.

Thank you, I have been flip-flopping between having no parentheses and
lots...I think I get it now.

I owe you a beer.

This will, however, probably not be my last post...

   n


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

Message: 2
Date: Mon, 31 Aug 2009 00:48:03 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Utter Newbie - simple problems,
        output - GHC vs GHCi
To: beginners@haskell.org
Message-ID: <200908310048.03973.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Montag 31 August 2009 00:09:41 schrieb Nigel Rantor:
> I am trying to get my head around Haskell but seem to keep butting
> against problems that have nothing to do with FP yet, but are simply to
> do with not understanding the tools.
>
> I've been trying a lot of code from multiple tutorials but I keep
> finding that the code simply does not work out of the box, and requires
> some other setup I am unaware of.

It's often old code which may have become obsolete by changes in the compiler 
and 
libraries.

>
> I am currently on Debian, using GHC 6.8.2 installed using apt, so I
> assume that the toolchain is installed and working correctly.
>
> For example, the most recent tutorial I've been looking at is the "yet
> another haskell tutorial", here -
> http://www.cs.utah.edu/~hal/docs/daume02yaht.pdf
>
> One of the exercises after talking about functions that act on lists is
> to determine the number of lowercase letters in a string.
>
> Fine, that makes complete sense to me. I figure something along the
> lines of:
>
> length( filter( Char.isLower "LoweR" ) )
>
> should return the value 3
>
> If I attempt this at the interactive GHC prompt I get the following:
>
> ---------------------------------------------------------------------------
>--------------- wig...@mink:~/src/ht$ ghci
> GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
> Loading package base ... linking ... done.
> Prelude> show( length( filter( Char.isLower "LoweR" ) ) )
>
> <interactive>:1:35:
>     Couldn't match expected type `Char' against inferred type `[Char]'
>     In the first argument of `GHC.Unicode.isLower', namely `"LoweR"'
>     In the first argument of `filter', namely
>         `(GHC.Unicode.isLower "LoweR")'
>     In the first argument of `length', namely
>         `(filter (GHC.Unicode.isLower "LoweR"))'
> Prelude>
> ---------------------------------------------------------------------------
>---------------

Wrong parentheses. 'filter' takes two arguments, the predicate by which to 
filter and the 
list to be filtered. With your parentheses, you pass it only one argument, 
namely

(Data.Char.isLower "LoweR")

However, isLower takes a Char as argument, while here it is given a String, 
this is the 
type error reported by ghci.
What you wanted is

length (filter Data.Char.isLower "LoweR")

Function application doesn't need parentheses in Haskell, so a multi-argument 
function is 
called

function arg1 arg2 arg3

and not function(arg1, arg2, arg3)

as in most imperative languages. It takes a bit getting used to.

You don't need the 'show', by the way, ghci prints the result of the evaluation 
of an 
expression typed at the prompt anyway.
And, while the modules Char, List, IO etc. still exist, the compiler now uses 
hierarchical 
modules and they now live in Data.Char, Data.List, System.IO etc. Better to get 
the habit 
of using hierarchical modules from the start.

>
> If I attempt to put the code into a file and compile it I get the
> following:
>
> [Code]
> ---------------------------------------------------------------------------
>--------------- module Main where
> import Char
> main = show( length( filter( Char.isLower "LoweR" ) ) )
> ---------------------------------------------------------------------------
>---------------

Same parenthisation issue as above, on top of that, main must have type IO (), 
but 

show whatEver

is a String. It would be

import Data.Char

main = print (length (filter isLower "LoweR"))

>
> [Terminal]
> ---------------------------------------------------------------------------
>--------------- wig...@mink:~/src/ht$ ghc -o test ex3.hs
>
> ex3.hs:3:42:
>     Couldn't match expected type `Char' against inferred type `[Char]'
>     In the first argument of `isLower', namely `"LoweR"'
>     In the first argument of `filter', namely `(isLower "LoweR")'
>     In the first argument of `length', namely
>         `(filter (isLower "LoweR"))'
> wig...@mink:~/src/ht$
> ---------------------------------------------------------------------------
>---------------
>
> This is one of the smallest examples I can think of posting for some
> help, and quite frankly, I'm feeling a bit dim because I just cannot
> understand why this doesn't work...I've tried in vain to mess with the
> code (I won't attempt to describe it, I'm not au fait enough with
> Haskell terminology yet, it would sound like gibberish *and* be incorrect)
>
> Any help would be awesome, equally, any ready-to-run examples/tutorials
> that people could recommend would likewise be awesome and beer-worthy[0].
>

Try the wikibook:

http://en.wikibooks.org/wiki/Haskell

it contains (almost?) all of YAHT and much more. It's still being written, but 
it's 
already very usable.

Also, you might take a look at http://book.realworldhaskell.org/ .

> Cheers,
>
>   n
>
> [0] offer only applies to those in the London area or those environs
> where I find myself randomly

Dang. Could've done with a beer :(



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

Message: 3
Date: Mon, 31 Aug 2009 01:53:13 +0200
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] Re: Type Class Woes ..
To: Tom Poliquin <poliq...@softcomp.com>
Cc: beginners@haskell.org
Message-ID:
        <e9350eaf0908301653k1978f4cfp778d643137391...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Sun, Aug 30, 2009 at 9:14 PM, Tom Poliquin<poliq...@softcomp.com> wrote:
> Chaddaï Fouché  wrote:
>>
>> data Volumic = Volume a => V a
>>
> I've never used existentials .. but this seems like a powerful idea.
> Unfortunately I couldn't get this to compile ..
> It was unhappy about 'data Volumic' so I changed it to
> 'data Volumic a' .. it was still unhappy and took me down
> the road of compiler switch options .. until I had ..
> ghc -XFlexibleInstances -XExistentialQuantification -XEmptyDataDecls --make
> Main.hs
> which was also unsuccessful.
>

Oops... Sorry, I just put together a simple example and didn't test
it, I forgot the forall :

> data Volumic = forall a . (Volume a) => V a

You must explicitly quantify the type variable to do existentials (and
use the proper extensions, which you did).

>
> Philosophical Summary ...
> All the examples of type classes examples I've seen in tutorials and
> books look simple, beautiful and elegant. No disrespect intended
> to the coding suggestions but they seem a little more difficult than
> I had expected for my toy problem ..
>
> So I'm wondering why that is ..
>
> - I'm stupidly trying to shoehorn my toy problem
>  into a type class example which is not the best approach.
>

Well it is a _toy_ problem where you're specifically trying to
shoehorn something into the form you wished to discover, this kind of
thing sometimes seems harder to do than resolve real problems where
the context and the practical objectives give you clues all along.

>
> - The problem is *not* a toy problem and is really
>   complicated.
>

In fact you're trying to address the so called "Expression problem"
here, it isn't a simple feat and while Haskell bring some answer they
are not so straightforwardly supported and easy to use as could be
wished (though I'm unaware of any practical language that do better
currently IMHO).

>
> - Type classes are more appropriate at the 'system' level
>   than the 'application' level. Applications are better off
>   using algebraic data types.
>

Depend on what you call "Application" I guess, given that creating a
big application in Haskell seems to consist of creating a
framework/dsl to express the main program in two lines, it may be that
you'll still need type class for that, but it's true that type classes
are better placed in libraries than in the application code, where
algebraic/record type and pattern matching are often a more
appropriate solution.

>
> - Tom (me) has expectations that are too high.
>   I do have high expectations of Haskell. I've written
>   several mid sized applications (obviously without
>   using type classes :-) ) and found them easy to write
>   and unbelievably easy to refactor!!!
>

It may be that too, while Haskell is impressive, it isn't perfect just yet. ;)

-- 
Jedaï


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

Message: 4
Date: Mon, 31 Aug 2009 13:31:51 +0200
From: Christian Maeder <christian.mae...@dfki.de>
Subject: [Haskell-beginners] Re: pretty-printing data
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: beginners@haskell.org
Message-ID: <4a9bb4a7.1040...@dfki.de>
Content-Type: text/plain; charset=ISO-8859-1

Michael Mossey wrote:
> For debugging purposes I'm interested in pretty-printing data; to start
> with, lists of algebraic data types. Basically I'd like 'show' with the
> ability to put each entry of a list on a separate line, and indented.
> Note that the algebraic data might have an inner list as one of its
> elements, so this is a non-obvious formatting problem.
> 
> I believe I can make instances of Show, can I not? Is there something
> called showList which I can use to code my own method of showing lists
> of a particular type? My understanding is that I can't make [a] an
> instance of Show; hence they provided showList.

For your own data type say "Foo" you can provide your own showList
definition, that will be used whenever you show something of type
"[Foo]". You cannot rewrite the (generic) "instance Show a => Show [a]".

instance Show Foo where
  show _ = "Foo"
  showList l s = unlines (map (("  " ++) . show) l) ++ s

With overlapping instances you could rewrite "instance Show [Foo]", but
you should prefer the above or start with a separate class "Pretty" and
use show as default implementation:

 class Show a = Pretty a
  pretty :: a -> String
  pretty = show

With some ghc extension (undecidable instances?) you can get instances
for all types:

 instance Show a = Pretty a

Provide a list instance:

 instance Pretty a => Pretty [a] where
   pretty l = ...

and you can write (overlapping) instances for other types. For your own
data types use "deriving Show" and provide a Pretty instance (if you
don't like the Show result).

HTH Christian



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

Message: 5
Date: Mon, 31 Aug 2009 12:42:01 +0100
From: Nigel Rantor <wig...@wiggly.org>
Subject: Re: [Haskell-beginners] Utter Newbie - simple problems,
        output -        GHC vs GHCi
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID: <4a9bb709.7070...@wiggly.org>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Daniel Fischer wrote:
> Am Montag 31 August 2009 00:09:41 schrieb Nigel Rantor:
>> I am trying to get my head around Haskell but seem to keep butting
>> against problems that have nothing to do with FP yet, but are simply to
>> do with not understanding the tools.
[snip]
>> Any help would be awesome, equally, any ready-to-run examples/tutorials
>> that people could recommend would likewise be awesome and beer-worthy[0].
>>
> 
> Try the wikibook:
> 
> http://en.wikibooks.org/wiki/Haskell
> 
> it contains (almost?) all of YAHT and much more. It's still being written, 
> but it's 
> already very usable.
> 
> Also, you might take a look at http://book.realworldhaskell.org/ .

Thanks for this, the extra info around my problems is a big help, and 
makes me feel slightly less frustrated.

>> Cheers,
>>
>>   n
>>
>> [0] offer only applies to those in the London area or those environs
>> where I find myself randomly
> 
> Dang. Could've done with a beer :(

You never know, I may be in a town near you soon...and, also, I'm liable 
to be asking for more help. If anyone gets 12 points I'll ship a case...

   n


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

Message: 6
Date: Mon, 31 Aug 2009 13:33:48 -0400
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: [Haskell-beginners] Parsec newbie question
To: beginners <beginners@haskell.org>
Message-ID:
        <b217a64f0908311033j1983b51bn9eec6e48149fd...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi all,

I'd like to use parsec to parse IP addresses. So far I've written a (tiny)
parser for bytes:

byte :: GenParser Char st Word8
byte = do
         n <- many1 digit
         return (read n)

The function works fine, but it accepts numbers greater than 255.
How do I encapsulate this condition in the parser so that it fails (with en
appropriate error message) in this case?


Thanks a lot,

Patrick

-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090831/0508dd4d/attachment-0001.html

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

Message: 7
Date: Mon, 31 Aug 2009 21:26:28 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Parsec newbie question
To: beginners@haskell.org
Message-ID: <200908312126.29044.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-15"

Am Montag 31 August 2009 19:33:48 schrieb Patrick LeBoutillier:
> Hi all,
>
> I'd like to use parsec to parse IP addresses. So far I've written a (tiny)
> parser for bytes:
>
> byte :: GenParser Char st Word8
> byte = do
>          n <- many1 digit
>          return (read n)
>
> The function works fine, but it accepts numbers greater than 255.
> How do I encapsulate this condition in the parser so that it fails (with en
> appropriate error message) in this case?
>

byte :: GenParser Char st Word8
byte = do
    ds <- many1 digit
    let n :: Integer  -- or Int, if you're not too paranoid
        n = read ds
    if n < 256
      then return (fromIntegral n)
      else fail $ "Number " ++ ds ++ " too large for a byte."

>
> Thanks a lot,
>
> Patrick



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

Message: 8
Date: Mon, 31 Aug 2009 12:02:36 -0700
From: Tom Poliquin <poliq...@softcomp.com>
Subject: Re: [Haskell-beginners] Re: Type Class Woes ..
To: beginners@haskell.org
Message-ID: <200908311202.37033.poliq...@softcomp.com>
Content-Type: text/plain;  charset="utf-8"


Tom Poliquin wrote:
> I chose the (contrived toy) problem of computing the volume
> of various fruits.

Chaddaï Fouché  wrote:
> ....you can still have a list of different fruits
> type, using existential types, 

> [ Code supplied]

Chaddai .. I added the 'forall' and it works great!

Thanks very much for the code and the 'philosophical'
comments !

Full code of your solution below.

Tom

{-# OPTIONS_GHC -XFlexibleInstances #-}
{-# OPTIONS_GHC -XExistentialQuantification #-} 
{-# OPTIONS_GHC -XEmptyDataDecls #-}
 
module Main where

data Fruit a = F {radius, length :: Double }

data Orange; data Banana -- empty data decls

class Volume a where
   vol :: a -> Double

instance Volume (Fruit Orange) where
  vol (F r _) = (4/3) * pi * r * r * r

instance Volume (Fruit Banana) where -- flexible instances
  vol (F r l) = pi * (r * r) * l
 
data Volumic = forall a . (Volume a) => V a -- existential quantification

fruit_list :: [Volumic]
fruit_list = [ V (F 3 undefined :: Fruit Orange) 
              ,V (F 1 6 :: Fruit Banana) ]

main = do

   fruit <- return $ fruit_list

   mapM (\(V f) -> putStrLn ("Volume -> " ++
                               " = " ++ show (vol f))) fruit


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

> On Sun, Aug 30, 2009 at 9:14 PM, Tom Poliquin<poliq...@softcomp.com> wrote:
> > Chaddaï Fouché  wrote:
> >> data Volumic = Volume a => V a
> >
> > I've never used existentials .. but this seems like a powerful idea.
> > Unfortunately I couldn't get this to compile ..
> > It was unhappy about 'data Volumic' so I changed it to
> > 'data Volumic a' .. it was still unhappy and took me down
> > the road of compiler switch options .. until I had ..
> > ghc -XFlexibleInstances -XExistentialQuantification -XEmptyDataDecls
> > --make Main.hs
> > which was also unsuccessful.
>
> Oops... Sorry, I just put together a simple example and didn't test
>
> it, I forgot the forall :
> > data Volumic = forall a . (Volume a) => V a
>
> You must explicitly quantify the type variable to do existentials (and
> use the proper extensions, which you did).
>
> > Philosophical Summary ...
> > All the examples of type classes examples I've seen in tutorials and
> > books look simple, beautiful and elegant. No disrespect intended
> > to the coding suggestions but they seem a little more difficult than
> > I had expected for my toy problem ..
> >
> > So I'm wondering why that is ..
> >
> > - I'm stupidly trying to shoehorn my toy problem
> >  into a type class example which is not the best approach.
>
> Well it is a _toy_ problem where you're specifically trying to
> shoehorn something into the form you wished to discover, this kind of
> thing sometimes seems harder to do than resolve real problems where
> the context and the practical objectives give you clues all along.
>
> > - The problem is *not* a toy problem and is really
> >   complicated.
>
> In fact you're trying to address the so called "Expression problem"
> here, it isn't a simple feat and while Haskell bring some answer they
> are not so straightforwardly supported and easy to use as could be
> wished (though I'm unaware of any practical language that do better
> currently IMHO).
>
> > - Type classes are more appropriate at the 'system' level
> >   than the 'application' level. Applications are better off
> >   using algebraic data types.
>
> Depend on what you call "Application" I guess, given that creating a
> big application in Haskell seems to consist of creating a
> framework/dsl to express the main program in two lines, it may be that
> you'll still need type class for that, but it's true that type classes
> are better placed in libraries than in the application code, where
> algebraic/record type and pattern matching are often a more
> appropriate solution.
>
> > - Tom (me) has expectations that are too high.
> >   I do have high expectations of Haskell. I've written
> >   several mid sized applications (obviously without
> >   using type classes :-) ) and found them easy to write
> >   and unbelievably easy to refactor!!!
>
> It may be that too, while Haskell is impressive, it isn't perfect just yet.
> ;)


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

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


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

Reply via email to