Re: [Haskell-cafe] Can't seem to get `par` working appropriately with lists

2008-02-22 Thread Luke Andrew

Felipe Lessa wrote:

On Thu, Feb 21, 2008 at 8:58 AM, Luke Andrew [EMAIL PROTECTED] wrote:
  

 test2.hs:

import Control.Parallel

fib1 n = if n == 0 then 0 else if n == 1 then 1 else fib1 (n-1) +
 fib1 (n-2)
fib2 n = if n == 0 then 0 else if n == 1 then 1 else fib2 (n-1) +
 fib2 (n-2)
fiblist1 n = [fib1 x| x - [1..n]]
fiblist2 n = [fib2 x| x - [1..n]]

main = do print $ zipWith (+) (fiblist2 37 `par` fiblist1 37)
 (fiblist2 37)



Besides what Jules Bean said, note also that 'par' works a bit like
'seq', only evaluating until WHNF. So even if you said

main =
  let f1 = fiblist1 37
  f2 = fiblist2 37
  in print $ zipWith (+) (f2 `par` f1) f2

you still wouldn't get what you want. Why? It only evaluates f1 and f2
until it reaches [] or (_:_), and nothing more, it doesn't even try to
figure out that f2 is _:_:_:_:···:[] nor it tries to see that f2 is
1:_, but you wanted that the parallel computation went until f2 was
1:1:2:3:···:[].

To do that, force the list (i.e. do a deep seq). There's
Control.Parallel.Strategies to help you doing this, but if you want to
reimplement it, try

force []  = ()
force (x:xs) = x `seq` force xs

main =
  let f1 = fiblist1 37
  f2 = fiblist2 37
  in print $ zipWith (+) (force f2 `par` f1) f2

'par' will try to see that 'force f2' is really (), but to do that
'force' will go all the way down thru the list forcing its spine and
its values.

HTH,

  
Thanks Felipe, works as advertised. Guest I'm going to have to read up 
on WHNF, I just ignored it after my initial success  hoped it would 
continue to work. Guess I should have RTFM :)

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


Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-22 Thread Thomas Schilling


On 22 feb 2008, at 08.18, Jules Bean wrote:


Thomas Schilling wrote:

On 21 feb 2008, at 18.35, Johan Tibell wrote:


I switched from lazy bytestrings to a left fold in my networking  
code
after reading what Oleg wrote about streams vs folds. No problems  
with

handles, etc. anymore.

Do you fold over chunks?  Can you continue to use Parsek or other  
utilities that need a stream-abstraction, and if so, how do you  
handle the end of a chunk.  This is the kind of callback interface  
where lazy evaluation really abstracts things nicely.


You can't call a stream-abstraction utility using a left-fold- 
enumerator without cheating (unsafeInterleave), because the stream- 
abstraction is incompatible (and leaky! even though it is convenient).


You can convert in the other direction fine.

Chunk are no problem, and convertible: you can build an element  
fold from a chunk fold, and a chunk fold from an element fold (as  
long as there is an 'end-of-input' marker).


Hm, thinking about it, parsers just need to be able to return a  
continuation instead of fail at the end of the input.  This  
continuation can then be invoked with the next chunk as input.

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


Re: [Haskell-cafe] The Proliferation of List-Like Types

2008-02-22 Thread Johan Tibell
On Fri, Feb 22, 2008 at 9:31 AM, Thomas Schilling
[EMAIL PROTECTED] wrote:
  On 22 feb 2008, at 08.18, Jules Bean wrote:
  
   You can't call a stream-abstraction utility using a left-fold-
   enumerator without cheating (unsafeInterleave), because the stream-
   abstraction is incompatible (and leaky! even though it is convenient).
  
   You can convert in the other direction fine.
  
   Chunk are no problem, and convertible: you can build an element
   fold from a chunk fold, and a chunk fold from an element fold (as
   long as there is an 'end-of-input' marker).

  Hm, thinking about it, parsers just need to be able to return a
  continuation instead of fail at the end of the input.  This
  continuation can then be invoked with the next chunk as input.

This is what I'll do and it is also what binary-strict's [1]
IncrementalGet parser does.

1. 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary-strict-0.3.0

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


Re: [Haskell-cafe] Doubting Haskell

2008-02-22 Thread Thomas Davie
A quick note here.  This is a *really* excellent tutorial on a variety  
of subjects.  It shows how monad operators can be used responsibly (to  
clarify code, not obfuscate it), it shows how chosing a good data  
structure and a good algorithm can work wonders for your code, and on  
a simplistic level, it shows how to build a database in Haskell.


Would it be possible to clean this up and put it in the wiki somewhere?

Thanks

Bob

On 20 Feb 2008, at 09:58, Cale Gibbard wrote:


(I'm copying the list on this, since my reply contains a tutorial
which might be of use to other beginners.)

On 19/02/2008, Alan Carter [EMAIL PROTECTED] wrote:

Hi Cale,

On Feb 19, 2008 3:48 PM, Cale Gibbard [EMAIL PROTECTED] wrote:

Just checking up, since you haven't replied on the list. Was my
information useful? Did I miss any questions you might have had? If
you'd like, I posted some examples of using catch here:


Thanks for your enquiry! My experiment continues. I did put a  
progress

report on the list - your examples together with a similar long an
short pair got me over the file opening problem, and taught me some
things about active whitespace :-) I couldn't get withFile working
(says out of scope, maybe 'cos I'm ghc 6.6 on my Mac)


Make sure to put:

import System.IO

at the top of your source file, if you haven't been. This should
import everything documented here:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-IO.html

but it turned out the line I was looking for (collapsed from the  
examples)

was:

 text - readFile data.txt `catch` \_ - return 

This ensures the program never loses control, crashing or becoming
unpredictable by attempting to use an invalid resource, by yielding  
an

empty String if for any reason the file read fails. Then an empty
String makes it very quickly through parsing. I guess that's quite
functiony :-)

Amazing how easy once I knew how. Even stranger that I couldn't  
find a

bread and butter example of it.

Then I was going very quickly for a while. My file is dumped from a
WordPress MySql table. Well formed lines have 4 tab separated fields
(I'm using pipes for tabs here):

line id | record id | property | value

Line IDs are unique and don't matter. All lines with the same record
ID give a value to a property in the same record, similar to this:

1|1|name|arthur
2|1|quest|seek holy grail
3|1|colour|blue
4|2|name|robin
5|2|quest|run away
6|2|colour|yellow

Organizing that was a joy. It took minutes:


let cutUp = tail (filter (\fields - (length fields) == 4)
 (map (\x - split x '\t')  
(lines text)))


This should almost certainly be a function of text:

cutUp text = tail (filter (\fields - (length fields) == 4)
(map (\x - split x '\t') (lines  
text)))



I found a split on someone's blog (looking for a library tokenizer),
but I can understand it just fine. I even get to chuck out ill-formed
lines and remove the very first (which contains MySql column names)  
on

the way through!


Sadly, there's no general library function for doing this. We have
words and lines (and words would work here, if your fields never have
spaces), but nobody's bothered to put anything more general for simple
splitting into the base libraries (though I'm sure there's plenty on
hackage -- MissingH has a Data.String.Utils module which contains
split and a bunch of others, for example). However, for anything more
complicated, there are also libraries like Parsec, which are generally
really effective, so I highly recommend looking at that at some point.


I then made a record to put things in, and wrote some lines to play
with it (these are the real property names):

data Entry = Entry
 { occupation:: String
 , iEnjoyMyJob   :: Int
 , myJobIsWellDefined:: Int
 , myCoworkersAreCooperative :: Int
 , myWorkplaceIsStressful:: Int
 , myJobIsStressful  :: Int
 , moraleIsGoodWhereIWork:: Int
 , iGetFrustratedAtWork  :: Int
 }
...
 let e = Entry{occupation = , iEnjoyMyJob = 0}
 let f = e {occupation = alan}
 let g = f {iEnjoyMyJob = 47}
 putStrLn ((occupation g) ++   ++ (show (iEnjoyMyJob g)))

Then I ran into another quagmire. I think I have to use Data.Map to
build a collection of records keyed by record id, and fill them in by
working through the list of 4 item lists called cutUp. As with the
file opening problem I can find a few examples that convert a list of
tuples to a Data.Map, one to one. I found a very complex example that
convinced me a map from Int to a record is possible, but gave me no
understanding of how to do it. I spent a while trying to use foldl
before I decided it can't be appropriate (I need to pass more  
values).

So I tried a couple of recursive functions, something like:

type Entries = M.Map Int Entry
...
 let entries = loadEntries cutUp
...
loadEntries :: [[String]] - Entries
loadEntries [] = M.empty Entries
loadEntries [x : xs] = loadEntry 

[Haskell-cafe] Tips of Conditional Expression

2008-02-22 Thread TOPE KAREM
I know the following:

[1] That the general form of conditional expression is: if *
Boolean_expression* then *exp1* else *exp2
*[2] That a conditional expression must always have both a then and an
elseexpression.
[3] That both *exp1* and *exp2* must have the same type, which is the type
of the entire conditional expression.
[4] That *exp1* must be true-value and *exp2* must be false-value

Reference: Discrete Mathematics Using Computer by John O'Donnell and et al.
(Second Edition)

My question: Is it possible that exp1 and exp 2  be different function calls
of another functions (separately) elsewhere within the same program?
Note: My Boolean_expression is Boolean
 My *exp1* is a function call elsewhere within the same program
(more like a subroutine)
 My *exp2* is another function call also elsewhere within the same
program.


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


[Haskell-cafe] Re: Tips of Conditional Expression

2008-02-22 Thread Christian Maeder
TOPE KAREM wrote:
 I know the following:
 
 [1] That the general form of conditional expression is: if
 *Boolean_expression* then /exp1/ else /exp2
 /[2] That a conditional expression must always have both a then and an
 else expression.
 [3] That both /exp1/ and /exp2/ must have the same type, which is the
 type of the entire conditional expression.
 [4] That /exp1/ must be true-value and /exp2/ must be false-value
 
 Reference: Discrete Mathematics Using Computer by John O'Donnell and et
 al. (Second Edition)
 
 My question: Is it possible that exp1 and exp 2  be different function
 calls of another functions (separately) elsewhere within the same program?
 Note: My Boolean_expression is Boolean
  My /exp1/ is a function call elsewhere within the same program
 (more like a subroutine)
  My /exp2/ is another function call also elsewhere within the
 same program.

I'm not sure what you're asking, but exp1 and exp2 may have (the same)
function type:

if cond then map else filter :: (Bool - Bool) - [Bool] - [Bool]

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


[Haskell-cafe] Tutorial for using the state monad or a better suggestion?

2008-02-22 Thread Jefferson Heard
So the reason I keep pinging the list so much of late is I'm currently
writing a GLUT program to visualize a heirarchical clustering of
18,000+ protein-protein interaction pairs (and associated
gene-ontology terms).  Thanks for the help on reading CSVs, those who
wrote me back...  my program intitializes and displays its first image
within 6 seconds, about 10 times faster and in 10 times less memory
than the Java program the guy was using.

Now I'm to the point of making this thing interactive, and I I'm
trying to figure out the Haskell way of doing this.  Last time I wrote
a program like this, I made a record data type with all the state and
placed it into an IORef and curried it into the GLUT callback
functions.  I'm going to do the same thing now if there aren't cringes
and wailings from people with a better sense of pure-functional
aesthetics out there on the list with a willingness to either point me
towards a tutorial that would help me do this better.  Keep in mind
that Graphics.UI.GLUT callbacks all want to return an IO (), and thus
leftover state monads at ends of functions aren't going to be
acceptable to the standard library...

Any ideas?  Oh, currently my program state includes:

The geometry I'm rendering (Ptr GLfloat vertex and color arrays),
The same geometry as a display list for rendering into the selection buffer
An indexed and named tree that represents the clustering
A tree of text containing tooltips to display
The previous current mouse position (for dragging purposes)
A couple of histograms as Array.IArray.Diff.DiffArrays
Various parameters for constructing rendered data out of the indexed
tree (for reconstruction after a node is collapsed/expanded)

So I'm carrying around some pretty bulky state; should give you some
understanding as to why I thougt the record data type would be the
sanest way to do this without polluting my parameter list with
individual IORrefs.

Oh, and again, it's not that I don't know that I can make the IORef
solution work, I can and I've done it before.  It's just that I
thought there might be a prettier way to do this.

Thanks in advance!

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


[Haskell-cafe] Re: Tips of Conditional Expression

2008-02-22 Thread TOPE KAREM
Thanks. My question is whether it can call a function (say map) previously
defined elsewhere in the program. Same goes for filter.

Tope

On Fri, Feb 22, 2008 at 6:04 AM, Christian Maeder [EMAIL PROTECTED]
wrote:

 TOPE KAREM wrote:
  I know the following:
 
  [1] That the general form of conditional expression is: if
  *Boolean_expression* then /exp1/ else /exp2
  /[2] That a conditional expression must always have both a then and an
  else expression.
  [3] That both /exp1/ and /exp2/ must have the same type, which is the
  type of the entire conditional expression.
  [4] That /exp1/ must be true-value and /exp2/ must be false-value
 
  Reference: Discrete Mathematics Using Computer by John O'Donnell and et
  al. (Second Edition)
 
  My question: Is it possible that exp1 and exp 2  be different function
  calls of another functions (separately) elsewhere within the same
 program?
  Note: My Boolean_expression is Boolean
   My /exp1/ is a function call elsewhere within the same program
  (more like a subroutine)
   My /exp2/ is another function call also elsewhere within the
  same program.

 I'm not sure what you're asking, but exp1 and exp2 may have (the same)
 function type:

 if cond then map else filter :: (Bool - Bool) - [Bool] - [Bool]

 HTH Christian

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


Re: [Haskell-cafe] Tutorial for using the state monad or a better suggestion?

2008-02-22 Thread Antoine Latter
I was trying to solve a similar problem while learning the FastCGI
package.  The regular CGI package allows the use of ReaderT to hold
config data.  Because FastCGI does the running of the passed in CGI
action within a few calls to alloca :: (Ptr a - IO b) - IO b, I
couldn't figure out a way to use monad transformers.

I settled on the top-level IORef trick I've seen elsewhere:

 bigBallOfState_ :: IORef MyState
 bigBallOfState_ = unsafePerformIO $ newIORef emptyState
 {-# NOINLINE bigBallOfState_ #-}

With a few accessors:

 setState :: MyState - IO ()
 setState = ...

 getState :: IO MyState
 getState = ...

I'm not going to pretend it's good style, and it assumes you only ever
need one copy of the state everywhere in your program.

-Antoine

On Fri, Feb 22, 2008 at 8:15 AM, Jefferson Heard
[EMAIL PROTECTED] wrote:
 So the reason I keep pinging the list so much of late is I'm currently
  writing a GLUT program to visualize a heirarchical clustering of
  18,000+ protein-protein interaction pairs (and associated
  gene-ontology terms).  Thanks for the help on reading CSVs, those who
  wrote me back...  my program intitializes and displays its first image
  within 6 seconds, about 10 times faster and in 10 times less memory
  than the Java program the guy was using.

  Now I'm to the point of making this thing interactive, and I I'm
  trying to figure out the Haskell way of doing this.  Last time I wrote
  a program like this, I made a record data type with all the state and
  placed it into an IORef and curried it into the GLUT callback
  functions.  I'm going to do the same thing now if there aren't cringes
  and wailings from people with a better sense of pure-functional
  aesthetics out there on the list with a willingness to either point me
  towards a tutorial that would help me do this better.  Keep in mind
  that Graphics.UI.GLUT callbacks all want to return an IO (), and thus
  leftover state monads at ends of functions aren't going to be
  acceptable to the standard library...

  Any ideas?  Oh, currently my program state includes:

  The geometry I'm rendering (Ptr GLfloat vertex and color arrays),
  The same geometry as a display list for rendering into the selection buffer
  An indexed and named tree that represents the clustering
  A tree of text containing tooltips to display
  The previous current mouse position (for dragging purposes)
  A couple of histograms as Array.IArray.Diff.DiffArrays
  Various parameters for constructing rendered data out of the indexed
  tree (for reconstruction after a node is collapsed/expanded)

  So I'm carrying around some pretty bulky state; should give you some
  understanding as to why I thougt the record data type would be the
  sanest way to do this without polluting my parameter list with
  individual IORrefs.

  Oh, and again, it's not that I don't know that I can make the IORef
  solution work, I can and I've done it before.  It's just that I
  thought there might be a prettier way to do this.

  Thanks in advance!

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

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


Re: [Haskell-cafe] Rendering TTF fonts in Haskell and OpenGL

2008-02-22 Thread Bit Connor
I also have made haskell bindings to FreeType, including support for
extracting glyph outlines.

I haven't had time to publish it yet. Hopefully I'll get around to it soon.

On Mon, Feb 18, 2008 at 5:07 AM, Jeremy Shaw [EMAIL PROTECTED] wrote:
 At Mon, 18 Feb 2008 01:26:17 +,

 Luke Palmer wrote:

   I have an immature, but precise and picky implementation that renders text 
 in
   a ttf font to an OpenGL texture (using SDL-ttf) here:
   http://svn.luqui.org/svn/misc/luke/work/code/haskell/frp/Fregl/Draw.hs
   (It may have some dependencies in the same directory).  Text support is
   way at the bottom.

  Along the same lines, I have an imcomplete, but direct binding to
  freetype and an incomplete binding to GLX which can be used to draw
  text to opengl textures:

  http://n-heptane.com/nhlab/repos/haskell-freetype/
  http://n-heptane.com/nhlab/repos/haskell-glx/

  This file contains an example of drawing text using GLX+FreeType:

  http://n-heptane.com/nhlab/repos/haskell-freetype/FreeTypeTest.hs

  This code has not been touched in a few years, so it probably needs
  some updates to work with ghc 6.8. Also, I believe the X11 package now
  has builtin support for ClientMessage, so that module can go away.

  j.


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

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


Re: [Haskell-cafe] Re: Tips of Conditional Expression

2008-02-22 Thread Daniel Fischer
Am Freitag, 22. Februar 2008 15:22 schrieb TOPE KAREM:
 Thanks. My question is whether it can call a function (say map) previously
 defined elsewhere in the program. Same goes for filter.

 Tope

Like

oddlyMakeEven [] = []
oddlyMakeEven ks@(k:_) = if odd k then map (*2) ks else filter even ks

?
Sure, each branch can be an arbitrarily complex expression.

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


Re: [Haskell-cafe] Rendering TTF fonts in Haskell and OpenGL

2008-02-22 Thread Claus Reinke

[cc-ed to hopengl list; are there many haskell opengl users
not on that list, btw?]

a standard package for easy-to-use, high-quality, portable 
font support would make a great addition to haskell's 
otherwise nice opengl bindings! 


is there a reason for going directly to freetype? from the
old opengl font survey at 


http://www.opengl.org/resources/features/fontsurvey/

i got the impression that accessing freetype2 via ftgl
might make things slightly easier, while also offering
more options (geometry instead of texture fonts), or 
did I misread?


http://ftgl.wiki.sourceforge.net/

the source doesn't seem to have changed since the
end of 2004, which might imply some issues with
newer compilers, etc?

has anyone tried to bind to ftgl? any comments on
that route?

and to what extent to the haskell gui libs with opengl
support allow their fonts to be used for text geometry
or textures in opengl?

claus

- Original Message - 
From: Bit Connor [EMAIL PROTECTED]

To: Jeremy Shaw [EMAIL PROTECTED]
Cc: Haskell-cafe Cafe haskell-cafe@haskell.org
Sent: Friday, February 22, 2008 2:42 PM
Subject: Re: [Haskell-cafe] Rendering TTF fonts in Haskell and OpenGL



I also have made haskell bindings to FreeType, including support for
extracting glyph outlines.

I haven't had time to publish it yet. Hopefully I'll get around to it soon.

On Mon, Feb 18, 2008 at 5:07 AM, Jeremy Shaw [EMAIL PROTECTED] wrote:

At Mon, 18 Feb 2008 01:26:17 +,

Luke Palmer wrote:

  I have an immature, but precise and picky implementation that renders text in
  a ttf font to an OpenGL texture (using SDL-ttf) here:
  http://svn.luqui.org/svn/misc/luke/work/code/haskell/frp/Fregl/Draw.hs
  (It may have some dependencies in the same directory).  Text support is
  way at the bottom.

 Along the same lines, I have an imcomplete, but direct binding to
 freetype and an incomplete binding to GLX which can be used to draw
 text to opengl textures:

 http://n-heptane.com/nhlab/repos/haskell-freetype/
 http://n-heptane.com/nhlab/repos/haskell-glx/

 This file contains an example of drawing text using GLX+FreeType:

 http://n-heptane.com/nhlab/repos/haskell-freetype/FreeTypeTest.hs

 This code has not been touched in a few years, so it probably needs
 some updates to work with ghc 6.8. Also, I believe the X11 package now
 has builtin support for ClientMessage, so that module can go away.

 j.


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


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

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


[Haskell-cafe] Re: Tips of Conditional Expression

2008-02-22 Thread Christian Maeder
TOPE KAREM wrote:
 Thanks. My question is whether it can call a function (say map)
 previously defined elsewhere in the program. Same goes for filter.

I'm still not sure what to answer. If map and filter were user defined
functions they may occur anywhere in your current module (or must be
imported) and you can apply any argument in scope (of proper type).

You could i.e. apply (if cond then map else filter) to id
  which is the same as if cond then map id else filter id

C.

 On Fri, Feb 22, 2008 at 6:04 AM, Christian Maeder
 [EMAIL PROTECTED] mailto:[EMAIL PROTECTED] wrote:
 I'm not sure what you're asking, but exp1 and exp2 may have (the same)
 function type:
 
 if cond then map else filter :: (Bool - Bool) - [Bool] - [Bool]

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


Re: [Haskell-cafe] haddock as a markdown preprocessor

2008-02-22 Thread Keith Fahlgren
On 2/21/08 3:57 PM, Duncan Coutts wrote:
 Consequently there is no support in
 Cabal etc for those kinds of documentation. GHC, Cabal and c2hs amongst
 others use docbook but it's a horrible format to write and the tools to
 process it are very finicky (we apparently have to hard code paths to
 specific versions of xslt stylesheets).

Hi,

DocBook authoring tools have progressed tremendously in the past few years, and
I disagree that the tools to process it are very finicky. If there are
specific questions about making DocBook more palatable for GHC, Cabal, c2hs,
others, please send them to me directly or the docbook-apps list:
http://www.docbook.org/help


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


[Haskell-cafe] Graphical graph reduction

2008-02-22 Thread dainichi
Hi Haskell-Cafe,

I'm relatively new to Haskell, but have a background with SML. One of the
things that amaze me about Haskell is lazy graph reduction, e.g. how the
graph unfolds during the evaluation of, say,

let fibs = 1 : 1 : zipWith (+) fibs (tail fibs) in take 10 fibs

Lazy lists can be simulated in SML too, but unless I do something clever
with references, I end up taking exponential time to compute the n'th
Fibonacci number.

Now to the point: Wouldn't it be great if I had a visual tool that visually
showed me the graph while the above evaluation unfolded? I could use it to
show some of my co-workers to whom laziness is a mystery, what it's all
about.

Does anybody know if such a tool exists? I'd be grateful for pointers if it
does. I very much doubt that I'm the first person who has thoughts like
this, but then again, who knows. People who really know Haskell might think
this is too trivial a task to really be worth spending time on.

If nothing similar exists, I was thinking about creating such a tool (i.e.
an interpreter with additional graph-displaying features) for a very, very
small subset/dialect of Haskell. I would probably be lazy (no pun intended)
and start right away with abstract syntax trees to avoid lexing and parsing
and such. My language of implementation would be SML, using references as
the edges of the graph.

Any ideas/comments would be welcome.

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


[Haskell-cafe] Re: Tips of Conditional Expression

2008-02-22 Thread TOPE KAREM
Thank you all. I am satisfied with all your inputs.

Tope

On Fri, Feb 22, 2008 at 7:17 AM, Christian Maeder [EMAIL PROTECTED]
wrote:

 TOPE KAREM wrote:
  Thanks. My question is whether it can call a function (say map)
  previously defined elsewhere in the program. Same goes for filter.

 I'm still not sure what to answer. If map and filter were user defined
 functions they may occur anywhere in your current module (or must be
 imported) and you can apply any argument in scope (of proper type).

 You could i.e. apply (if cond then map else filter) to id
  which is the same as if cond then map id else filter id

 C.

  On Fri, Feb 22, 2008 at 6:04 AM, Christian Maeder
  [EMAIL PROTECTED] mailto:[EMAIL PROTECTED] wrote:
  I'm not sure what you're asking, but exp1 and exp2 may have (the
 same)
  function type:
 
  if cond then map else filter :: (Bool - Bool) - [Bool] - [Bool]


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


Re: [Haskell-cafe] Graphical graph reduction

2008-02-22 Thread Svein Ove Aas
2008/2/22  [EMAIL PROTECTED]:
 Does anybody know if such a tool exists? I'd be grateful for pointers if it
 does. I very much doubt that I'm the first person who has thoughts like
 this, but then again, who knows. People who really know Haskell might think
 this is too trivial a task to really be worth spending time on.

 If nothing similar exists, I was thinking about creating such a tool (i.e.
 an interpreter with additional graph-displaying features) for a very, very
 small subset/dialect of Haskell. I would probably be lazy (no pun intended)
 and start right away with abstract syntax trees to avoid lexing and parsing
 and such. My language of implementation would be SML, using references as
 the edges of the graph.

 Any ideas/comments would be welcome.

Rather than spending time on a project specifically to do this, it
seems like a great addition to GHCi's still mostly theoretical
debugger. I'll understand if you don't want to take on such a project
right now, though.

I'm not aware of any program that does exactly what you're asking for,
but I'm attaching a lambdabot interaction for your reading pleasure. I
believe it will speak for itself.

 Baughn  let fibs = 1 : 1 : zipWith (+) fibs (tail fibs) in fibs :: [Expr]
 lambdabot  [1,1,1 + 1,1 + (1 + 1),1 + 1 + (1 + (1 + 1)),1 + (1 + 1)
+ (1 + 1 + (1 + (1 ...
1

-- 
In a demon-haunted world, science is a candle in the dark
http://dresdencodak.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with Python AST

2008-02-22 Thread Roel van Dijk
On Fri, Feb 22, 2008 at 2:42 PM, Daniel Gorín [EMAIL PROTECTED] wrote:

 On Feb 21, 2008, at 7:55 PM, Roel van Dijk wrote:

   Your solutions allows a bit more but fails with the equivalent of
  
   def foo():
 for i in range(10):
   if i == 6:
 return None
  
   The loop context 'overwrites' the function context which makes the
   return statement illegal. I think I need a type level list.

  i see. how about this?

  if_ = If [(IntLit 6, Suite [] [Break])] (Just $ Suite [] [Return])
  while_ = While (IntLit 6) (Suite [] [if_]) Nothing
  while2_ = While (IntLit 6) (Suite [] [Return]) Nothing
  foo = FunDecl $ Suite [] [while_, while2_]

  p = Program [foo]


  newtype Ident = Id String

  data BinOp = Add
 | Sub

  data Exp = IntLit Integer
   | BinOpExp BinOp Exp Exp

  data Ctx reqloop reqfun
  data True
  data False

  data Statement ctx where
If  :: [(Exp, Suite (Ctx reqloop reqfun))]
- Maybe (Else (Ctx reqloop reqfun))
- Statement (Ctx reqloop reqfun)
While   :: Exp
- (Suite (Ctx True reqfun))
- Maybe (Else (Ctx True reqfun))
- Statement (Ctx reqloop reqfun)
Pass:: Statement (Ctx reqloop reqfun)
Break   :: Statement (Ctx True reqfun)
Return  :: Statement (Ctx reqloop True)
FunDecl :: Suite (Ctx False reqfun) - Statement (Ctx False False)

  newtype Global = Global [Ident]

  data Suite ctx = Suite [Global] [Statement ctx]

  type Else ctx = Suite ctx

  newtype Program = Program [Statement (Ctx False False)]

Ah, you set a specific context when needed. Very nice. Although I had
to remove the Ctx type. Otherwise I need pattern matching at the type
level to bind the reqLoop and reqFun type variables (is such a thing
even possible?):

  data Statement (Ctx reqLoop reqFun) where 

Now I simple pass 2 type variables to my statements:

  data Statement reqLoop reqFun where 

I now have a complete Python AST and pretty printer. Onwards towards a parser!

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


Re: [Haskell-cafe] Graphical graph reduction

2008-02-22 Thread Bulat Ziganshin
Hello dainichi,

Friday, February 22, 2008, 6:55:54 PM, you wrote:

 If nothing similar exists, I was thinking about creating such a
 tool (i.e. an interpreter with additional graph-displaying features)

not exactly this, but now i'm reading introduction into Q language [1]
which says on p.11 The interpreter has a built-in symbolic debugger
which allows you to execute a reduction sequence step by step: ...,
so you may use it to demonstrate how reductions work. Q by itself is
rather interesting language - haskell-like syntax, dynamic, eager with
good support for laziness. btw, this manual is probably better than we
have for Haskell, i've seen programmers who thinks that Haskell is
hard to learn and Q is simple and may be it's just due to its manual
which takes into account typical learning problems and explains
obvious things (which are really obvious only for seasoned FP
programmers)

[1] http://switch.dl.sourceforge.net/sourceforge/q-lang/qnutshell-0.5.pdf


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: Graphical graph reduction

2008-02-22 Thread apfelmus

Kai wrote:

Wouldn't it be great if I had a visual tool that visually
showed me the graph while the above evaluation unfolded?

Does anybody know if such a tool exists?


I don't know of such a tool, the closest one to that is probably the new 
ghci debugger.


There is also a paper and accompanying website

  Peter Sestoft. Demonstrating Lambda Calculus Reduction.
  http://www.dina.kvl.dk/~sestoft/lamreduce/

but graph reduction with sharing is not covered.

Slightly off topic, Twan's blog post

  http://twan.home.fmf.nl/blog/haskell/
simple-reflection-of-expressions.details

demonstrates a neat way to figure out how (polymorphic) higher-order 
functions like  foldr  or  foldl  work. It would be really cool if there 
was a similar embedded approach for graph reduction, but I don't think 
that's possible.



If nothing similar exists, I was thinking about creating such a tool (i.e.
an interpreter with additional graph-displaying features) for a very, very
small subset/dialect of Haskell.


The Haskell wikibook http://en.wikibooks.org/wiki/Haskell would 
greatly benefit from such a tool for the chapters about graph reduction, 
so I'd be a potential user :)



I would probably be lazy (no pun intended)
and start right away with abstract syntax trees to avoid lexing and parsing
and such.  My language of implementation would be SML, using references as
the edges of the graph.


Of course, I'd prefer Haskell as the implementation language and since 
you want to learn Haskell anyway ... :)


Concerning the graph representation, using references is probably a bad 
idea anyway since they're not purely functional in style. There is 
Martin Erwig's Functional Graph Library (Data.Graph.Inductive) shipping 
with ghc:


  Martin Erwig. Inductive Graphs and Functional Graph Algorithms.
  http://web.engr.oregonstate.edu/~erwig/papers/abstracts.html#JFP01

There is also

  Norman Ramsey, João Dias.
  An Applicative Control-Flow Graph Based on Huet’s Zipper.

which uses a zipper to represent a control-flow graph. I'm mentioning 
this paper for the following quote: the mutable flow graph was big and 
complex, and it led to many bugs. We have replaced it by a smaller, 
simpler, applicative flow graph based on Huet’s (1997) zipper. The new 
flow graph is a success. In other words: forget mutable references :)


Moreover, it's not clear whether a graph should be used at all. Well, at 
least concerning the _presentation_. A todo-note at the beginning of 
http://en.wikibooks.org/wiki/Haskell/Graph_reduction lists the 
possible choices, I'm currently leaning in favor of a  let .. in 
statements in the spirit of


  John Maraist, Martin Odersky and Philip Wadler.
  The call-by-need lambda calculus.
  http://homepages.inf.ed.ac.uk/wadler/topics/
call-by-need.html#need-journal


Overall, the main problem for a graph reduction demonstration tool to 
solve is not how to perform graph reduction but how to present it. The 
point is: the tool is unnecessary for very simple examples since those 
are better done by hand. But an unsophisticated tool is useless for the 
more complicated cases too, since no one can make sense of the output 
anymore!



Regards,
apfelmus

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


Re: [Haskell-cafe] Tutorial for using the state monad or a better suggestion?

2008-02-22 Thread Brandon S. Allbery KF8NH


On Feb 22, 2008, at 9:15 , Jefferson Heard wrote:


Now I'm to the point of making this thing interactive, and I I'm
trying to figure out the Haskell way of doing this.  Last time I wrote
a program like this, I made a record data type with all the state and
placed it into an IORef and curried it into the GLUT callback
functions.  I'm going to do the same thing now if there aren't cringes
and wailings from people with a better sense of pure-functional
aesthetics out there on the list with a willingness to either point me
towards a tutorial that would help me do this better.  Keep in mind
that Graphics.UI.GLUT callbacks all want to return an IO (), and thus
leftover state monads at ends of functions aren't going to be
acceptable to the standard library...


What I do (with gtk2hs) is visible at http://hpaste.org/3137 ---  
MWPState is a fairly large record.


I will note that this code stores the mutable data in separate  
IORefs, whereas I'm told that it's better to use a single IORef with  
all the mutable state inside it.  (For some reason I had assumed that  
the overhead would be higher.)  That said, the wrappers make it  
fairly easy to refactor it.  Since the IORef(s) and much of the  
remaining state is read-only, I use a ReaderT IO instead of StateT  
IO; this also turned out to be convenient for what turned out to be a  
significant optimization (in response to a timer firing, it collects  
a bunch of data and feeds it into a TreeView, and it turned out to be  
useful to collect it all at the front and use local to roll a  
modified record with the cached values).


(The code in that paste is rather out of date, probably I should  
update it.)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Tutorial for using the state monad or a better suggestion?

2008-02-22 Thread Jefferson Heard
Thanks.  There seems to be some consensus developing around using
IORefs to hold all the program state.

-- Jeff

On Fri, Feb 22, 2008 at 12:11 PM, Brandon S. Allbery KF8NH
[EMAIL PROTECTED] wrote:

  On Feb 22, 2008, at 9:15 , Jefferson Heard wrote:

   Now I'm to the point of making this thing interactive, and I I'm
   trying to figure out the Haskell way of doing this.  Last time I wrote
   a program like this, I made a record data type with all the state and
   placed it into an IORef and curried it into the GLUT callback
   functions.  I'm going to do the same thing now if there aren't cringes
   and wailings from people with a better sense of pure-functional
   aesthetics out there on the list with a willingness to either point me
   towards a tutorial that would help me do this better.  Keep in mind
   that Graphics.UI.GLUT callbacks all want to return an IO (), and thus
   leftover state monads at ends of functions aren't going to be
   acceptable to the standard library...

  What I do (with gtk2hs) is visible at http://hpaste.org/3137 ---
  MWPState is a fairly large record.

  I will note that this code stores the mutable data in separate
  IORefs, whereas I'm told that it's better to use a single IORef with
  all the mutable state inside it.  (For some reason I had assumed that
  the overhead would be higher.)  That said, the wrappers make it
  fairly easy to refactor it.  Since the IORef(s) and much of the
  remaining state is read-only, I use a ReaderT IO instead of StateT
  IO; this also turned out to be convenient for what turned out to be a
  significant optimization (in response to a timer firing, it collects
  a bunch of data and feeds it into a TreeView, and it turned out to be
  useful to collect it all at the front and use local to roll a
  modified record with the cached values).

  (The code in that paste is rather out of date, probably I should
  update it.)

  --
  brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
  system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
  electrical and computer engineering, carnegie mellon universityKF8NH






-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


[Haskell-cafe] Re: Haskell + Windows Mobile?

2008-02-22 Thread David B . Wildgoose
Bulat Ziganshin bulat.ziganshin at gmail.com writes:

 
 Hello haskell-cafe,
 
 is there any haskell implementation for Windows Mobile? does they are
 support creation of GUI apps and internet networking features?
 

Hugs is available for Windows CE, (I have it on my Jornada 720), but I've only 
used it for non-GUI work.

However with Windows Mobile 5 Microsoft decided to unilaterally remove the 
console drivers, instantly breaking a large number of useful Windows CE 
programs.


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


Re: [Haskell-cafe] haddock as a markdown preprocessor

2008-02-22 Thread Conal Elliott
Hi Yitzchak,

About -- |, -- ^, and -- $doc, we might call them markup
meta-directives, since they delimit the text to be preprocessed and then
produced as markup.  The meta-directives and the --  line prefixes would
be removed in the process.

As for producing machine-readable API metadata, I hadn't been thinking along
those lines, and I enthusiastically agree with you.  Further factor haddock
into a metadata extractor and a documentation generator.

Cheers,  - Conal


On Fri, Feb 22, 2008 at 3:25 AM, Yitzchak Gale [EMAIL PROTECTED] wrote:

 Conal Elliott wrote:
  Pare the Haddock markup language down to
  very few markup directives, say just 'foo' and
  Foo.Bar.

 Other critical ones:

 -- | This shows which syntax this text describes.
 -- ^ So does this.

 Less critical, but usually not provided by general
 markup languages:

 -- $doc A movable documentation chunk.

 If Haddock itself does not parse any other markup,
 we must make sure to use markup that does not
 lock up its information. It should be something we
 have a parser for, or something that has good
 tools for turning it into some robust machine-readable
 format in a lossless way.

 The reason is that I may want to use a bit of
 Haskell in a much larger project that uses some
 other markup system for its API documentation.

 So, for example, if I want to integrate the output
 into a larger DITA project, there should be an easy
 way to do that. Or Doxygen, or whatever else.

 Then Haddock would need to have some way
 of outputting its own information nicely, with
 embedded chunks of markup. You would read that,
 passing each chunk of markup through its parser.

 Truth is, I don't see any such parser for markdown.
 Do you know of one? Maybe we would have to
 write one.

 I think that improving the markup capabilities of
 Haddock is a minor issue. The main value of
 Haddock is its API metadata. Haddock currently
 keeps most of that in its bellly, using it secretly
 to create its own presentation output. The biggest
 improvement would be getting meaningful
 machine-readable output.

 Your idea of abstracting out the markup could
 actually make that easier, if we keep that goal
 in mind as well.

 Thanks,
 Yitz

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


Re: [Haskell-cafe] Tutorial for using the state monad or a better suggestion?

2008-02-22 Thread Don Stewart
jefferson.r.heard:
 So the reason I keep pinging the list so much of late is I'm currently
 writing a GLUT program to visualize a heirarchical clustering of
 18,000+ protein-protein interaction pairs (and associated
 gene-ontology terms).  Thanks for the help on reading CSVs, those who
 wrote me back...  my program intitializes and displays its first image
 within 6 seconds, about 10 times faster and in 10 times less memory
 than the Java program the guy was using.

Wonderful. I'm glad you're making progress. Be sure to lean on the
friendly Haskell consultants of -cafe@ for help as you need it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haddock as a markdown preprocessor

2008-02-22 Thread Reinier Lamers


Op 22-feb-2008, om 1:54 heeft Conal Elliott het volgende geschreven:
The goal redesigning for composability is that we get more for  
less.  Haddock can focus on its speciality, namely hyperlinked  
Haskell code documentation, and pandoc on its, namely human- 
writable and -readable prose with modern features (images, friendly  
hyperlinks, smart quotes  dashes, footnotes, super- and  
subscripts, pretty math, bibliography-style link specs, etc).   
Haddock development can focus its resources on Haskell-specific  
functionality, and we library writers can still use a full-featured  
mark-up language.
While I like the idea of a very powerful authoring system, I doubt  
that we should mix the documentation code with the source code. It  
seems much clearer to me to separate such heavily-formatted  
documentation from the source into separate files.


Of course, the source code includes comments that specify what  
functions do, and so provide a bit of API documentation. But such  
comments should contain as little formatting as possible to keep them  
readable in a text editor.


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


Re: [Haskell-cafe] Rendering TTF fonts in Haskell and OpenGL

2008-02-22 Thread Don Stewart
bit:
 I also have made haskell bindings to FreeType, including support for
 extracting glyph outlines.
 
 I haven't had time to publish it yet. Hopefully I'll get around to it
 soon.

Do you need a place to host the repository? code.haskell.org
is available if you want to host there.

Just visit community.haskell.org and request an account.

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


Fwd: [Haskell-cafe] Repeated function application

2008-02-22 Thread Thomas Hartman
This was easier for me to understand when written so, with the start
 value explicit

 times3 :: (a - a) - Int - (a - a)
 times3 f n !start | n == 0 = start
   | otherwise = times3 f (n-1) (f start)

 -- no stack overflow :)
 tTimes3 = times3 (+1) 100 0

 Here, only the third arg, the start value, needs to be
 bangified/strictified, and it's pretty clear why. Without the bang
pattern, it stack overflows.

 What I'm not sure of is whether this version is in fact completely
 equivalent to Dan's version above.

 I hope it is.

 2008/2/21, Dan Weston [EMAIL PROTECTED]:

 Ben Butler-Cole wrote:
Hello
   
I was surprised to be unable to find anything like this in the
standard libraries:
   
times :: (a - a) - Int - (a - a)
times f 0 = id
times f n = f . (times f (n-1))
   
Am I missing something more general which would allow me to
repeatedly apply a function to an input? Or is this not useful?
 
 
  Invariably, this seems to invite a stack overflow when I try this (and
   is usually much slower anyway). Unless f is conditionally lazy, f^n and
   f will have the same strictness, so there is no point in keeping nested
   thunks.
 
   If you apply f immediately to x, there is no stack explosion and faster
   runtime:
 
 
   times :: (a - a) - Int - (a - a)
 
  times f !n !x | n  0 = times f (n-1) (f x)
 | otherwise = x
 
 
   Dan
 
 
   ___
   Haskell-Cafe mailing list
   Haskell-Cafe@haskell.org
   http://www.haskell.org/mailman/listinfo/haskell-cafe
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Repeated function application

2008-02-22 Thread Thomas Hartman
On second thought... never mind.

The only thing of (somewhat marginal) interest that my latest comment
adds is that the second argument doesn't need to be strict.

Otherwise my code is exactly identical to Dan's.

2008/2/22, Thomas Hartman [EMAIL PROTECTED]:
 This was easier for me to understand when written so, with the start

  value explicit

   times3 :: (a - a) - Int - (a - a)
   times3 f n !start | n == 0 = start
| otherwise = times3 f (n-1) (f start)

   -- no stack overflow :)
   tTimes3 = times3 (+1) 100 0

   Here, only the third arg, the start value, needs to be

  bangified/strictified, and it's pretty clear why. Without the bang
  pattern, it stack overflows.


   What I'm not sure of is whether this version is in fact completely
   equivalent to Dan's version above.

   I hope it is.

   2008/2/21, Dan Weston [EMAIL PROTECTED]:

   Ben Butler-Cole wrote:
  Hello
 
  I was surprised to be unable to find anything like this in the
  standard libraries:
 
  times :: (a - a) - Int - (a - a)
  times f 0 = id
  times f n = f . (times f (n-1))
 
  Am I missing something more general which would allow me to
  repeatedly apply a function to an input? Or is this not useful?
   
   
Invariably, this seems to invite a stack overflow when I try this (and
 is usually much slower anyway). Unless f is conditionally lazy, f^n and
 f will have the same strictness, so there is no point in keeping nested
 thunks.
   
 If you apply f immediately to x, there is no stack explosion and faster
 runtime:
   
   
 times :: (a - a) - Int - (a - a)
   
times f !n !x | n  0 = times f (n-1) (f x)
   | otherwise = x
   
   
 Dan
   
   
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
   

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


Re: [Haskell-cafe] Repeated function application

2008-02-22 Thread Dan Weston
Actually, the second argument is already strict, and the ! doesn't make 
it any stricter (and is therefore gratuitous): when you evaluate the 
conditional (n == 0), n is evaluated.


Dan

Thomas Hartman wrote:

On second thought... never mind.

The only thing of (somewhat marginal) interest that my latest comment
adds is that the second argument doesn't need to be strict.

Otherwise my code is exactly identical to Dan's.

2008/2/22, Thomas Hartman [EMAIL PROTECTED]:

This was easier for me to understand when written so, with the start

 value explicit

  times3 :: (a - a) - Int - (a - a)
  times3 f n !start | n == 0 = start
   | otherwise = times3 f (n-1) (f start)

  -- no stack overflow :)
  tTimes3 = times3 (+1) 100 0

  Here, only the third arg, the start value, needs to be

 bangified/strictified, and it's pretty clear why. Without the bang
 pattern, it stack overflows.


  What I'm not sure of is whether this version is in fact completely
  equivalent to Dan's version above.

  I hope it is.

  2008/2/21, Dan Weston [EMAIL PROTECTED]:

  Ben Butler-Cole wrote:
 Hello

 I was surprised to be unable to find anything like this in the
 standard libraries:

 times :: (a - a) - Int - (a - a)
 times f 0 = id
 times f n = f . (times f (n-1))

 Am I missing something more general which would allow me to
 repeatedly apply a function to an input? Or is this not useful?
  
  
   Invariably, this seems to invite a stack overflow when I try this (and
is usually much slower anyway). Unless f is conditionally lazy, f^n and
f will have the same strictness, so there is no point in keeping nested
thunks.
  
If you apply f immediately to x, there is no stack explosion and faster
runtime:
  
  
times :: (a - a) - Int - (a - a)
  
   times f !n !x | n  0 = times f (n-1) (f x)
  | otherwise = x
  
  
Dan
  
  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
  


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





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


[Haskell-cafe] Haskell w/ delimited continuations

2008-02-22 Thread Taral
My understanding of these things is limited, but what would stop me,
theoretically speaking, of making a version of ghc with these
primitives added:

type Prompt r

reset :: (Prompt r - r) - r
shift :: Prompt r - ((a - _) - r) - a

(Where _ is either r or forall b. b)

-- 
Taral [EMAIL PROTECTED]
Please let me know if there's any further trouble I can give you.
-- Unknown
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell w/ delimited continuations

2008-02-22 Thread Ryan Ingram
You might want to take a look at
http://www.haskell.org/pipermail/haskell/2007-December/020034.html

which shows an implementation of delimited continuations in Haskell98
and possibly gets rid of any requirement of implementing primitives.

  -- ryan

On 2/22/08, Taral [EMAIL PROTECTED] wrote:
 My understanding of these things is limited, but what would stop me,
 theoretically speaking, of making a version of ghc with these
 primitives added:

 type Prompt r

 reset :: (Prompt r - r) - r
 shift :: Prompt r - ((a - _) - r) - a

 (Where _ is either r or forall b. b)

 --
 Taral [EMAIL PROTECTED]
 Please let me know if there's any further trouble I can give you.
-- Unknown
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] haddock as a markdown preprocessor

2008-02-22 Thread Conal Elliott
On Fri, Feb 22, 2008 at 10:57 AM, Reinier Lamers [EMAIL PROTECTED]
wrote:

 [...]
 Of course, the source code includes comments that specify what
 functions do, and so provide a bit of API documentation. But such
 comments should contain as little formatting as possible to keep them
 readable in a text editor.

Hi Reinier,

Do you know about the [Markdown] format and the [Pandoc] processor?
[Markdown] is designed for *readability* in text editors and based on common
text conventions.

From the [markdown] home page:

 The overriding design goal for Markdown's formatting syntax is to make it
as readable as possible. The idea is that a Markdown-formatted document
should be publishable as-is, as plain text, without looking like it's been
marked up with tags or formatting instructions. While Markdown's syntax has
been influenced by several existing text-to-HTML filters, the single biggest
source of inspiration for Markdown's syntax is the format of plain text
email.

Don't take their word for it or mine.  You can copy and paste this message
into the [Try Pandoc] page.

Regards,   - Conal

[Markdown]: http://daringfireball.net/projects/markdown The markdown
project page
[Pandoc]: http://johnmacfarlane.net/pandoc/try The Pandoc project page
[Try Pandoc]: http://johnmacfarlane.net/pandoc/try Try out Pandoc for
yourself
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell w/ delimited continuations

