[Haskell-cafe] Re: Existential types (Was: Type vs TypeClass duality)

2007-10-26 Thread apfelmus

Wouter Swierstra wrote:
In a sense, that's also the reason why stream fusion à la Duncan + 
Roman + Don uses an existential type


  data Stream a where
Stream :: ∀s. s - (s - Step a s) - Stream a

  data Step a s = Done
| Yield a s
| Skip s


I thought there was a deeper reason for this, but I might be wrong.
[..]

data CoFix f = In (f (CoFix f))

Then the unfold producing a value of type CoFix f has type:

forall a . (a - f a) - a - CoFix f

(exists a . (a - f a, a)) - CoFix f

Using the co-Church encoding of colists yields the above Stream data 
type, where f corresponds to the Step data type. (The Skip 
constructor is a bit of a fix to cope with filter and friends).


Yes. I mean, I want to say that the efficiency gain of fusion is based 
on the fact that the state (the seed  a ) can be represented more 
compactly than the resulting  CoFix f . I.e. while


   ∃a. (a - f a, a)  =~=  CoFix f

the former type may be a more compact representation than the latter, 
demonstrating that an existential type may have performance benefits 
compared to an isomorphic alternative. (This is even without sharing 
here, Ryan remark was about sharing issues)


Regards,
apfelmus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell to math

2007-10-26 Thread jerzy . karczmarczuk
Henning Thielemann writes: 


Peter Verswyvelen wrote:



Now what I would like to do, is to create a mathematical expression in
Haskell (using e.g. an expression tree), which can be evaluated in
Haskell, and be converted to something pretty-math-printable (MathML,
PS, PDF, LaTex, whatever).


There is the LaTeX preprocessor lhs2TeX which can typeset Haskell
expressions in LaTeX's math mode. However I find the conversion not very
well designed (e.g. the handling of parentheses).


There was a program TeX Haskell mode by Manuel Chakravarty, also
lambdaTeX, etc., but if I understand well, this IS NOT what Peter V.
wants. He wants a specific pretty-printer *in Haskell*. This was most
probably a subject of many students' exercices... 

Jerzy Karczmarczuk 


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell to math

2007-10-26 Thread Henning Thielemann

On Fri, 26 Oct 2007, Peter Verswyvelen wrote:

 Some packages like Open Office and Microsoft Word contain a math
 expression writer. The same can be done with Maple, etc. Standard
 formats such as MathML, LaTex etc exist.

 Now what I would like to do, is to create a mathematical expression in
 Haskell (using e.g. an expression tree), which can be evaluated in
 Haskell, and be converted to something pretty-math-printable (MathML,
 PS, PDF, LaTex, whatever).

There is the LaTeX preprocessor lhs2TeX which can typeset Haskell
expressions in LaTeX's math mode. However I find the conversion not very
well designed (e.g. the handling of parentheses).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell to math

2007-10-26 Thread Peter Verswyvelen
Some packages like Open Office and Microsoft Word contain a math 
expression writer. The same can be done with Maple, etc. Standard 
formats such as MathML, LaTex etc exist.


Now what I would like to do, is to create a mathematical expression in 
Haskell (using e.g. an expression tree), which can be evaluated in 
Haskell, and be converted to something pretty-math-printable (MathML, 
PS, PDF, LaTex, whatever).


Does something like this already exist?

Thanks a lot,
Peter


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Linking problems with a fresh gtk2hs build

2007-10-26 Thread Olivier Boudry
Hello,

I just built gtk2hs 0.9.12 using MinGW, GTK_2.0 and ghc-6.8.0.20071016. I
just changed some EXTERNALDEPS in the Makefile based on info found in the
following page http://haskell.org/haskellwiki/Grapefruit

25a126,128
 if HAVE_SPLIT_BASE
 tools_c2hs_c2hsLocal_EXTERNALDEPS += pretty containers array
 endif
358a362,364
 if HAVE_SPLIT_BASE
 libHSgtk_a_EXTERNALDEPS += containers array
 endif
1578a1585,1587
 if HAVE_SPLIT_BASE
 libHSsoegtk_a_EXTERNALDEPS += old-time
 endif

I had no problem building and installing the library but when trying to
compile the HelloWorld example to check the installation I get this error:

C:\Tempghc --make HelloGtk.hs
Linking HelloGtk.exe ...
C:/Progra~1/Haskell/lib/gtk2hs/libHSgtk.a(Gtk__1.o)(.text+0x419):fake:
undefined
 reference to `__stginit_gtkzm0zi9zi12_GraphicsziUIziGtkziLayoutziHPaned_'
collect2: ld returned 1 exit status

I found an irc log talking of using nm to track the problem. Tried nm and
got this (different from the problem specified in the irc log).

nm libHSgtk.a | grep
__stginit_gtkzm0zi9zi12_GraphicsziUIziGtkziLayoutziHPaned_
 U ___stginit_gtkzm0zi9zi12_GraphicsziUIziGtkziLayoutziHPaned_
c:\MinGW\bin\nm.exe: HPaned__4.o: File format not recognized
c:\MinGW\bin\nm.exe: MenuBar__48.o: File format not recognized

The missing symbol is found but I have a problem with the HPaned__4.o and
MenuBar__48.o of the libHSgtk.a file.

Any idea of what could have gone wrong?

Thanks,

Olivier.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-26 Thread Graham Fawcett
On 10/25/07, Derek Elkins [EMAIL PROTECTED] wrote:
 On Thu, 2007-10-25 at 11:30 -0400, Graham Fawcett wrote:
  I'm writing a Gnu DBM module as an exercise for learning Haskell and
  its FFI. I'm wondering how I might write a function that returns the
  database keys as a lazy list.
 Just use unsafeInterleaveIO in the obvious definition to read all the
 keys.  That said, it's not called unsafeInterleaveIO for no reason.

I got it to work, using unsafeInterleaveIO. Thanks! But I suspect I
might be working too hard to get the result. Is anyone willing to
critique my code?

Given firstKey and nextKey:

  firstKey :: DbP - IO (Maybe String)
  nextKey :: DbP - String - IO (Maybe String)

I wrote these eager and lazy key-iterators:

  allKeys :: DbP - IO [String]
  allKeys = traverseKeys id

  unsafeLazyKeys :: DbP - IO [String]
  unsafeLazyKeys = traverseKeys unsafeInterleaveIO

  traverseKeys :: (IO [String] - IO [String]) - DbP - IO [String]
  traverseKeys valve db = traverse firstKey
  where traverse :: (DbP - IO (Maybe String)) - IO [String]
traverse func = do nxt - func db
   case nxt of
 Nothing - return []
 Just v - do rest - valve $
  traverse (\db -
nextKey db v)
  return $ v : rest

Intuition suggests there's a higher-order way of writing 'traverse'.

(It was an 'aha' moment for me to realize Haskell would let me choose
strict or lazy evaluation by passing in a different 'valve'
function. Powerful stuff.)

Thanks again,
Graham
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell to math

2007-10-26 Thread Peter Verswyvelen
Jerzy K wrote

wants. He wants a specific pretty-printer *in Haskell*. This was most
probably a subject of many students' exercices...

Yes Jerzy, exactly. I wrote some Haskell code to create plots of binary 
relations and functions on the Cartesian plane, using GTK2HS (Cairo). I have to 
pretty print the math formulas used in these plots. Now I'm retyping the math 
formulas in Word, but being a really lazy programmer, I want to automate this 
task.

So I wanted to write some code that renders math formulas (maybe using GTK, or 
to MathML; I must admit I don't know LaTex at all, sorry...), but since this 
feels like a lot of work to get right, I was wandering if it existed allready.

Okay, I could have skipped all the above and just use Maple or whatever other 
tool, but I'm trying to use Haskell whenever possible, because I'm kind of 
addicated to it. Also I still feel a bit stuck in newbie land (although I think 
I'm approaching escape velocity ;-), so I grab every opportunity to practice in 
Haskell...

Thanks,
Peter


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] How to thoroughly clean up Haskell stuff on linux

2007-10-26 Thread Lihn, Steve
Tom,
Although there are ghc rpms
(http://www.haskell.org/ghc/dist/6.6.1/rpm/), it can not be installed as
non-root user. The rpm lock and rpm db issue makes it a complicated and
pathological case -- see thread here
https://lists.dulug.duke.edu/pipermail/rpm-devel/2005-April/000403.html
https://lists.dulug.duke.edu/pipermail/rpm-devel/2005-April/000403.html
 . I don't know if the rpm can be packaged differently as your link
suggests to avoid these issues.
 
I would suggest making a note on the GHC download page for non-root user
not to try the rpm, it is a waste of time. The tar.bz2 file works fine.
Just be careful when dealing with Lambdabot (and GOA). BTW, the 661 rpm
depends on gmp-devel and readline, which further complicated the case
for non-root user.
 
Steve



From: Thomas Hartman [mailto:[EMAIL PROTECTED] 
Sent: Tuesday, October 16, 2007 10:04 AM
To: Lihn, Steve
Cc: Brandon S. Allbery KF8NH; Haskell-Cafe Haskell-Cafe; Stefan O'Rear
Subject: RE: [Haskell-cafe] How to thoroughly clean up Haskell stuff on
linux



Indeed, I don't want to waste time but have no choice (rpm needs root),


not sure if this'll help (never tried it myself) but this claims there's
a non-root way to use rpm 

http://www.techonthenet.com/linux/build_rpm.php 

cheers, t. 
---

This e-mail may contain confidential and/or privileged information. If
you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this

e-mail is strictly forbidden.


--
Notice:  This e-mail message, together with any attachments, contains
information of Merck  Co., Inc. (One Merck Drive, Whitehouse Station,
New Jersey, USA 08889), and/or its affiliates (which may be known
outside the United States as Merck Frosst, Merck Sharp  Dohme or MSD
and in Japan, as Banyu - direct contact information for affiliates is 
available at http://www.merck.com/contact/contacts.html) that may be 
confidential, proprietary copyrighted and/or legally privileged. It is 
intended solely for the use of the individual or entity named on this 
message. If you are not the intended recipient, and have received this 
message in error, please notify us immediately by reply e-mail and then 
delete it from your system.

--___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fusing foldr's

2007-10-26 Thread Josef Svenningsson
Sorry for reacting so late on this mail. I'm digging through some old mails...

On 10/12/07, Dan Weston [EMAIL PROTECTED] wrote:
 Always check optimizations to make sure they are not pessimizations!

 Actually, traversing the list twice is very cheap compared to space
 leakage, and accumulating pairs requires tuple boxing and unboxing which
 I don't know how to get GHC not to do.

I agree hole-heartedly that replacing multiple traversals with a
single traversal should be done with care as it more often than not
results in a pessimization. Indeed you showed just that with your
examples! But I'd thought it'd be interesting to see how it can
actually be an improvement if done carefully.

\begin{code}
import Control.Arrow
import qualified Data.Strict.Tuple as T
import Data.Strict.Tuple (Pair(..))
import Control.Parallel

avg4 = uncurry (/) . (foldl' (+) 0  foldl' (\x y - x + 1) 0)
avgS = T.uncurry (/) . foldl' (\p n - ((+n) *!* (+1)) p) (0 :!: 0)
avgP = uncurry (/) . (foldl' (+) 0 ! foldl' (\x y - x + 1) 0)

(*!*) f g (a :!: b) = f a :!: g b

(!) f g a = fa `par` (fa,ga)
  where fa = f a
ga = g a
\end{code}

avg4 is the function which was best among Dan's benchmarks. avgS uses
strict tuples. I just threw in avgP for fun, it traverses the lists in
parallel. Note: I do have a dual core machine so it makes sense to try
avgP.

I fed these functions to ghc with the -O2 and -threaded flags and
timed them using the list [1..1000]. The result (best times out of
several runs):
avg4: 284 ms
avgS: 184 ms
avgP: 248 ms

It seems doing a single traversal can be faster if your write your
function carefully. Doing the traversal in parallel was beneficial but
not as good as the single traversal.

Cheers,

/Josef
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linking problems with a fresh gtk2hs build

2007-10-26 Thread Duncan Coutts
On Fri, 2007-10-26 at 09:17 -0400, Olivier Boudry wrote:
 Hello,
 
 I just built gtk2hs 0.9.12 using MinGW, GTK_2.0 and
 ghc-6.8.0.20071016. I just changed some EXTERNALDEPS in the Makefile
 based on info found in the following page
 http://haskell.org/haskellwiki/Grapefruit

I'm not sure what's going wrong there. I should note that there is a
gtk2hs-0.9.12 branch which contains the fixes to build with ghc-6.8.0.x
and there will be a gtk2hs point release once ghc-6.8.1 is released.

You could try cleaning, and ./configure --disable-split-objs to see if
that fares any better.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Linking problems with a fresh gtk2hs build

2007-10-26 Thread Olivier Boudry
More info on this problem:

I rebuilt the whole stuff using exactly the same method and working from a
new extract of the sources. Now I get the same kind of error but on another
object. This error looks a bit random!?!

nm.exe libHSgtk.a  /dev/null
C:\MinGW\bin\nm.exe: TextView__112.o: File format not recognized

I checked the other libraries and they all look OK except libHSgtk.a

Could it have something to do with split objects? I have hundreds of
TextView__... objects. I'm no trying to rebuild the whole stuff with
--disable-split-objs.

Olivier.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-26 Thread Brent Yorgey
On 10/26/07, Graham Fawcett [EMAIL PROTECTED] wrote:

 On 10/25/07, Derek Elkins [EMAIL PROTECTED] wrote:
  On Thu, 2007-10-25 at 11:30 -0400, Graham Fawcett wrote:
   I'm writing a Gnu DBM module as an exercise for learning Haskell and
   its FFI. I'm wondering how I might write a function that returns the
   database keys as a lazy list.
  Just use unsafeInterleaveIO in the obvious definition to read all the
  keys.  That said, it's not called unsafeInterleaveIO for no reason.

 I got it to work, using unsafeInterleaveIO. Thanks! But I suspect I
 might be working too hard to get the result. Is anyone willing to
 critique my code?

 Given firstKey and nextKey:

   firstKey :: DbP - IO (Maybe String)
   nextKey :: DbP - String - IO (Maybe String)

 I wrote these eager and lazy key-iterators:

   allKeys :: DbP - IO [String]
   allKeys = traverseKeys id

   unsafeLazyKeys :: DbP - IO [String]
   unsafeLazyKeys = traverseKeys unsafeInterleaveIO

   traverseKeys :: (IO [String] - IO [String]) - DbP - IO [String]
   traverseKeys valve db = traverse firstKey
   where traverse :: (DbP - IO (Maybe String)) - IO [String]
 traverse func = do nxt - func db
case nxt of
  Nothing - return []
  Just v - do rest - valve $
   traverse (\db -
 nextKey db v)
   return $ v : rest

 Intuition suggests there's a higher-order way of writing 'traverse'.


'traverse' is a sort of unfold.  Here's the type of unfoldr:

unfoldr :: (b - Maybe (a,b)) - b - [a]

It's not too hard to implement a monadic version, although I don't think
it's in the libraries:

unfoldrM :: (Monad m) = (b - m (Maybe (a,b))) - b - m [a]
unfoldrM f b = do
next - f b
case next of
Just (a, b') - liftM (a:) (unfoldrM f b')
Nothing - return []

You can probably see the similarity to traverse.  However, the type is
different enough from traverse that I don't think it would be that simple to
implement traverseKeys in terms of unfoldrM.  The fact that traverseKeys
uses different functions for the first step and all the rest makes things
difficult, too.  In the end it looks to me like you're probably better off
just implementing traverse directly as you have done, although perhaps
someone will find a better way.

I will note, however, that the last few lines of traverse can be written
more simply as:

Just v - liftM (v:) . valve . traverse $ (\db - nextKey db v)

or even

Just v - liftM (v:) . valve . traverse . flip nextKey $ v

Perhaps that's going too far for your taste, but the main point is the liftM
(v:); instead of extracting 'rest', consing v, and then putting the new list
back in IO with 'return', you can just use liftM to apply the cons function
inside the monad in the first place.

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fusing foldr's

2007-10-26 Thread Dan Weston
Thanks for letting me know about the Data.Strict library on Hackage. I 
will definitely make use of that! BTW, you left out an import 
Data.List(foldl') in your example.


My timing test is an order of magnitude worse than yours. Do you have an 
extra zero in your list endpoint?


 I fed these functions to ghc with the -O2 and -threaded flags and
 timed them using the list [1..1000]. The result (best times out of
 several runs):
 avg4: 284 ms
 avgS: 184 ms
 avgP: 248 ms

Using ghc -threaded -O2 --make Avg.hs for ghc 6.6.1, I ran your tests on 
[1..1000] and got the user times:


avg4: 12.75 s
avgS:  3.65 s
avgP: 15.56 s

The funny thing is that avg4/avgS = 3.5 for and only 1.5 for you. I 
understand that with only 1 processor my avgP time may be twice yours, 
but not the avgS or avg4.


I have the following machine:

Main memory size: 2026 Mbytes
Num Processors: 1
Processor Type: Intel(R) Xeon(TM) CPU 2.80GHz x32
Clock Speed: 2790 MHZ

Josef Svenningsson wrote:

Sorry for reacting so late on this mail. I'm digging through some old mails...

On 10/12/07, Dan Weston [EMAIL PROTECTED] wrote:

Always check optimizations to make sure they are not pessimizations!

Actually, traversing the list twice is very cheap compared to space
leakage, and accumulating pairs requires tuple boxing and unboxing which
I don't know how to get GHC not to do.


I agree hole-heartedly that replacing multiple traversals with a
single traversal should be done with care as it more often than not
results in a pessimization. Indeed you showed just that with your
examples! But I'd thought it'd be interesting to see how it can
actually be an improvement if done carefully.

\begin{code}
import Control.Arrow
import qualified Data.Strict.Tuple as T
import Data.Strict.Tuple (Pair(..))
import Control.Parallel

avg4 = uncurry (/) . (foldl' (+) 0  foldl' (\x y - x + 1) 0)
avgS = T.uncurry (/) . foldl' (\p n - ((+n) *!* (+1)) p) (0 :!: 0)
avgP = uncurry (/) . (foldl' (+) 0 ! foldl' (\x y - x + 1) 0)

(*!*) f g (a :!: b) = f a :!: g b

(!) f g a = fa `par` (fa,ga)
  where fa = f a
ga = g a
\end{code}

avg4 is the function which was best among Dan's benchmarks. avgS uses
strict tuples. I just threw in avgP for fun, it traverses the lists in
parallel. Note: I do have a dual core machine so it makes sense to try
avgP.

I fed these functions to ghc with the -O2 and -threaded flags and
timed them using the list [1..1000]. The result (best times out of
several runs):
avg4: 284 ms
avgS: 184 ms
avgP: 248 ms

It seems doing a single traversal can be faster if your write your
function carefully. Doing the traversal in parallel was beneficial but
not as good as the single traversal.

Cheers,

/Josef





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-26 Thread Graham Fawcett
On 10/26/07, Brent Yorgey [EMAIL PROTECTED] wrote:
In the end it looks to me like you're probably better off
 just implementing traverse directly as you have done, although perhaps
 someone will find a better way.

Beginner's luck. ;-) I see the unfold similarity, but yes, it doesn't
seem a good fit here.

 I will note, however, that the last few lines of traverse can be written
 more simply as:
 Just v - liftM (v:) . valve . traverse $ (\db - nextKey db v)
 or even
 Just v - liftM (v:) . valve . traverse . flip nextKey $ v

 Perhaps that's going too far for your taste...

Not at all -- it's terse but the data flow is clear.

Thanks very much,
Graham
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe