Re: [Haskell-cafe] handling read exceptions

2004-04-13 Thread Sven Panne
S. Alexander Jacobson wrote:
My point is that I am reading in name/value pairs
and once I know the name, I know the type of the
value, but I don't want to have to pass that
information programatically to the point in the
code where I am doing the read.
OK, I see... I don't know the exact syntax you are using (e.g. how
are the strings terminated?), but reads is still useful:
   readIS :: ReadS (Either Integer String)
   readIS s = take 1 $
  [ (Left  x, t) | (x, t) - reads s ] ++
  [ (Right x, t) | (x, t) - lex   s ]
Then we have:

   Main readIS 123blah
   [(Left 123,blah)]
   Main readIS blah123
   [(Right blah123,)]
   Main readIS 
   [(Right ,)]
   Main readIS foo bar
   [(Right foo, bar)]
If you have only simple parsing tasks and are not looking for extreme
performance, the Read class is a good choice. Otherwise you should
probably have a look at the Parsec package which comes with Hugs and GHC:
   http://www.haskell.org/ghc/docs/latest/html/libraries/parsec/Text.ParserCombinators.Parsec.html

or Happy:

   http://haskell.org/happy/

Cheers,
   S.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Building Haddock on Windows

2004-04-13 Thread Simon Marlow
Yes, I suspect you have a mismatch between the version of Haddock on
your system and the version of Haddock used to produce the interfaces.
Try upgrading GHC.