2008-02-22 Thread Don Stewart
See also,

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/CC-delcont

An implementation of multi-prompt delimited continuations based on the
paper, A Monadic Framework for Delimited Continuations, by R. Kent
Dybvig, Simon Peyton Jones and Amr Sabry

reset :: MonadDelimitedCont p s m = (p a - m a) - m a
shift :: MonadDelimitedCont p s m = p b - ((m a - m b) - m b) - m a

ryani.spam:
 You might want to take a look at
 http://www.haskell.org/pipermail/haskell/2007-December/020034.html
 
 which shows an implementation of delimited continuations in Haskell98
 and possibly gets rid of any requirement of implementing primitives.
 
   -- ryan
 
 On 2/22/08, Taral [EMAIL PROTECTED] wrote:
  My understanding of these things is limited, but what would stop me,
  theoretically speaking, of making a version of ghc with these
  primitives added:
 
  type Prompt r
 
  reset :: (Prompt r - r) - r
  shift :: Prompt r - ((a - _) - r) - a
 
  (Where _ is either r or forall b. b)
 
  --
  Taral [EMAIL PROTECTED]
  Please let me know if there's any further trouble I can give you.
 -- Unknown
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Support for Transaction Memory by Sun Microsystems ..

2008-02-22 Thread Galchin Vasili
Hello,

 Found this:


http://www.theregister.co.uk/2007/08/21/sun_transactional_memory_rock/


http://research.sun.com/spotlight/2007/2007-08-13_transactional_memory.html

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


Re: [Haskell-cafe] Re: Haskell w/ delimited continuations

2008-02-22 Thread Derek Elkins
On Fri, 2008-02-22 at 14:27 -0800, Taral wrote:
 On 2/22/08, Taral [EMAIL PROTECTED] wrote:
   reset :: (Prompt r - r) - r
   shift :: Prompt r - ((a - _) - r) - a
 
 The point of the question is about shift/reset with *these types*. I
 know there are implementations with other types.


Nothing but sanity is stopping you.  If you make a new language, you can
do whatever you like.  However, with shift and reset you can represent
any effect, so you would utterly lose purity.

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


[Haskell-cafe] Re: Haskell w/ delimited continuations

2008-02-22 Thread Taral
On 2/22/08, Taral [EMAIL PROTECTED] wrote:
  reset :: (Prompt r - r) - r
  shift :: Prompt r - ((a - _) - r) - a

The point of the question is about shift/reset with *these types*. I
know there are implementations with other types.

-- 
Taral [EMAIL PROTECTED]
Please let me know if there's any further trouble I can give you.
-- Unknown
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell w/ delimited continuations

2008-02-22 Thread Taral
On 2/22/08, Derek Elkins [EMAIL PROTECTED] wrote:
 Nothing but sanity is stopping you.  If you make a new language, you can
  do whatever you like.  However, with shift and reset you can represent
  any effect, so you would utterly lose purity.

Can you give an example of an impure function created using these primitives?

-- 
Taral [EMAIL PROTECTED]
Please let me know if there's any further trouble I can give you.
-- Unknown
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell w/ delimited continuations

2008-02-22 Thread Derek Elkins
On Fri, 2008-02-22 at 15:13 -0800, Taral wrote:
 On 2/22/08, Derek Elkins [EMAIL PROTECTED] wrote:
  Nothing but sanity is stopping you.  If you make a new language, you can
   do whatever you like.  However, with shift and reset you can represent
   any effect, so you would utterly lose purity.
 
 Can you give an example of an impure function created using these primitives?

shift and reset

but see these slides
http://cs.ioc.ee/mpc-amast06/msfp/filinski-slides.pdf
and/or one or both of 
http://citeseer.ist.psu.edu/filinski94representing.html
http://citeseer.ist.psu.edu/filinski99representing.html

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


[Haskell-cafe] Re: [Haskell] Re: Re: RE: Extensible records: Static duck typing

2008-02-22 Thread Ben Franksen
Mark P Jones wrote:
 Ben Franksen wrote:
 TREX seems to be generally agreed to be too complicated to implement and
 explain.
 
 What evidence do you have for this?

Not much, I have to admit that. It basically seems to be SPJ's opinion, as
he writes in his proposal that he never got around to implementing [TREX]
in GHC. Why not? Mainly because the implementation cost turned out to be
relatively high and further claims his new proposal is considerably
simpler to implement, and [...] it is rather simpler to explain.

I also had the impression from earlier discussions that there are few people
who support the TREX idea. I could be completely wrong, though.

 Speaking as somebody who
 implemented Trex for Hugs (and who also witnessed Ben Gaster
 build an independent implementation), I'd have to disagree
 about the first part of this.  As I recall, the implementation
 was reasonably straightforward, and wasn't any more complicated
 than other common type system extensions that I've worked on.
 I'm also not sure why you think it is complicated to explain,
 but I suppose that's even more subjective.

I did not say, nor did I want to imply, that this is my own opinion. I would
be extremely happy to have TREX in ghc and all the other implementations, I
just fear that it is not going to happen, at least not any time soon. In
fact I am almost completely un-biased as to which record system Haskell
gets, as long as DOES get one and preferably IN MY LIFETIME. I'd give up a
serious amount of expressive power if it brings us nearer to this goal.
Maybe this is just me being short-sighted and egotistical.

 One of the most difficult things about the Trex implementation
 was finding a syntax that meshed nicely with the rest of the
 Haskell syntax. This is likely to be a problem for any record
 system extension of Haskell---unless you're prepared to accept
 a more unconventional syntax---because many of the symbols that
 you might want to use ({, }, ., |, \, for example) have already
 been adopted for other purposes.  Ah, syntax!

Oh yes, that is indeed quite hard. One more reason for me to a prefer a
simpler system.

Cheers
Ben

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


Re: [Haskell-cafe] haddock as a markdown preprocessor

2008-02-22 Thread Duncan Coutts

On Fri, 2008-02-22 at 07:21 -0800, Keith Fahlgren wrote:
 On 2/21/08 3:57 PM, Duncan Coutts wrote:
  Consequently there is no support in
  Cabal etc for those kinds of documentation. GHC, Cabal and c2hs amongst
  others use docbook but it's a horrible format to write and the tools to
  process it are very finicky (we apparently have to hard code paths to
  specific versions of xslt stylesheets).
 
 Hi,
 
 DocBook authoring tools have progressed tremendously in the past few years, 
 and
 I disagree that the tools to process it are very finicky. If there are
 specific questions about making DocBook more palatable for GHC, Cabal, c2hs,
 others, please send them to me directly or the docbook-apps list:
 http://www.docbook.org/help

I admit to knowing rather little about it but I've noticed that these
three projects are using xsltproc directly as their docbook processor
(the other two just copied GHC). Because xsltproc is a general purpose
tool they have to supply a large number of parameters including a hard
coded location of an xslt script (and xsltproc seems to always want to
go to the network to download a dtd when it already has a version it can
use offline).

Currently Cabal uses:
xsltproc --param use.id.as.filename 1 --param toc.section.depth 3
 --stringparam base.dir dist/doc/users-guide/
 --stringparam html.stylesheet doc/fptools.css
 /usr/share/sgml/docbook/xsl-stylesheets-1.70.1/xhtml/chunk.xsl
 doc/Cabal.xml

Yes, that's a hard coded path to the style sheet. GHC does it slightly
more cleverly by using a configure.ac test to look through a very large
number of hard coded paths to try and find the above style sheet.
c2hs used to use docbook2html which was easier to use in terms of
specifying command lines but produced worse output and didn't seem to
work on more recent distros so c2hs switched to xml docbook format
rather than the previous sgml format.

Basically I'd like to know what tool (that is packaged on every linux
distro) do I use to convert a docbook .xml file to xhtml. I took a quick
look on the FAQ linked from docbook.org/help and could not immediately
find what standard tools and commands I'm supposed to use.

Duncan

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


Re: [Haskell-cafe] haddock as a markdown preprocessor

2008-02-22 Thread Duncan Coutts

On Sat, 2008-02-23 at 01:28 +, Duncan Coutts wrote:

 Basically I'd like to know what tool (that is packaged on every linux
 distro) do I use to convert a docbook .xml file to xhtml. I took a quick
 look on the FAQ linked from docbook.org/help and could not immediately
 find what standard tools and commands I'm supposed to use.

After a bit more looking around I found the xmlto program which is
packaged for my distro:

xmlto xhtml doc/Cabal.xml -o doc/manual

That's considerably nicer. Now all I need to do is figure out how to
tell it to use a particular css file we use.

I can't help noticing that the second tutorial listed on the wiki (and
the first one I've found that actually tells you want tools to use)
seems to suggest using xsltproc with long hard coded paths:
http://opensource.bureau-cornavin.com/crash-course/en/hello-world.html

Duncan

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


Re: [Haskell-cafe] Re: Haskell w/ delimited continuations

2008-02-22 Thread Taral
On 2/22/08, Derek Elkins [EMAIL PROTECTED] wrote:
 shift and reset

I was under the impression that reset was a pure function. What side
effects does it have?

-- 
Taral [EMAIL PROTECTED]
Please let me know if there's any further trouble I can give you.
-- Unknown
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell w/ delimited continuations

2008-02-22 Thread Derek Elkins
On Fri, 2008-02-22 at 19:04 -0800, Taral wrote:
 On 2/22/08, Derek Elkins [EMAIL PROTECTED] wrote:
  shift and reset
 
 I was under the impression that reset was a pure function. What side
 effects does it have?

It depends on how you define pure function.  It's not particularly
relevant and I mostly included it as I consider them a pair.

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


[Haskell-cafe] Re: Haskell w/ delimited continuations

2008-02-22 Thread Taral
On 2/22/08, Taral [EMAIL PROTECTED] wrote:
  shift :: Prompt r - ((a - _) - r) - a

  (Where _ is either r or forall b. b)

It occurs to me that _ has to be r, otherwise the subcontinuation can escape.

-- 
Taral [EMAIL PROTECTED]
Please let me know if there's any further trouble I can give you.
-- Unknown
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe