What's difference between Integer and Int?

2003-08-19 Thread Serguey Zefirov
Hello glasgow-haskell-users,

The following program
---
--main = print (show (fibs!!20))
main = print (show (nth 20 fibs))

nth 0 (h:_) = h
nth n (h:t) = nth (n-1) t

fibs :: [Integer]
-- fibs = 1 : (map snd $ iterate (\(x,y) - (y, x+y)) (1,1))
fibs = [1..]
---
compiled with ghc 6.0:

  ghc -O -o a.exe a.hs

does not execute correctly. It causes stack overflow in 1M stack.

If we change fibs :: [Integer] to fibs :: [Int] the new program
runs Ok. 


-- 
Best regards,
 Serguey  mailto:[EMAIL PROTECTED]

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: What's difference between Integer and Int?

2003-08-19 Thread Carsten Schultz
Hi Serguey!

On Tue, Aug 19, 2003 at 03:14:53PM -0700, Serguey Zefirov wrote:
 Hello glasgow-haskell-users,
 
 The following program
 ---
 --main = print (show (fibs!!20))
 main = print (show (nth 20 fibs))
 
 nth 0 (h:_) = h
 nth n (h:t) = nth (n-1) t
 
 fibs :: [Integer]
 -- fibs = 1 : (map snd $ iterate (\(x,y) - (y, x+y)) (1,1))
 fibs = [1..]
 ---
 compiled with ghc 6.0:
 
   ghc -O -o a.exe a.hs
 
 does not execute correctly. It causes stack overflow in 1M stack.
 
 If we change fibs :: [Integer] to fibs :: [Int] the new program
 runs Ok. 

I was confused by that at first, too.  This is caused by the way [1..]
works. `nth 20 [1..]' returns the expression `1+1+1+1+1+1+1+...+1'
and evaluating that causes the stack overflow.  For Ints the additions
are apparently carried out during the construction of [1..], probably
because they are considered cheap.

You can fix this by using

===
elementStrict :: [a] - [a]
elementStrict = foldr (($!) (:)) []
===

and replacing [1..] by (elementStrict [1..]).

With that, the following program will also work.

===
module Main(main) where

main = print (fibs!!20)

fibs :: [Integer]
fibs = 1 : elementStrict (map snd $ iterate (\(x,y) - (y, x+y)) (1,1))
===

It produces a result with 41798 decimal digits.

Greetings,

Carsten

-- 
Carsten Schultz (2:40, 33:47), FB Mathematik, FU Berlin
http://carsten.fu-mathe-team.de/
PGP/GPG key on the pgp.net key servers, 
fingerprint on my home page.


pgp0.pgp
Description: PGP signature


GHC 6.0.1 for Mac OS X available through darwinports

2003-08-19 Thread Gregory Wright
Hello,

GHC 6.0.1 for Mac OS X is now available through the darwinports system.

Darwinports is similar to the *BSD port system. It downloads and builds 
both
the target and dependencies automatically for your machine.

Note that darwinports is still under development. OS X users who want a 
simple,
reliable installation should use Wolfgang Thaller's GHC disk image. The 
darwinports
version is aimed at people who want to build from source. If you have 
suggestions
for particular customizations, let me know. Darwinports has support for 
'variant'
builds that make customization easy.

For more information on darwinports, and to download the 
infrastructure, see

http://www.opendarwin.org/projects/darwinports/

Best Wishes,

Greg Wright

Gregory Wright
Antiope Associates
18 Clay Street
Fair Haven, New Jersey 07704
USA
[EMAIL PROTECTED]

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Hash functions

2003-08-19 Thread George Russell
Many thanks for Data.HashTable, which I am about to use.  Unfortunately
I seem to need an unseemly hack because the key I want, namely ThreadId's,
don't have a hash function defined, and defining one requires me to muck
around with GHC internal functions.  Could some more hash functions be
provided?
The logical method would be to have

   class HashKey key where
  hash :: key - Int32
and define it for as many types as possible.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


2nd CfP: SNPD'03 Workshop on High-Level Approaches to Parallel and Distributed Computing

2003-08-19 Thread Clemens Grelck
Please apologize in case you receive multiple copies of this information.

==

 2nd CALL FOR PAPERS

 Workshop on 
 High-Level Approaches to Parallel and Distributed Computing

 held in the context of the

 Fourth ACIS International Conference on
 Software Engineering, Artificial Intelligence, 
 Networking, and Parallel/Distributed Computing (SNPD'03)

 October 16th - 18th, 2003

 Luebeck, Germany

 http://www.isp.uni-luebeck.de/snpd03/Workshop/ws02/index.htm

==


Scope and Topics:
==

Today parallel and distributed computing systems are readily available
and provide a continuously improving price/performance ratio. However,
this technological breakthrough in hardware is not accompanied by 
similar progress in software technology. Parallel and distributed
programming is still dominated by low-level techniques such as explicit
message passing. This low level of abstraction makes programming these
systems exceedingly difficult, time-consuming, and error-prone.
Hence, parallel and distributed computing requires new programming models
which liberate programmers from low-level concerns and increase programming
productivity while maintaining reasonable trade-offs between level of 
abstraction and runtime performance.

Topics of interest include, but are not limited to
 - methodologies for high-level parallel programming,
 - parallel programming languages,
 - high-level libraries for parallel computing,
 - compilers and runtime systems for parallel computing,
 - implementation aspects of high-level parallel programming environments,
 - compiler-based optimization and parallelization,
 - experience with high-level parallel programming environments,
 - support for debugging and performance analysis,
 - concurrent array programming,
 - programming concepts for the grid.

This workshop provides a forum for researchers and practitioners 
interested in the design, implementation, and evaluation of 
high-level parallel programming concepts. It aims at creating
some focus within the otherwise broad spectrum of the SNPD'03
conference. The workshop will take place as a special session
during SNPD'03. Participants must register for SNPD'03. There
are no additional fees for attending workshops.



Workshop Chair and Organizer:
==

Clemens Grelck
University of Luebeck
Institute of Software Technology and Programming Languages
Seelandstr. 1A
23569 Luebeck, Germany
E-Mail: [EMAIL PROTECTED]


Papers and Publication:


Original, unpublished papers in English not exceeding 8 pages in 
ACIS double column format are solicited. For detailed formatting
instructions see the SNPD'03 conference web site at

  http://www.isp.uni-luebeck.de/snpd03/index.htm

Please send your papers as PDF documents by electronic mail directly 
to the workshop chair:

  [EMAIL PROTECTED]

Please indicate your paper submission by the subject

  SNPD03 WORKSHOP SUBMISSION

Accepted papers will be published in the conference proceedings with
ISBN. A selection of excellent papers presented at the conference 
including its workshops will be published in a special issue of the
International Journal of Computer and Information Science.


Important Deadlines:
=

Full paper submission due:August, 30th
Notification of acceptance:   September, 10th
Camera-ready papers due:  September, 24th
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: more unsafePerformIO questions (is it safe to use with ReadMode Handles)?

2003-08-19 Thread Simon Marlow
 
 I'm finishing up my Haskell interface to WordNet
 (http://www.cogsci.princeton.edu/~wn/) and have a standard
 unsafePerformIO question :).
 
 Basically, the interface functions by first calling an initialization
 function, 'initializeWordNet :: IO WordNetEnv'.  WordNetEnv is
 essentially just a record of a lot of Handles which we will be reading
 from and doing binary search in.
 
 All the functions which use the WordNetEnv (i.e., every other function
 in the interface) basically do the following:
 
   - take one handle from the WordNetEnv and do binary search 
 in it, read a line.
 
   - use that line to read another line from another of the handles
 
   - parse that last one
 
 of course, therefore, all of these functions have type '... - IO
 something'.
 
 However, one of the rules of thumb for using unsafePerformIO is when
 you can imagine a functional interface doing the same thing.  I can:
 simply read in all the databases in initializeWordNet and then do
 Data.List.lookup on the results.  Does this mean it's safe to wrap all
 these functions in unsafePerformIO?

It sounds like your interface is pure, as long as you don't expect the
contents of any of the databases to change during the run of your
program.  That is, it doesn't matter whether you do all the IO at the
start or lazilly on demand.

If the databases *do* change over time, then there are two
possibilities:

  1. the contents change due to external factors only
  2. the contents change because this program doing the writing

in (1), you can still pretend the interface is pure, by imagining that
all the changes happened earlier.  This works as long as you only read
the external data once.  In (2), you have a truly impure interface, so
using unsafePerformIO would be wrong.

Cheers,
Simon

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


Re: overlapping instances and functional dependencies

2003-08-19 Thread Wolfgang Jeltsch
Hello,

I think, I realized now what my mistake was. The handling of overlapping 
instances comes into play when the compiler has to decide which method 
definition to choose for a specific instance. It is not for choosing one of 
more possible instances.

In my example, C Int (Int,Char,Bool) Int and C Int (Int,Char,Bool) Char where 
both candidates for instances of C. Because they match the pattern of the 
first instance declaration (which is the more general one), both candidates 
actually have to be instances. The handling of overlapping instances only 
states that the compiler has to use the method definitions of the second 
instance declaration for the instance C (Int,Char,Bool) Char.

Am I correct?

Wolfgang


On Monday, 2003-08-18, 00:37, CEST, Wolfgang Jeltsch wrote:
 I wrote on Saturday, 2003-08-09, 01:32, CEST:
  Hello,
 
  I have this code:
  class C a b c | a b - c where
  f :: a - b - c
 
  instance C a b c = C a (x,y,b) c where
  f a (_,_,b) = f a b
 
  instance C a (a,c,b) c where
  f _ (_,c,_) = c
  ghci -fglasgow-exts -fallow-overlapping-instances compiles it without
  complaint but hugs -98 +o says:
  ERROR ClassProblem.hs:7 - Instances are not consistent with
  dependencies
  *** This instance: C a (a,b,c) b
  *** Conflicts with   : C a (b,c,d) e
  *** For class: C a b c
  *** Under dependency : a b - c
  Can anyone tell me what the reason for this is and, maybe, how to avoid
  these problems with Hugs?
 
  Wolfgang

 Hal Daume answered on Saturday, 2003-08-09, 01:53, CEST:
  Suppose somewhere we have an instance:
 
   instance C Int Bool Int
 
  when the first instance decl you have says we also have
 
instance C Int (x,y,Bool) Int
 
  in this case, Int + (x,y,Bool) should uniq. specify Int.
 
  however, we also have:
 
instance C a (a,c,b) c
 
  where, if we let a=Int, b=Bool, c=Char, then we get that
Int + (Int,Char,Bool) should uniq. specify Char.
 
  these two confict because if, in the first case, we instantiate x to Int
  and y to Char, then one says that the third param should be a Bool and
  the other says the third param should be a Char.
 
  (or at least this is my understanding -- someone might correct me)
 
   - Hal

 Hello,

 I wouldn't suppose that there is a conflict in your example. The question
 is for which t there is an instance C Int (Int,Char,Bool) t. There are two
 competing instance declarations:
 (1) instance C a b c = C a (x,y,b) c [...]
 Because in your example there is an instance C Int Bool Int we
 would get the instance C Int (Int,Char,Bool) Int.
 (2) instance C a (a,c,b) c [...]
 This clearly votes for C Int (Int,Char,Bool) Char.
 But the second instance declaration is more specific. In the first one we
 have the pattern arbitrary type - triple type - arbitrary type with no
 further restrictions. In the second one we have the same pattern but with
 the restriction that the first parameter must equal the type of the first
 triple element and the third parameter must equal the type of the second
 triple element. Because of the handling of overlapping instances, the
 compiler should take the second instance declaration and deduce the
 instance C Int (Int,Char,Bool) Char.

 What's wrong with my interpretation?

 Wolfgang

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


Re: more unsafePerformIO questions (is it safe to use with ReadMode Handles)?

2003-08-19 Thread Ganesh Sittampalam
On Tue, 19 Aug 2003 10:27:23 +0100, Simon Marlow [EMAIL PROTECTED]
wrote:

If the databases *do* change over time, then there are two
possibilities:

  1. the contents change due to external factors only
  2. the contents change because this program doing the writing

in (1), you can still pretend the interface is pure, by imagining that
all the changes happened earlier.  This works as long as you only read
the external data once.

Isn't there the possibility of inlining causing a read to happen twice even
if it only appears to happen once?

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


RE: more unsafePerformIO questions (is it safe to use with ReadMode Handles)?

2003-08-19 Thread Simon Marlow
 
 If the databases *do* change over time, then there are two
 possibilities:
 
   1. the contents change due to external factors only
   2. the contents change because this program doing the writing
 
 in (1), you can still pretend the interface is pure, by 
 imagining that
 all the changes happened earlier.  This works as long as you 
 only read
 the external data once.
 
 Isn't there the possibility of inlining causing a read to 
 happen twice even if it only appears to happen once?

In theory that would be a valid transformation, but in practice no
compiler would duplicate arbitrary computations.  GHC certainly doesn't.

Cheers,
Simon

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


Re: more unsafePerformIO questions (is it safe to use with ReadMode Handles)?

2003-08-19 Thread Ganesh Sittampalam
On Tue, 19 Aug 2003 10:52:57 +0100, Simon Marlow [EMAIL PROTECTED]
wrote:

 Isn't there the possibility of inlining causing a read to 
 happen twice even if it only appears to happen once?

In theory that would be a valid transformation, but in practice no
compiler would duplicate arbitrary computations.  GHC certainly doesn't.

I was thinking of a situation like 

let x = unsafePerformIO readFooFromDB in x+x

I see from your Secrets of the GHC inliner paper that x wouldn't be
inlined by GHC, but it seems to me like a serious abuse of the principle of
referential transparency to write programs that _assume_ that.

Cheers,

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


RE: more unsafePerformIO questions (is it safe to use with ReadMode Handles)?

2003-08-19 Thread Simon Marlow
 
  Isn't there the possibility of inlining causing a read to 
  happen twice even if it only appears to happen once?
 
 In theory that would be a valid transformation, but in practice no
 compiler would duplicate arbitrary computations.  GHC 
 certainly doesn't.
 
 I was thinking of a situation like 
 
 let x = unsafePerformIO readFooFromDB in x+x
 
 I see from your Secrets of the GHC inliner paper that x wouldn't be
 inlined by GHC, but it seems to me like a serious abuse of 
 the principle of
 referential transparency to write programs that _assume_ that.

Yes, I agree that one shouldn't rely on the no duplication of work
property.  However, folloing this argument we arrive at the conclusion
that hGetContents is an invalid use of unsafePerformIO.  (which is
something I've been saying for a while now :-).

Cheers,
Simon

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


Re: more unsafePerformIO questions ([...])

2003-08-19 Thread Wolfgang Jeltsch
On Tuesday, 2003-08-19, 13:18, Simon Marlow wrote:
 [...]

 Yes, I agree that one shouldn't rely on the no duplication of work
 property.  However, folloing this argument we arrive at the conclusion that
 hGetContents is an invalid use of unsafePerformIO.  (which is something I've
 been saying for a while now :-).

Can't hGetContents be implemented without unsafePerformIO but with 
unsafeInterleaveIO? Wouldn't this be valid? Am I'm missing something here?

 Cheers,
   Simon

Wolfgang

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


RE: more unsafePerformIO questions ([...])

2003-08-19 Thread Simon Marlow
 
 On Tuesday, 2003-08-19, 13:18, Simon Marlow wrote:
  [...]
 
  Yes, I agree that one shouldn't rely on the no duplication of work
  property.  However, folloing this argument we arrive at the 
 conclusion that
  hGetContents is an invalid use of unsafePerformIO.  (which 
 is something I've
  been saying for a while now :-).
 
 Can't hGetContents be implemented without unsafePerformIO but with 
 unsafeInterleaveIO? Wouldn't this be valid? Am I'm missing 
 something here?

unsafeInterleaveIO = return . unsafePerformIO

Well, almost.  unsafeInterleaveIO should also give you the guarantee
that the IO in its argument can't be performed *before* the
unsafeInterleaveIO is executed, but I don't think this distinction is
important to the present discussion.

Actually I dislike unsafeInterleaveIO even more than unsafePerformIO,
because it has an implicit laziness assumption.  The only purpose of
unsafeInterleaveIO is to delay some IO until it is demanded.  But
Haskell lacks a precise definition of demand, prefering to leave the
evaluation order up to the implementation.  Hence, unsafeInterleaveIO is
left in limbo - it might do something useful, but that depends entirely
on your implementation.  GHC doesn't guarantee much about
unsafeInterleaveIO at all.

Cheers,
Simon

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


Announce: HWordNet - A Haskell Interface to WordNet

2003-08-19 Thread Hal Daume III
Briefly,

  http://www.isi.edu/~hdaume/HWordNet/


HWordNet is a Haskell binding to the WordNet database. You will actually
need to have WordNet installed to use the Haskell interface, but you won't
need any of the source (the Haskell interface is 100% pure Haskell; no
crummy FFI bindings here!). However, it does of course use the WordNet
database files, so you'll need those.

  See http://www.cogsci.princeton.edu/~wn/ for more about WordNet

This interface doesn't cover all of WordNet -- for instance, it doesn't
yet do morphology. This will be available in a release soon. Also, it does
use implicit parameters, so you've got to have GHC or Hugs or some other
compiler that supports those.

 - Hal


--
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: more unsafePerformIO questions (is it safe to use with ReadMode Handles)?

2003-08-19 Thread Andrew J Bromage
G'day all.

On Tue, Aug 19, 2003 at 11:11:23AM +0100, Ganesh Sittampalam wrote:

 I was thinking of a situation like 
 
 let x = unsafePerformIO readFooFromDB in x+x
 
 I see from your Secrets of the GHC inliner paper that x wouldn't be
 inlined by GHC, but it seems to me like a serious abuse of the principle of
 referential transparency to write programs that _assume_ that.

I would have thought that this was the principle of full laziness
(which Haskell doesn't guarantee, but all compilers in practice
support) was more important here.  If the code instead was this:

let x = expensiveComputation foo in x + x

I would certainly hope that expensiveComputation wasn't called twice,
and even though the language doesn't guarantee it, I have already
written code that assumed it.

Cheers,
Andrew Bromage
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


ANNOUNCE: New Chameleon version (03-08)

2003-08-19 Thread Martin Sulzmann

Latest version can be downloaded via
http://www.comp.nus.edu.sg/~sulzmann/chameleon/

You might also want to check out

http://www.comp.nus.edu.sg/~sulzmann/chr/publications.html

- The Chameleon Type Debugger (Tool Demonstration) 
- Interactive Type Debugging in Haskell 

Martin

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


let vs. where [was: Re: more unsafePerformIO questions (is it safe to use with ReadMode Handles)?]

2003-08-19 Thread Jan Scheffczyk
Hi Andrew,

   let x = expensiveComputation foo in x + x

 I would certainly hope that expensiveComputation wasn't called twice,
 and even though the language doesn't guarantee it, I have already
 written code that assumed it.

I always thought that there is a tiny difference between let and where:
Using let expensiveComputation foo might be computed twice (depending on 
the compiler?).
But using:

  x + x
  where x = expensiveComputation foo

should compute the value for x only once.
Therefore, I always try to use where for common subexpressions.

Please correct me if I'm wrong here.

Cheers,
Jan

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


RE: Database interface

2003-08-19 Thread Tim Docker
Tom Pledger writes:

 By the way, how does the  a  in  a - b - IO (b, Bool)  work?
 It looks like it has something to do with the current row.  Does
 doquery have to accommodate any possible substitution for  a ?

I fired this off without thinking about it too much, and looking
at the prelude type signatures for fold. The list being folded over
is implied by the DB query, is accessible through the IO monad.
Hence a parameter is not required. It would really be:

doquery :: Process - String - b - (b - IO (b,Bool)) - IO b

 I don't have a preference, but offer this view of the options:
 
 With an exception, Stop, and return the last b you saw.
 With a boolean,Stop, and return this b.

I think I like the behavior where, when the bool in the tuple
is true, the b in the tuple is immediately returned from the
query. Exceptions would be propagated to the caller of doquery
without modification (but with appropriate cleanups).

One thing that I am unsure about is whether the column value
accessing functions that I specified before

   stringv :: Process - CInt - IO String
   doublev :: Process - CInt - IO Double
   intv:: Process - CInt - IO Int

should return actions in the IO monad as above, or instead should
be in some other DBQuery monad, that trivially extends the IO monad,
but is only valid inside the doquery call. This would have the benefit
of restricting the column access functions to inside a query via the
type system.

I'd also probably use a typeclass to specify a single colv function.
ie:

   class DBCol a where
   colv :: DBQuery a

   instance DBCol String where...
   instance DBCol Double where...

   doquery :: Process - String - b - (b - DBQuery (b,Bool)) - IO b

Any comments?

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


Re: More type design questions

2003-08-19 Thread Konrad Hinsen
On Monday 18 August 2003 22:24, Remi Turk wrote:

 Would this suffice?
...

I guess so - it looks like what Brandon proposed, up to cosmetic differences.

Still, those cosmetic differences give me the chance to ask another question.

 instance Functor Vector where
 fmap f (Vector x y z)
 = Vector (f x) (f y) (f z)

Under what conditions would Haskell programmers make some type an instance of 
Functor? Whenever it could possibly be done (i.e. whenever fmap makes sense)? 
Or just when fmap would be used frequently for some type?

In this case, I can't think of any other use for fmap than defining scalar 
multiplication. There is no other vector operation that applies some 
operation to each element and returns another vector. Would it be considered 
better to define fmap nevertheless, and then use it in scalar 
multiplication, or would one prefer to define the mapping operation into its 
only application?

Konrad.

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


Monads and Maybe

2003-08-19 Thread Konrad Hinsen
I have been following the recent Monad tutorial discussion with interest, 
and even read the tutorial, which is a useful addition to the existing 
Haskell documentation. So useful in fact that it raises a question...

The whole monad mechanism seems to geared towards functions of one argument, 
plus eventually state, that get chained together. How about functions with 
several arguments?

As an example, I'll use the Maybe monad. Suppose I want to write code to 
handle experimental data, in which there might be missing values. I might 
then decide to represent measurements by data of type Maybe Double, with 
missing values represented by Nothing. I could then go on to define 
functions on missing values, which would return Nothing when their argument 
is Nothing, and I could string these functions together via the monad 
mechanism. Fine.  But how would I handle e.g. addition of two such values? 
The result should be Nothing when either of its arguments is Nothing. Is 
there any mechanism to handle that?

Konrad.

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


sequencing data structures

2003-08-19 Thread Martin Norbäck
I want to sequence data structures in an efficient manner, to store them
to files and to send them over the network.

Simply deriving Show and Read is not very good, because it's space
inefficient and read cannot give any output until the whole data
structure is parsed.

So I thought I should store them in some space efficient format.

First problem: how to make them derivable (so that I don't have to write
boilerplate class instances for all my data structures).

I read the derivable type classes paper, but it's not implemented in
ghc (only Unit and :+: and :*: are, which is not enough).

So how to go about it? Using DrIFT? Template Haskell?

Second problem: how should such a format look like?

Ideally, I want to be able to write an infinite data structure (at least
one containing loops). If that is not possible I want to be able to read
as lazily as possible, this means traversing the data structure in
breadth first order, so that a cons form can be reached quickly.

Does anyone have any thoughts/pointers on this subject? It would
surprise me if nobody has had this problem before.

Regards,

Martin

-- 
Martin Norbäck  [EMAIL PROTECTED]  
Kapplandsgatan 40   +46 (0)708 26 33 60
S-414 78  GÖTEBORG  http://www.dtek.chalmers.se/~d95mback/
SWEDEN  OpenPGP ID: 3FA8580B

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


Re: sequencing data structures

2003-08-19 Thread Iavor Diatchki
hello,

there were a lot of discussions on the library mailing list about 
deriving binary, which is related to what you are asking.  i don't think 
that dealt with cyclic datatypes though.   i don't think you can do much 
about that from within haskell, unless you somehow encoded the sharing 
explicitly in the datastructure (by adding node identifiers or something).

bye
iavor


Martin Norbäck wrote:
I want to sequence data structures in an efficient manner, to store them
to files and to send them over the network.
Simply deriving Show and Read is not very good, because it's space
inefficient and read cannot give any output until the whole data
structure is parsed.
So I thought I should store them in some space efficient format.

First problem: how to make them derivable (so that I don't have to write
boilerplate class instances for all my data structures).
I read the derivable type classes paper, but it's not implemented in
ghc (only Unit and :+: and :*: are, which is not enough).
So how to go about it? Using DrIFT? Template Haskell?

Second problem: how should such a format look like?

Ideally, I want to be able to write an infinite data structure (at least
one containing loops). If that is not possible I want to be able to read
as lazily as possible, this means traversing the data structure in
breadth first order, so that a cons form can be reached quickly.
Does anyone have any thoughts/pointers on this subject? It would
surprise me if nobody has had this problem before.
Regards,

	Martin



--
==
| Iavor S. Diatchki, Ph.D. student   |
| Department of Computer Science and Engineering |
| School of OGI at OHSU  |
| http://www.cse.ogi.edu/~diatchki   |
==
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: More type design questions

2003-08-19 Thread Andrew J Bromage
G'day all.

On Tue, Aug 19, 2003 at 12:31:08PM +0200, Konrad Hinsen wrote:

 Under what conditions would Haskell programmers make some type an instance of 
 Functor? Whenever it could possibly be done (i.e. whenever fmap makes sense)? 
 Or just when fmap would be used frequently for some type?

Like anything else in software development, it's a judgement call.

The questions you have to ask might include:

- Does it make sense?
- Is it an appropriate abstraction for this type?
- Would I want to encourage another programmer to use it?
- Do I want to use it myself?
- Would it unnecessarily limit the possible implementations of
  this abstract type?

The last point is particularly important to consider.  A Set-like type,
for example, is mathematically a functor, but any implementation of
fmap will in general change the relative orderings, hash values etc of
member elements.  This means that supporting fmap efficiently might
rule out many interesting implementations of this container.

If in doubt, don't implement it (yet).

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