Cheers,
Simon 

 -Original Message-
 From: Bayley, Alistair [mailto:[EMAIL PROTECTED] 
 Sent: 05 April 2004 16:19
 To: Simon Marlow
 Cc: [EMAIL PROTECTED]
 Subject: RE: [Haskell-cafe] Building Haddock on Windows
 
 Trying to invoke Haddock with
 --read-interface=c:\ghc\ghc-6.0\doc\html\base\base.haddock
 
 Initially I get a stack overflow, so I added: +RTS -K2M -RTS ...
 
 and now I get:
 Fail: end of file
 Action: Data.Binary.getWord8
 
 Is the --read-interface option specified correctly? This is 
 where my GHC
 installation is, and the base.haddock file exists in there. I 
 assume this is
 the interface file.
 
 Is this a compatibility problem? i.e. haddock file 
 distributed with GHC 6.0
 too old for Haddock 0.6?
 
 
  -Original Message-
  From: Simon Marlow [mailto:[EMAIL PROTECTED]
  Sent: 17 March 2004 15:29
  To: Bayley, Alistair
  Cc: [EMAIL PROTECTED]
  Subject: RE: [Haskell-cafe] Building Haddock on Windows
  
  
- why doesn't it know what Int, String, Float, IO, Monad, 
   Show, etc are?
   What invocation option do I need to ensure it links to
   Prelude/hierarchical-library stuff? (I think it's 
   --read-interface; must I
   generate interface files for the Prelude and libraries though?)
  
  You get the interfaces for the libraries with a GHC 
  installation.  Just
  use the --read-interface flag to tell Haddock about them.
  
  Cheers,
  Simon
 
 -
 *
 Confidentiality Note: The information contained in this 
 message, and any attachments, may contain confidential 
 and/or privileged material. It is intended solely for the 
 person(s) or entity to which it is addressed. Any review, 
 retransmission, dissemination, or taking of any action in 
 reliance upon this information by persons or entities other 
 than the intended recipient(s) is prohibited. If you received
 this in error, please contact the sender and delete the 
 material from any computer.
 *
 
 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] What's wrong with my Haskell code?

2004-04-13 Thread Meihui Fan
when loading the following code, hugs escaped and reported that

ERROR cal24.hs:10 - Instance of Integral (Ratio Integer) required for 
definition of Main.eval

I don't know why and how to solve it, anyone help me?

data ETree = Add ETree ETree
   | Sub ETree ETree
   | Mul ETree ETree
   | Div ETree ETree
   | Node Integer
   deriving Show
eval :: ETree-Maybe Rational
eval (Node x)= Just (fromInteger x)
eval (Add t1 t2) = do { x-eval t1; y-eval t2;
if x=y then return (x+y) else Nothing }
eval (Sub t1 t2) = do { x-eval t1; y-eval t2; return (x-y) }
eval (Mul t1 t2) = do { x-eval t1; y-eval t2;
if x=y then return (x*y) else Nothing }
eval (Div t1 t2) = do { x-eval t1; y-eval t2;
if y/=0 then return (x `div` y) else Nothing }
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's wrong with my Haskell code?

2004-04-13 Thread Arthur Baars
It is because you use 'div' instead of '/'.

div :: Integral a = a - a - a

(/) :: Fractional a = a - a - a

Rationals are instance of the class Fractional, but not of Integral
Prelude :i Fractional
class Num a = Fractional a where
  (/) :: a - a - a
  recip :: a - a
  fromRational :: Rational - a
  fromDouble :: Double - a
-- instances:
instance Fractional Float
instance Fractional Double
instance Integral a = Fractional (Ratio a)
Hope this helps,

Arthur

On 13-apr-04, at 20:44, Meihui Fan wrote:

when loading the following code, hugs escaped and reported that

ERROR cal24.hs:10 - Instance of Integral (Ratio Integer) required 
for definition of Main.eval

I don't know why and how to solve it, anyone help me?

data ETree = Add ETree ETree
   | Sub ETree ETree
   | Mul ETree ETree
   | Div ETree ETree
   | Node Integer
   deriving Show
eval :: ETree-Maybe Rational
eval (Node x)= Just (fromInteger x)
eval (Add t1 t2) = do { x-eval t1; y-eval t2;
if x=y then return (x+y) else Nothing }
eval (Sub t1 t2) = do { x-eval t1; y-eval t2; return (x-y) }
eval (Mul t1 t2) = do { x-eval t1; y-eval t2;
if x=y then return (x*y) else Nothing }
eval (Div t1 t2) = do { x-eval t1; y-eval t2;
if y/=0 then return (x `div` y) else Nothing }
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Building Haddock on Windows

2004-04-13 Thread Bayley, Alistair
 Try upgrading GHC.

Thanks, I'll try that.

Would it be too much to ask that Haddock be distributed with GHC?

Reasons for:
 - GHC library docs are produced with Haddock
 - GHC library docs already include Haddock interface files
 - would ensure version of Haddock matches that used to produce interface
files
 - would save lazy developers like myself from downloading and compiling.
Think of it as one less barrier to overcome; a small step closer to more
widespread adoption.

Reasons against:
 - would favour one documentation tool over others
 - would add an unnecessary item to GHC build/packaging procedure (is this
much of an overhead?)

Mind you, if you include Haddock, why stop there? Why not include other
developers tools, like (say) Hmake, Happy, Hat, ...?

Alistair.


 -Original Message-
 From: Simon Marlow [mailto:[EMAIL PROTECTED]
 Sent: 13 April 2004 10:59
 To: Bayley, Alistair
 Cc: [EMAIL PROTECTED]
 Subject: RE: [Haskell-cafe] Building Haddock on Windows
 
 
 Yes, I suspect you have a mismatch between the version of Haddock on
 your system and the version of Haddock used to produce the interfaces.
 Try upgrading GHC.
 
 Cheers,
   Simon 
 
  -Original Message-
  From: Bayley, Alistair [mailto:[EMAIL PROTECTED] 
  Sent: 05 April 2004 16:19
  To: Simon Marlow
  Cc: [EMAIL PROTECTED]
  Subject: RE: [Haskell-cafe] Building Haddock on Windows
  
  Trying to invoke Haddock with
  --read-interface=c:\ghc\ghc-6.0\doc\html\base\base.haddock
  
  Initially I get a stack overflow, so I added: +RTS -K2M -RTS ...
  
  and now I get:
  Fail: end of file
  Action: Data.Binary.getWord8
  
  Is the --read-interface option specified correctly? This is 
  where my GHC
  installation is, and the base.haddock file exists in there. I 
  assume this is
  the interface file.
  
  Is this a compatibility problem? i.e. haddock file 
  distributed with GHC 6.0
  too old for Haddock 0.6?

-
*
Confidentiality Note: The information contained in this 
message, and any attachments, may contain confidential 
and/or privileged material. It is intended solely for the 
person(s) or entity to which it is addressed. Any review, 
retransmission, dissemination, or taking of any action in 
reliance upon this information by persons or entities other 
than the intended recipient(s) is prohibited. If you received
this in error, please contact the sender and delete the 
material from any computer.
*

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] WildCard question

2004-04-13 Thread Paul Cosby

Hi,

I am very new to haskell and the program hugs and I am having problems using the wildcard operator _

Every time I try to use it in an definition it says something like the symbol /017 is not recognised. I am sure my defintions are correct as I tested it with an example defintion from Alan Thompsons craft of functional programming book.

I am guessing that all the relevant modules havenot been loaded properly. I have reinstalled hugs with full implementation and this has not helped.
I am using a windows 98 PC.

Any help suggestions? Or has anyone just got the wildcard definition which are could just paste into my scripts

Many thanks
		  
Yahoo! Messenger - Communicate instantly..."Ping" your friends 
today! Download Messenger Now___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] WildCard question

2004-04-13 Thread Ketil Malde
Paul Cosby [EMAIL PROTECTED] writes:

 Every time I try to use [underscore] in an definition it says
 something like the symbol /017 is not recognised

Could that be \017, i.e. octal 17 (defined in ASCII as SI, whatever
that may be)?

 Any help suggestions?

Wild guess: Are your files using the same character set as your
Haskell system is expecting?  I know Windows pulls some occasional
stunts with the character set (and occasionally lies about it), but I
wasn't aware that it affected underscore.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] C Bindings?

2004-04-13 Thread Russ Lewis
Does Haskell have some mechanism that allows it to link to C, or other 
imperative languages?

I know, you could use the IO Monad to do it...using stdin and stdout as 
pipes to any other program.  But is there a way to link Haskell into a C 
program?

Thanks again for the help for a newbie...
   Russ
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] C Bindings?

