showsPrec: cui bono?

2002-11-12 Thread Jerzy Karczmarczuk
A simple, primitive question:

has anybody here used in a non-trivial way the showsPrec anti-parser?
My students asked me what is it for, it is never used in the Hugs
Prelude, OK, once: possible parentheses around fractions n%d.

I explained that it is a good contraption to make one own pretty-
printers, like readsPrec can be useful for simple, precedence-based
parsers.

But I am still unhappy. The associativity is not taken into account,
and for non-trivial purposes both ...Prec functions seem not as useful
as I would like.

Any comments?  Thanks.

Jerzy Karczmarczuk

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



Re: showsPrec: cui bono?

2002-11-12 Thread C.Reinke

 has anybody here used in a non-trivial way the showsPrec anti-parser?

Isn't the idea to make things trivial while avoiding performance
penalties? Perhaps: simple pretty-printing of abstract syntax trees?

I often use it to get simple debugging output for complex internal
data structures (first, use deriving; then, define showsPrec; if
that's still not good enough, do some real thinking..).

Anyway, this reminded me of a litte old hack of mine.  Only trivial
use of showsPrec, but perhaps you'll like it anyway?-)

http://www.cs.ukc.ac.uk/people/staff/cr3/toolbox/haskell/R.hs

As with anything else in my toolbox, no warranty for nothing..

Cheers,
Claus

--- cut here

{-
  Representative thingies..

  A little hack to pair values with string representations
  of their expressions. Useful if you want to explain what

map (+1) [1..4] or foldr1 (*) [1..5]

  do, or if you want to demonstrate the difference between 

foldr (+) 0 [1..4] and foldl (+) 0 [1..4]

  Load this module into Hugs (Hugs mode) and type in some of 
  these examples to get an idea of what I mean. Also try

map (+) [1..4]
  
  This could be extended in various directions, but I wanted to 
  keep things simple. I'm not convinced that extra complications 
  would be worth the effort.

  Claus Reinke
-}

default (R Integer)

data R a = R {rep:: String
 ,val:: a
 }

instance Show (R a) where
  showsPrec _ a = showString (rep a)

instance Show (R a - R b) where
  showsPrec _ f = showString (\\x-++(rep (f x)))
where
  x = R{rep=x,val=error variable}

instance Show (R a - R b - R c) where
  showsPrec _ f = showString (\\x y-++(rep (f x y)))
where
  x = R{rep=x,val=error variable}
  y = R{rep=y,val=error variable}

lift1 op a = R {rep=(++(rep op)++ ++(rep a)++)
   ,val= (   (val op)   (val a)   )
   }

lift2 op a b  = R {rep=(++(rep op)++ ++(rep a)++ ++(rep b)++)
  ,val= (   (val op)   (val a)   (val b)   )
  }

lift2infix op a b  = R {rep=(++(rep a)++ ++(rep op)++ ++(rep b)++)
   ,val= (   (val a)  `iop`   (val b)   )
   }
   where
iop = val op

instance (Num a,Show a) = Num (R a) where
  (+)= lift2infix R{rep=+,val=(+)}
  (-)= lift2infix R{rep=-,val=(-)}
  (*)= lift2infix R{rep=*,val=(*)}
  negate = lift1 R{rep=-,val=negate}
  fromInteger a = (\fIa-R{rep=show fIa,val=fIa}) (fromInteger a)

instance (Eq a,Num a) = Eq (R a) where
  a == b = (val a) == (val b)

instance (Ord a,Num a) = Ord (R a) where
  a = b = (val a) = (val b)

instance (Enum a,Num a,Show a) = Enum (R a) where
  fromEnum   = fromEnum.val
  toEnum   a = R{rep=show a,val=toEnum a}
  enumFrom x = map toEnum [fromEnum x..] -- missing in Hugs Prelude..

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



Calling Haskell from Python / C++

2002-11-12 Thread Jonathan Holt
Hi,

I've just recently learned about Haskell, and I'm
impressed by the abstractions and expressiveness that
it affords. I'm particularly interested in it for a
small parser project that I'm planning.

However, my main programming languages are Python and
C++, and for various reasons switching entirely to
Haskell is completely out of the question (no
flame-bait intended!).

So here is what I envision: I write the main
application in Python. I write a (hopefully) small
Haskell module that:
a) Calls back to the main Python app for reading the
text to be parsed, preferably using laziness.
b) Parses the text, and maybe processes a bit.
c) Returns the parsed data-structure. (This may be
tricky, but I think I know how to do it).

This all seems quite cool. And it can also be very
useful in a wide veriety of other circumstances, i.e.
whenever a complex computation can be outsourced
from Python/C++ to Haskell.

But I can't find any way to interface Python and
Haskell in this way. The FFI seems to allow for this,
but there arn't any tools to actually do it... So my
question is: How would one do such a thing?

Thanks in advance,
 -JH


__
Do you Yahoo!?
U2 on LAUNCH - Exclusive greatest hits videos
http://launch.yahoo.com/u2
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Haskell98 Report copyright

2002-11-12 Thread Christopher Milton
I hope we don't have a repeat of the MathWorld website
shutdown.* I also can't find a webpage with the definition
of Standard ML... only avaible in print from MIT Press?

Chris

* http://mathworld.wolfram.com/erics_commentary.html

=
Christopher Milton
[EMAIL PROTECTED]

__
Do you Yahoo!?
U2 on LAUNCH - Exclusive greatest hits videos
http://launch.yahoo.com/u2
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



1 line simple cat in Haskell

2002-11-12 Thread Ahn Ki-yung
If you are steaming with compicated codes, then how about taking a break.
Let's play with a simple cat.

\begin{code}

main = mapM (=putChar) getCharS where getCharS = getChar:getCharS

\end{code}

Tested with ghc.
Works good except that you get some messages on stderror
because eof is not handled.

How would you suggest to neatly insert the error handling code into ?

P.S.
Instead of coding with C++,
I want to write my server main code like this.

server_main = mapM (=process.reply) where getReqS = getReq:getReqS

Only if I had enough time ... :-p
Using HDirect and so on ...

-- 
Ahn Ki-yung


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