2004-04-13 Thread Gregory Wright
Hi,

The Foreign Function Interface (FFI) is your friend for these tasks:

http://www.cse.unsw.edu.au/~chak/haskell/ffi/

On the haskell.org web page, under libraries and tools there are 
links to
a number of tools to help you connect your C  haskell programs.
The GreenCard and c-haskell tools seem to be used by a number
of people.

Alastair Reid's Guide to Haskell's Foreign Function Interface,

http://www.reid-consulting-uk.ltd.uk/docs/ffi.html

is a good place to start. It has some comparison of the various tools.

Best Wishes,
Greg
On Apr 13, 2004, at 12:56 PM, Russ Lewis wrote:

Does Haskell have some mechanism that allows it to link to C, or other 
imperative languages?

I know, you could use the IO Monad to do it...using stdin and stdout 
as pipes to any other program.  But is there a way to link Haskell 
into a C program?

Thanks again for the help for a newbie...
   Russ
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] C Bindings?

2004-04-13 Thread Graham Klyne
It's not really newbie stuff, but maybe this is what you're looking for:

  http://www.cse.unsw.edu.au/~chak/haskell/ffi/

#g
--
At 09:56 13/04/04 -0700, Russ Lewis wrote:
Does Haskell have some mechanism that allows it to link to C, or other 
imperative languages?

I know, you could use the IO Monad to do it...using stdin and stdout as 
pipes to any other program.  But is there a way to link Haskell into a C 
program?

Thanks again for the help for a newbie...
   Russ
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] WildCard question

2004-04-13 Thread Jon Fairbairn
On 2004-04-13 at 18:52+0200 Ketil Malde wrote:
 Paul Cosby [EMAIL PROTECTED] writes:
 
  Every time I try to use [underscore] in an definition it says
  something like the symbol /017 is not recognised
 
 Could that be \017, i.e. octal 17 (defined in ASCII as SI, whatever
 that may be)?

SI is Shift In, if I remember correctly, not that the
operation of devices like Flexowriters is of any
relevance. However, I'd guess that it's hexadecimal 17,
because ord '_' `rem` 16 == 15 == 0x17. So for some reason
it's talking about the botom four bits of '_'!

  Any help suggestions?
 
 Wild guess: Are your files using the same character set as
 your Haskell system is expecting?  I know Windows pulls
 some occasional stunts with the character set (and
 occasionally lies about it), but I wasn't aware that it
 affected underscore.

Windows is a mystery to me, however. My guess would be
something translating from one page of a character table to
another. What locale are you in?

  Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe