Re: [Haskell-cafe] Is Haskell a 5GL?

2006-09-30 Thread Ivan Tarasov
I've used Mathematica a lot (and, unfortunately, still using it), and written a program, which uses symbolic computations a lot to deal with simplification of multivariate polynomial systems of inequalities. Now I'm trying to get rid of that Mathematica code and rewrite the program in Haskell because writing and debugging a program in Mathematica which is more complex than doing some simple computations is a mess. 
Nevertheless, Mathematica is a great product, especially if you know how to get what you want from it. IvanOn 9/30/06, Tamas K Papp 
[EMAIL PROTECTED] wrote:On Mon, Sep 25, 2006 at 03:27:32PM +0200, Henning Thielemann wrote:
Hi Henning, Actually, laziness allows me to formulate algorithms that look more like the specification of the problem than the solution. E.g., I can formulate the solution of a differential equation in terms of a power series or time
 series in that way. However I have to put some effort into formulating it in a way that works. E.g. I'm only able to solve such equations if it is possible to express the second derivative in terms of the first and the
 zeroth one. Computer algebra systems are essentially better here.In my experience, most people use CAS interactively: they encounter anintegral or a PDE that's difficult to solve, so they type it into
Mathematica (which frequently cannot solve it either, then you gocrazy, numerical, or both ;-).It is more like a sophisticatedsymbolic calculator with a lot of patterns built in for manipulatingexpressions.
Mathematica has features of a programming language, but most people Iknow are not using those when manipulating formulas, and conversely,when _programming_ in Mathematica (ie writing code and then executing
it do so something repetitive) they rarely do anything symbolic.CAS are great for specific purposes, especially for replacing thosetomes which have solutions of equations/ODEs/PDEs/integrals etc inthem, and some CAS have Algol-style flow control and numerical methods
which you can use for solving numerical problems, but the two arealmost never mixed.Best,Tamas___Haskell-Cafe mailing list
Haskell-Cafe@haskell.orghttp://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: Typeclass vs. Prolog programming

2006-09-30 Thread oleg

I previously wrote:
 The typechecker commits to the instance
 and adds to the current constraints
 TypeCast x Int, Ord Bool, Eq Bool
 The latter two are obviously satisfied and so discharged. The former
 leads to the substitution {x-Int}.

I should have been more precise and said: 
The former _eventually_ leads to the substitution {x-Int}.

Your analysis is right on the mark. That's exactly how I think of
TypeCast.


 This is all very beautiful, but it's a little annoying that the
 cornerstone silver bullet TypeCast has to be defined in a way that
 fools the typechecker into doing the right thing in spite of itself.

One of the drafts of the HList paper, when describing TypeCast,
literally had a phrase about `fooling the typechecker'...

Well, it seems things like TypeCast were not envisioned by the
Founding Fathers. In this respect, the story of C++ templates come to
mind. My feeling is that we're still discovering the capabilities of
the Haskell typechecker and the right abstractions. We should view
TypeCast as an ungainly _encoding_ of a simple abstraction, or just as
a tool for implementing type-level typecase and local improvement
rules. When the right abstraction emerges (and perhaps it already has:
CHR), GHC might implement it directly. Until then, we can use the
encoding...

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


Re: [Haskell-cafe] smallest double eps

2006-09-30 Thread Lennart Augustsson

Hang on, hang on, now I'm getting confused.

First you asked for the smallest (positive) x such that
   1+x /= x
which is around x=4.5e15.
Then Joachim wondered if you wanted
   1+x /= 1
which is around x=2.2e-16.
But not you claim to be looking for the smallest positive number that  
a Double can represent.  Which is a totally different beast.  The  
smallest possible Double depends on if you want to accept  
denormalized numbers or not.  If you don't, then it's about x=4.5e-308.


Now what is the number you are looking for?

-- Lennart

On Sep 29, 2006, at 22:02 , Tamas K Papp wrote:


On Fri, Sep 29, 2006 at 06:53:35PM -0700, Chad Scherrer wrote:


Tamas,

You might want to read Joachim's post more carefully - he's trying to
help you, and I think he makes a good point.


Chad,

If his point is that there is no smallest positive number, then I
think I understand it, thanks.  I should have said that I was looking
for the smallest positive number Double can represent, but thought
that was clear from the context.

If this is not his point, I'd really appreciate an explanation.

Thanks,

Tamas
___
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] irrefutable patterns for existential types / GADTs

2006-09-30 Thread oleg

It seems that irrefutable pattern match with existentials is safe. The
fact that irrefutable pattern match with GADT is unsafe has been
demonstrated back in September 2004.

Let us consider the following regular existential data type

 data TFoo where
Foo :: Show a = a - TFoo
Bar :: Int - TFoo

Despite the 'where' syntax, it is NOT GADT; it is just a regular data
type. We can write

 test_foo vf = case vf of ~(Foo x) - body

Now, if 'x' does not occur in `body', we could have just as well written 
test_foo vf = body
If `x' does occur in body and the scrutinee is not of the form `Foo',
then 'x' is undefined, and so 'body' bottoms out when it demands the
value of 'x'. No surprise, and no concern here.

Let is now consider a GADT

 data GTFoo a where
 GFoo :: GTFoo Int
 GBar :: GTFoo Bool

 test_gfoo :: GTFoo a - a
 test_gfoo vf = case vf of GFoo - (1::Int)


It can be faithfully emulated as follows

 -- the data constructors Em_GFoo and Em_GBar must be hidden!
 data EmulateGTFoo a = Em_GFoo | Em_GBar

 em_gfoo :: EmulateGTFoo Int
 em_gfoo = Em_GFoo
 em_gbar :: EmulateGTFoo Bool
 em_gbar = Em_GBar

The constructors Em_GFoo and Em_GBar should be hidden. The user should
use `smart' constructors em_gfoo and em_gbar, which not only set the
correct type (Int vs Bool) but also produce the witness, viz. Em_GFoo
or Em_GBar.

Now, the test_gfoo function should be written as

 tesd_emulate_gfoo :: EmulateGTFoo a - a 
 tesd_emulate_gfoo vf = case vf of Em_GFoo - unsafeCoerce (1::Int)

So, we test for evidence, Em_GFoo, and if it is presented, we proceed
with unsafeCoerce, which generalizes Int to the desired type 'a'. We
know this generalization is safe because the evidence Em_GFoo told us
that 'a' was really Int. The similarity with Dynamics is uncanny.

Now, had we used an irrefutable match instead, we would have
proceeded with unsafeCoerce without checking for the evidence. 

The following code, written back in Sep 13, 2004, shows that the above
is not an empty concern. The code did indeed typecheck, with the
version of GHC (tidt-branch CVS branch) that existed at that
time. Running the code produced the result one'd expect when reading
an Int as a Bool. I think the code below was the reason GHC prohibited
irrefutable GADT pattern matching since.


 {-# OPTIONS -fglasgow-exts #-}

 module Main where

 import Data.IORef

 data T a where
   Li:: Int - T Int
   Lb:: Bool - T Bool
   La:: a - T a

 writeInt:: T a - IORef a - IO ()
 writeInt v ref = case v of
  ~(Li x) - writeIORef ref (1::Int)

 readBool:: T a - IORef a - IO ()
 readBool v ref = case v of
  ~(Lb x) - 
  readIORef ref = (print . not)

 tt::T a - IO ()
 tt v = case v of
  ~(Li x) -  print OK

 main = do
   tt (La undefined)
   ref - newIORef undefined
   writeInt (La undefined) ref
   readBool (La undefined) ref
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is Haskell a 5GL?

2006-09-30 Thread jerzy . karczmarczuk

Tamas K Papp writes:


Henning Thielemann wrote:



Actually, laziness allows me to formulate algorithms that look more like
the specification of the problem than the solution. E.g., I can formulate
the solution of a differential equation in terms of a power series or time
series in that way. However I have to put some effort into formulating it
in a way that works. E.g. I'm only able to solve such equations if it is
possible to express the second derivative in terms of the first and the
zeroth one. Computer algebra systems are essentially better here.


In my experience, most people use CAS interactively: they encounter an
integral or a PDE that's difficult to solve, so they type it into
Mathematica (which frequently cannot solve it either, then you go
crazy, numerical, or both ;-).  It is more like a sophisticated
symbolic calculator with a lot of patterns built in for manipulating
expressions.


I should have reacted earlier...
Please don't exaggerate with *opposing* CAS and Haskell, Prolog, or other
*universal* languages. CAS such as Maple, Mupad, and also Mathematica in
a sense are also universal, but they simply have

* enormous libraries permitting to deal with symbolic expressions ;
* Pattern matching/rewriting contraptions useful to manipulate deeply
intricate structures.

All this CAN BE DONE in Haskell as well, but reinventing the wheel is
rarely interesting (sometimes is, though) (*).

Still CAS are no magic, and - getting back to Henning's example: No CAS
will give you the power expansion of a solution of a differential equation
if you can't algorithmize the needed recurrencies. But if you can, then
you can do it in a numerical setting using Haskell or something else.
Haskell allows you to apply laziness in a perverse way as well, for
example solving - as a power series - a *singular* equation (Bessel), where
you define the first derivative through the function and its second
derivative, although at first glance this seems mad. But look here,
a quite old stuff... : Theor. Comp. Sci. 187,(1997), pp. 203--219.
on-line :
http://users.info.unicaen.fr/~karczma/arpap/lazysem.pdf
page 4...

Jerzy Karczmarczuk

===

(*) A reference for your culture:
Jorge Luis Borges, Pierre Ménard, the Author of Don Quixote. It is a
story about a person who WROTE (not: copied) a book, exactly, letter by
letter, identical to the book of Cervantes. It was identical, but having
been written another time/place, and addressed to different readers, it
had a different *deep meaning*, it was a different novel. Or was it?...

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


[Haskell-cafe] Re: irrefutable patterns for existential types / GADTs

2006-09-30 Thread apfelmus
 {-# OPTIONS -fglasgow-exts #-}

 module Main where

 import Data.IORef

 data T a where
   Li:: Int - T Int
   Lb:: Bool - T Bool
   La:: a - T a

 writeInt:: T a - IORef a - IO ()
 writeInt v ref = case v of
 ~(Li x) - writeIORef ref (1::Int)

 readBool:: T a - IORef a - IO ()
 readBool v ref = case v of
 ~(Lb x) - 
 readIORef ref = (print . not)

 tt::T a - IO ()
 tt v = case v of
  ~(Li x) -  print OK

 main = do
  tt (La undefined)
  ref - newIORef undefined
  writeInt (La undefined) ref
  readBool (La undefined) ref

This code is more intricate than

  data Eq a b where Refl :: Eq a a

  coerce :: Eq a b - a - b
  coerce ~Refl x = x

but I think it amounts to exactly the same thing: ref and x are forced
to a particular type witnessed by the GADT.

But I think that something still can be squeezed out, strictness is not
absolutely necessary (see upcoming mail on this thread).

Regards,
apfelmus

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


[Haskell-cafe] Re: irrefutable patterns for existential types / GADTs

2006-09-30 Thread apfelmus
Here is a formulation of what exactly I require from irrefutable pattern
matches for GADTs.

The problem arouse from the Optimization problem thread. In short,
here is a GADT-using, type safe version of Bertram's solution (without
balancing)

  -- a binary search tree with witness about its shape
 data Map s k a where
 Leaf :: Map () k a
 Node :: k - a - Map s k a - Map t k a - Map (s,t) k a
 
 empty :: Map () k a
 empty = Leaf
 
 member :: Ord k = k - Map s k a - Bool
 member _ Leaf= False
 member k (Node k' _ l r) = case compare k k' of
 LT - member k l
 EQ - True
 GT - member k r
 
 -- a wrapper for an existential type
 data Undoer s k a where
 Undoer :: (Map t k a) - (Map t k a - (a,Map s k a)) - Undoer s k a
 
 -- insert key element blueprint map (blueprint, result, map)
 insert :: Ord k = k - a - Map s k a - Undoer s k a
 insert k a Leaf =
Undoer (Node k a Leaf Leaf) (\(Node k a Leaf Leaf) - (a,Leaf))
 insert k a (Node k' b (l :: Map l k a) (r :: Map r k a) :: Map s k a)
 = case compare k k' of
 LT - case insert k a l of
 Undoer (m :: Map t k a) f -
 Undoer (Node k' b m r :: Map (t,r) k a)
 (\(Node k' b' m' r' :: Map (t,r) k a) -
 let (a,l') = f m' in
   (a,Node k' b' l' r' :: Map s k a))
 EQ - error inserting existing element
 GT - case insert k a r of
 Undoer (m :: Map t k a) f -
 Undoer (Node k' b l m :: Map (l,t) k a)
 (\(Node k' b' l' m' :: Map (l,t) k a) -
 let (a,r') = f m' in
   (a,Node k' b' l' r' :: Map s k a))
 

 update :: Ord k = k - (a - a) - Map s k a - Map s k a
 -- the culprit, to be defined later
 
 splitSeq :: Ord a = [(a,b)] - [(a,[b])]
 splitSeq = fst . splitSeq' empty
 
 splitSeq' :: Ord a = Map s a [b] - [(a,b)] - ([(a,[b])], Map s a [b])
 splitSeq' bp [] = ([], bp)
 splitSeq' bp ((a,b):xs) = case member a bp of
 True - let (l, m)  = splitSeq' bp xs in (l, update a (b:) m)
 _- case insert a [] bp of
 Undoer bp' f - let
 (rs,m)  = splitSeq' bp' xs
 (bs,m') = f m
 in ((a, b:bs) : rs, m')

To make this work in a lazy manner (it becomes an online algorithm then
and works for infinite lists), I'd like to have

 update :: Ord k = k - (a - a) - Map s k a - Map s k a
 update k f ~(Node k' a l r) = case compare k k' of
 LT - Node k' a (update k f l) r
 EQ - Node k' (f a) l r
 GT - Node k' a l (update k f r)

reasoning that the Node constructor should be output before one inspects
the incoming ~Node. I thought that (l, m)  = splitSeq' bp xs witnesses
that  bp  and  m  have the same Shape  s, but this is the point where
the not-normalizing argument throws in: the type of splitSeq' claims to
be a proof that  bp  and  m  have the same  s  but who knows whether it
really terminates?


So, I'm opting for a different update which is more along the lines of
Bertram's original:

 update :: Ord k = k - (a - a)
   - Map s k a - Map t k a - Map s k a
 update k f (Node k' _ l' r') ~(Node _ a l r) = case compare k k' of
 LT - Node k' a (update k f l' l) r
 EQ - Node k' (f a) l r
 GT - Node k' a l (update k f r)

The blueprint gives immediate witness that splitSeq' preserves shape, so
this update should be fine.



To summarize, the main problem is to get a lazy/online algorithm (the
problem here falls into the more haste, less speed category) while
staying more type safe.
@Conor: how does this issue look like in Epigram?

Regards,
apfelmus

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


[Haskell-cafe] Re: irrefutable patterns for existential types / GADTs

2006-09-30 Thread apfelmus
 But that makes it refutable! For the above, either
 
  coerce _|_ x === x
 
 or the notation is being abused.

Making a pattern irrefutable does not mean that the function in question
will become lazy:

  fromJust (~Just x) = x

  fromJust _|_ === _|_

The point with coerce is that it looks very much like being lazy in its
first argument but in fact it is not.

 The trouble is that GADT pattern matching has an impact on types, as
 well as being a selector-destructor mechanism, and for the impact on
 types to be safe, the match must be strict.

 I think it's the extra power of GADTs to tell you more about type
 variables already in play which does the damage.

But I think that something still can be squeezed out, strictness is not
absolutely necessary. I thought something along the lines of

  f :: Eq a b - a - Maybe b
  f ~Refl x = Just x

with

  f _|_ x  === Just _|_

The point is one can always output the constructor Just, it does not
inspect the type of x.

Now, I don't think anymore that this is feasible as the type of (Just x)
still depends on the type of x (even if the constructor Just does not
mention it). Nevertheless, I still want to remove strictness, see my
next mail in this thread.

 For existentials, I'm not sure, but it seems to me that there's not such
 a serious issue. Isn't the only way you can use the type which allegedly
 exists to project out some dictionary/other data which is packed inside
 the existential? Won't this projection will cause a nice safe _|_
 instead of a nasty unsafe segfault?

I agree. The only practical problem I can imagine is that GHC internally
treats existentials as GADTs.

Regards,
apfelmus

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


Re: [Haskell-cafe] smallest double eps

2006-09-30 Thread Tamas K Papp
On Sat, Sep 30, 2006 at 04:19:50AM -0400, Lennart Augustsson wrote:
 Hang on, hang on, now I'm getting confused.
 
 First you asked for the smallest (positive) x such that
1+x /= x
 which is around x=4.5e15.
 Then Joachim wondered if you wanted
1+x /= 1
 which is around x=2.2e-16.

Oops, sorry, there was a typo in my original post.  I was looking for
the latter.

Thanks for the help,

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


Re: [Haskell-cafe] Re: irrefutable patterns for existential types / GADTs

2006-09-30 Thread Conor McBride

Hi

[EMAIL PROTECTED] wrote:

To summarize, the main problem is to get a lazy/online algorithm (the
problem here falls into the more haste, less speed category) while
staying more type safe.
@Conor: how does this issue look like in Epigram?
  


Thanks for asking!

In the current Epigram prototype editor/checker, nothing clever happens.
Apart from anything else, typechecking relies on /partial/ evaluation,
so we can't presume that the only normal forms in a datatype are made
with constructors: they might be expressions which have got stuck.

However, Edwin Brady's prototype compiler delivers code for
run-time-only usage, and here we begin to get paid for working in a
total (once suitably stratified) language. It isn't necessary to perform
constructor discrimination when it's statically known that exactly one
constructor is possible, so those patterns can always be made
irrefutable, with matching replaced by projection. It's not yet obvious
whether this is always, never, predictably sometimes, or unpredictably
sometimes a good idea. However, we'd certainly be able to support an
explicit notation for irrefutable patterns, guaranteed to match whenever
the named subobjects were needed.

So we don't just give that coerce example an irrefutable pattern, we can
erase all run-time trace of equality evidence, and indeed any other data
whose value is completely determined by the indices of its type. If you
don't need to discriminate on it, you don't need to look at it, so you
don't need to keep it.

Even though type-vs-value distinction no longer aligns with the
static-vs-dynamic distinction, you don't get any less run-time
type-erasure. You should actually get more run-time value-erasure!

Online algorithms do look like a good place to try to get some leverage
from this, but we haven't really been in a position to experiment so
far. I'm sure that will change.

All the best

Conor



This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

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


Re: [Haskell-cafe] Re: irrefutable patterns for existential types / GADTs

2006-09-30 Thread Jim Apple

On 9/30/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

  data Eq a b where Refl :: Eq a a

  coerce :: Eq a b - a - b
  coerce ~Refl x = x


But this works well with Leibniz-style equality (
http://homepage.mac.com/pasalic/p2/papers/thesis.pdf ), because the
Equality proof/term is actually used:

data Equal a b = Equal (forall f . f a - f b)
newtype Id x = Id { unId :: x}
coerce :: Equal a b - a - b
coerce ~(Equal f) x = unId (f (Id x))

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


[Haskell-cafe] cutting long strings into lines

2006-09-30 Thread Andrea Rossato
Hello!

I've been trying for quite some time to find an elegant solution to
cut long strings into lines, but the only solution I was able to come
up is the following piece of ugly code.

Is there a library function for that? What kind of approach would you
suggest?

Thanks for your kind attention.

Andrea

Here's the code:

-- does the actual job
wrapString str =  foldr addNL  $ rmFirstSpace $ concat $ splitS (getIndx $ 
indx str) str

-- gets the indexes of the spaces within a string 
indx = findIndices (\x - if x == ' ' then True else False)

-- gets the indexes of where to split the string into lines: lines
-- must be between 60 and 75 char long
getIndx :: [Int] - [Int]
getIndx = takeFirst . checkBound . (delete 0) . nub . map (\x - if  x  60   
x `rem` 60 = 0  x `rem` 70 = 10  then x else 0)

-- groups indexes when their distance is too short
checkBound = groupBy (\x y - if y - x  10 then True else False)

-- takes the first index of a group of indexes
takeFirst = map (\(x:xs) - x)

-- split a string given a list of indexes
splitS _ [] = []
splitS (x:xs) (ls) = [take x ls] : splitS (map (\i - i - x) xs) (drop x ls)
splitS _ ls = [ls]:[]

-- remove the first space from the begging of a string in a list of strings 
rmFirstSpace = map (\(x:xs) - if x == ' ' then xs else x:xs) 

-- used by foldr to fold the list of substrings 
addNL s s1 = s ++ \n ++ s1


try with putStrLn $ wrapString longString
where: 
longString = The Haskell XML Toolbox (HXT) is a collection of tools for 
processing XML with Haskell. The core component of the Haskell XML Toolbox is a 
domain specific language, consisting of a set of combinators, for processing 
XML trees in a simple and elegant way. The combinator library is based on the 
concept of arrows. The main component is a validating and namespace aware 
XML-Parser that supports almost fully the XML 1.0 Standard. Extensions are a 
validator for RelaxNG and an XPath evaluator.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] smallest double eps

2006-09-30 Thread Chad Scherrer


Hang on, hang on, now I'm getting confused.

First you asked for the smallest (positive) x such that
1+x /= x
which is around x=4.5e15.
Then Joachim wondered if you wanted
1+x /= 1
which is around x=2.2e-16.
But not you claim to be looking for the smallest positive number that
a Double can represent.  Which is a totally different beast.  The
smallest possible Double depends on if you want to accept
denormalized numbers or not.  If you don't, then it's about x=4.5e-308.

Now what is the number you are looking for?

-- Lennart



This is the point I was confused about also. Joachim seemed to be
correcting what might have been a misstatement of the problem.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is Haskell a 5GL?

2006-09-30 Thread Andrae Muys


On 30/09/2006, at 6:15 AM, Nicolas Frisby wrote:

Software engineering is as of yet misnamed. A professional engineer's
design work should never include figuring out why the first attempt
exploded/collapsed/failed--professionals in mature engineering fields
only debug catastrophes.


That is only the case when engineers are performing pure  
development.  When they are involved in research, engineers first  
attempts routinely explode/collapse/fail. Building a house, bridge,  
refinery, family car, etc, stopped being research a long time ago.   
However F1 racing cars, and interplanetary autonomous vehicles are.   
Software Engineering is so new a discipline that we still don't know  
how to render any but the most trivial of problems 'pure design'.



My intended takeaway is that design in software engineering does not
yet compare to design in the mature engineering fields. In my
engineering-centric opinion, the goal of computer science is to enrich
the design principles of software engineering so that it does compare.


I couldn't agree more.  So I'm going to quote the passage from Robert  
Dockins that you objected to.


On 29/09/06, Robert Dockins [EMAIL PROTECTED] wrote:
In a similar way, if a someone refuses or is unable to learn the  
mathematical foundations of computation, I don't think I really  
want him programming any systems that I'm going to be relying on.   
He don't need to be an expert in category theory, but if  
programmers aren't learning the skills they need to understand the  
basics and mathematical notation of PL theory, then something is  
very, very wrong.  (Not to beat you over the head with my point,  
but what I'm saying is that programmers really ought to know this  
stuff and the fact that most do not is a terrible state of affairs).


Of course we will have hobbyist programmers, in much the same way we  
have home handymen or backyard mechanics.  However anyone claiming to  
be a professional programmer has to deal with everything they do not  
being pure design, but containing a non-trivial element of research.   
For that reason I have to agree with Robert.  I too am very concerned  
at the number of programmers writing code that I rely on who don't  
have a basic understanding of the mathematical foundations of what  
they do.


Andrae

--
Andrae Muys
[EMAIL PROTECTED]
Principal Mulgara Consultant
Netymon Pty Ltd


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


Re: [Haskell-cafe] cutting long strings into lines

2006-09-30 Thread Mark T.B. Carroll
I've been doing it as the enclosed. I wrote it a while ago, though, and
haven't really looked too hard at it since.

-- Mark
module WordWrap (wrap) where
import Data.Maybe

options :: String - [(String, String)]

options [] = [(, )]

options (x:xs) =
let rest = map (\(ys, zs) - (x:ys, zs)) (options xs)
 in if x == ' ' then (, xs) : rest else rest

bestSplit :: Int - String - (String, String)

bestSplit width string =
last (head wraps : takeWhile ((= width) . length . fst) (options string))

wrap :: Int - String - [String]

wrap _  = []

wrap width string =
let (x, ys) = bestSplit width string
 in x : wrap width ys
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] smallest double eps

2006-09-30 Thread Brian Hulley

Lennart Augustsson wrote:

Hang on, hang on, now I'm getting confused.

First you asked for the smallest (positive) x such that
   1+x /= x
which is around x=4.5e15.


1 + 0 /= 0

0 is smaller than 4.5e15

So I don't understand this at all...

Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

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


Re: [Haskell-cafe] smallest double eps

2006-09-30 Thread Thomas Davie


On 30 Sep 2006, at 17:19, Brian Hulley wrote:


Lennart Augustsson wrote:

Hang on, hang on, now I'm getting confused.
First you asked for the smallest (positive) x such that
   1+x /= x
which is around x=4.5e15.


1 + 0 /= 0

0 is smaller than 4.5e15

So I don't understand this at all...


But then 0 isn't positive.

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


[Haskell-cafe] Re: Greetings

2006-09-30 Thread Paul Johnson

I've done some stuff with maybe 50k rows at a time.  A few bits and pieces:

1: I've used HSQL 
(http://sourceforge.net/project/showfiles.php?group_id=65248) to talk to 
ODBC databases.  Works fine, but possibly a bit slowly.  I'm not sure 
where the delay is: it might just be the network I was running it over.  
One gotcha: the field function takes a field name, but its not random 
access.  Access the fields in query order or it crashes.


2: For large data sets laziness is your friend.  When reading files 
getContents presents an entire file as a list, but its really 
evaluated lazily.  This is implemented using unsafeInterleaveIO.  I've 
never used this, but in theory you should be able to set up a query that 
returns the entire database as a list and then step through it using 
lazy evaluation in the same way.


3: You don't say whether these algorithms are just row-by-row algorithms 
or whether there is something more sophisticated going on.  Either way, 
try to make things into lists and then apply map, fold and filter 
operations.  Its much more declarative and high level when you do it 
that way.


Let us know how you get on.

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


Re: [Haskell-cafe] smallest double eps

2006-09-30 Thread Brian Hulley

Thomas Davie wrote:

On 30 Sep 2006, at 17:19, Brian Hulley wrote:


Lennart Augustsson wrote:

Hang on, hang on, now I'm getting confused.
First you asked for the smallest (positive) x such that
   1+x /= x
which is around x=4.5e15.


1 + 0 /= 0

0 is smaller than 4.5e15

So I don't understand this at all...


But then 0 isn't positive.


Why not?
In any case every positive number nust satisfy the above inequation so what 
about 0.1, which is certainly smaller than 4500?


Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] cutting long strings into lines

2006-09-30 Thread Matthias Fischmann

On Sat, Sep 30, 2006 at 11:54:19AM -0400, Mark T.B. Carroll wrote:
 module WordWrap (wrap) where
 import Data.Maybe
 
 options :: String - [(String, String)]
 
 options [] = [(, )]
 
 options (x:xs) =
 let rest = map (\(ys, zs) - (x:ys, zs)) (options xs)
  in if x == ' ' then (, xs) : rest else rest
 
 bestSplit :: Int - String - (String, String)
 
 bestSplit width string =
 last (head wraps : takeWhile ((= width) . length . fst) (options string))

works better if you just skip the head wraps part.  (and now i am
curious: what was it supposed to mean?  how did it get there?)

 wrap :: Int - String - [String]
 
 wrap _  = []
 
 wrap width string =
 let (x, ys) = bestSplit width string
  in x : wrap width ys


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


Re: [Haskell-cafe] cutting long strings into lines

2006-09-30 Thread Bulat Ziganshin
Hello Andrea,

Saturday, September 30, 2006, 7:02:34 PM, you wrote:

 -- gets the indexes of the spaces within a string
 indx = findIndices (\x - if x == ' ' then True else False)

indx = findIndices (==' ')

 -- takes the first index of a group of indexes
 takeFirst = map (\(x:xs) - x)

takeFirst = map head

 -- split a string given a list of indexes
 splitS _ [] = []
 splitS (x:xs) (ls) = [take x ls] : splitS (map (\i - i - x) xs) (drop x ls)
 splitS _ ls = [ls]:[]

 -- remove the first space from the begging of a string in a list of strings
 rmFirstSpace = map (\(x:xs) - if x == ' ' then xs else x:xs)

i would prefer to use map rmFirstSpace where
rmFirstSpace (' ':xs) = xs
rmFirstSpace xs = xs

 -- used by foldr to fold the list of substrings 
 addNL s s1 = s ++ \n ++ s1

foldrl addNl == unlines ?


 try with putStrLn $ wrapString longString
 where: 
 longString = The Haskell XML Toolbox (HXT) is a collection of
 tools for processing XML with Haskell. The core component of the
 Haskell XML Toolbox is a domain specific language, consisting of a
 set of combinators, for processing XML trees in a simple and elegant
 way. The combinator library is based on the concept of arrows. The
 main component is a validating and namespace aware XML-Parser that
 supports almost fully the XML 1.0 Standard. Extensions are a
 validator for RelaxNG and an XPath evaluator.

i think that your algorithm is too complex. standard algorithm, imho,
is to find last space before 80 (or 75) chars margin, split here and
then repeat this procedure again. so, one line split may look like

splitAt . last . filter (80) . findIndices (==' ')

and then you need to define function which repeats this operation on
the rest of list. or, slightky different solution:

-- |this function splits the list xs into parts whose length defined
-- by call to function len_f on the rest of list
splitByLen len_f [] = []
splitByLen len_f xs = y : splitByLen len_f ys
   where (y,ys) = splitAt (len_f xs) xs

-- |this function finds last space in String within 80-char boundary
len_f = last . filter (80) . findIndices (==' ')

so, splitByLen len_f should give you that you need, you need only to
add checks for some additional conditions (first word in line is more
than 80 bytes long, it is a last line) and removing of the extra space
on each line

btw, are you seen http://haskell.org/haskellwiki/Simple_unix_tools ?



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] cutting long strings into lines

2006-09-30 Thread Matthias Fischmann

On Sat, Sep 30, 2006 at 04:36:02PM +0100, Neil Mitchell wrote:
 (if you can't be bothered to do that, the answer is lines ;)

although this wasn't the original problem, i like it, too :).  but now
i am stuck in finding an optimal implementation for lines.  the
following implementation is slightly slower than the built-in
function, and i suspect this to stem from the occurrance of reverse
for each line:

cut1 :: String - [String]
cut1 = f 
where
f x  = [reverse x]
f x ('\n':xs)  = reverse x : f  xs
f x (c:xs) = f (c:x) xs

i vaguely remember having seen a CPS trick here before, but all i can
come up with is the yet a little slower

cut2 :: String - [String]
cut2 = f id
where
f k  = [k ]
f k ('\n':xs)  = k  : f id xs
f k (c:xs) = f k' xs  where k' cs = k (c:cs)

also, i think both implementations are line-strict, that is, each line
is fully evaluated once touched in the first character.

is there a similar implementation, with CPS or not, that is lazy in
the lines and more efficient?


thanks,
matthias


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


Re: [Haskell-cafe] cutting long strings into lines

2006-09-30 Thread Andrea Rossato
On Sat, Sep 30, 2006 at 08:56:24PM +0400, Bulat Ziganshin wrote:
 i think that your algorithm is too complex. standard algorithm, imho,
 is to find last space before 80 (or 75) chars margin, split here and
 then repeat this procedure again. so, one line split may look like
 
 splitAt . last . filter (80) . findIndices (==' ')
...

Thank you very much for your analysis. I find it extremely helpful. 


 btw, are you seen http://haskell.org/haskellwiki/Simple_unix_tools ?

I did not! But I'm studying this page right now. Thanks for mentioning it.

Once again, thank you!
Andrea
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] cant get trivial c2hs to work

2006-09-30 Thread Anatoly Yakovenko

I am trying to figure out how to use c2hs, so I wrote a wrapper for
asin from math.h:
$ cat ASin.chs
module MySin (mysin)

import C2HS

#include math.h

asin::Double - Double
asin xx =
  {#call fun asin#} xx

and this is my main:
$ cat Main.hs
module Main where

import ASin

main = do
  putStrLn $ show $ asin 0.5

`c2hs ASin.chs` generates this:

$ cat ASin.hs
-- GENERATED by C-Haskell Compiler, version 0.14.5 Travelling
Lightly, 12 Dec 2005 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 ASin.chs #-}module MySin (mysin)

import C2HS


asin::Double - Double
asin xx =
  asin xx



foreign import ccall safe ASin.h asin
 asin :: (CDouble - CDouble)


but, when i try to build the wone thing, i get an error that i dont understand:

$ ghc -v --make -fffi Main.hs
Glasgow Haskell Compiler, Version 6.4.2, for Haskell 98, compiled by
GHC version 6.4.2
Using package config file: /usr/lib/ghc-6.4.2/package.conf
Hsc static flags: -static
*** Chasing dependencies:
Chasing modules from: Main.hs
*** Deleting temp files
Deleting:

ASin.chs:2:0: parse error on input `import'


So, what am i missing?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] smallest double eps

2006-09-30 Thread Bryan Burgers

 Hang on, hang on, now I'm getting confused.
 First you asked for the smallest (positive) x such that
1+x /= x
 which is around x=4.5e15.

 1 + 0 /= 0

 0 is smaller than 4.5e15

 So I don't understand this at all...

 But then 0 isn't positive.

Why not?
In any case every positive number nust satisfy the above inequation so what
about 0.1, which is certainly smaller than 4500?


In math, every positive number must satisfy the above inequation, that
is true. But as Chad said, the smallest number in Haskell (at least
according to my GHC, it could be different with different processors,
right?) that satisfies the equation is 2.2e-16.


1 + 2.2e-16 /= 1

True

1 + 2.2e-17 /= 1

False

This is because the Double type only holds so much precision. After
getting small enough, the type just can't hold any more precision, and
the value is essentially 0.


last $ takeWhile (\x - 1 + x /= 1) (iterate (/2) 1)

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


[Haskell-cafe] Re: cant get trivial c2hs to work

2006-09-30 Thread Anatoly Yakovenko

doh, i was just missing where after module... in my .chs file, and
some other syntax errors...

On 9/30/06, Anatoly Yakovenko [EMAIL PROTECTED] wrote:

I am trying to figure out how to use c2hs, so I wrote a wrapper for
asin from math.h:
$ cat ASin.chs
module MySin (mysin)

import C2HS

#include math.h

asin::Double - Double
asin xx =
   {#call fun asin#} xx

and this is my main:
$ cat Main.hs
module Main where

import ASin

main = do
   putStrLn $ show $ asin 0.5

`c2hs ASin.chs` generates this:

$ cat ASin.hs
-- GENERATED by C-Haskell Compiler, version 0.14.5 Travelling
Lightly, 12 Dec 2005 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 ASin.chs #-}module MySin (mysin)

import C2HS


asin::Double - Double
asin xx =
   asin xx



foreign import ccall safe ASin.h asin
  asin :: (CDouble - CDouble)


but, when i try to build the wone thing, i get an error that i dont understand:

$ ghc -v --make -fffi Main.hs
Glasgow Haskell Compiler, Version 6.4.2, for Haskell 98, compiled by
GHC version 6.4.2
Using package config file: /usr/lib/ghc-6.4.2/package.conf
Hsc static flags: -static
*** Chasing dependencies:
Chasing modules from: Main.hs
*** Deleting temp files
Deleting:

ASin.chs:2:0: parse error on input `import'


So, what am i missing?


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


Re: [Haskell-cafe] cutting long strings into lines

2006-09-30 Thread Andrea Rossato
On Sat, Sep 30, 2006 at 08:56:24PM +0400, Bulat Ziganshin wrote:
 splitByLen len_f [] = []
 splitByLen len_f xs = y : splitByLen len_f ys
where (y,ys) = splitAt (len_f xs) xs
...
 so, splitByLen len_f should give you that you need, you need only to
 add checks for some additional conditions (first word in line is more
 than 80 bytes long, it is a last line) and removing of the extra space
 on each line

I came up with this solution that seem to be fine, to me. I does the
checking of those additional conditions:

findSplitP at = last . filter (at) . findIndices (==' ')
where last [] = at
  last [x] = x
  last (_:xs) = last xs

wrapLS at [] = []
wrapLS at s = take ln s ++ \n ++ rest 
where ln = findSplitP at s
  remain = drop ln s
  rest = if length remain  at 
 then wrapLS at (tail remain) 
 else tail remain

then you can use lines/unlines to split it.

Thanks for your help.
Best regards,
Andrea
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] cutting long strings into lines

2006-09-30 Thread Udo Stenzel
Matthias Fischmann wrote:
 although this wasn't the original problem, i like it, too :).  but now
 i am stuck in finding an optimal implementation for lines.

Isn't the obvious one good enough?

lines [] = []
lines s = go s
  where
go [] = [[]]
go ('\n':s) = [] : lines s
go (c:s) = let (l:ls) = go s in (c:l):ls


Udo.
-- 
Money can't buy friends, but it can get you a better class of enemy.
-- Spike Milligan


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


Re: [Haskell-cafe] cutting long strings into lines

2006-09-30 Thread Matthias Fischmann

On Sat, Sep 30, 2006 at 08:51:40PM +0200, Udo Stenzel wrote:
 To: Matthias Fischmann [EMAIL PROTECTED]
 Cc: haskell-cafe@haskell.org
 From: Udo Stenzel [EMAIL PROTECTED]
 Date: Sat, 30 Sep 2006 20:51:40 +0200
 Subject: Re: [Haskell-cafe] cutting long strings into lines
 
 Matthias Fischmann wrote:
  although this wasn't the original problem, i like it, too :).  but now
  i am stuck in finding an optimal implementation for lines.
 
 Isn't the obvious one good enough?
 
 lines [] = []
 lines s = go s
   where
 go [] = [[]]
 go ('\n':s) = [] : lines s
 go (c:s) = let (l:ls) = go s in (c:l):ls

thanks.  good enough, yes.  just not obvious to me...  (-:
matthias


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


Re: [Haskell-cafe] smallest double eps

2006-09-30 Thread Brandon Moore

Bryan Burgers wrote:

 Hang on, hang on, now I'm getting confused.
 First you asked for the smallest (positive) x such that
1+x /= x
 which is around x=4.5e15.

 1 + 0 /= 0

 0 is smaller than 4.5e15

 So I don't understand this at all...

 But then 0 isn't positive.

Why not?
In any case every positive number nust satisfy the above inequation 
so what

about 0.1, which is certainly smaller than 4500?

People are confusing equality and inequality -
the nontrivial thing here is to find the smallest positive x
that satisfies the equation 1 + x == x.

In math, every positive number must satisfy the above inequation, that
is true. But as Chad said, the smallest number in Haskell (at least
according to my GHC, it could be different with different processors,
right?) that satisfies the equation is 2.2e-16.

And you've changed the subject - the stuff above was talking about
x + 1 /= x, you're demonstrating solutions to a different problem, 
finding the smallest

x such that 1 + x == 1. That's the number often called epsilon.

1 + 2.2e-16 /= 1

True

1 + 2.2e-17 /= 1

False

Let's stop confusing ourselves about this.

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


Re: [Haskell-cafe] smallest double eps

2006-09-30 Thread Victor Bandur
 Forwarded Message 
From: Victor Bandur [EMAIL PROTECTED]
Reply-To: [EMAIL PROTECTED]
To: Brandon Moore [EMAIL PROTECTED]
Subject: Re: [Haskell-cafe] smallest double eps
Date: Sat, 30 Sep 2006 20:17:05 -0400

Hi all,

I'm new to this mailing list, so my response may be a little out of
place, but I think either what's being asked is what is the smallest x
such that 1 + x /= 1 (machine epsilon,) or the largest such that 1+x /=
x.  The bounds seem to be confused.

Victor

On Sat, 2006-30-09 at 16:10 -0700, Brandon Moore wrote:
 Bryan Burgers wrote:
   Hang on, hang on, now I'm getting confused.
   First you asked for the smallest (positive) x such that
  1+x /= x
   which is around x=4.5e15.
  
   1 + 0 /= 0
  
   0 is smaller than 4.5e15
  
   So I don't understand this at all...
  
   But then 0 isn't positive.
 
  Why not?
  In any case every positive number nust satisfy the above inequation 
  so what
  about 0.1, which is certainly smaller than 4500?
 People are confusing equality and inequality -
 the nontrivial thing here is to find the smallest positive x
 that satisfies the equation 1 + x == x.
  In math, every positive number must satisfy the above inequation, that
  is true. But as Chad said, the smallest number in Haskell (at least
  according to my GHC, it could be different with different processors,
  right?) that satisfies the equation is 2.2e-16.
 And you've changed the subject - the stuff above was talking about
 x + 1 /= x, you're demonstrating solutions to a different problem, 
 finding the smallest
 x such that 1 + x == 1. That's the number often called epsilon.
  1 + 2.2e-16 /= 1
  True
  1 + 2.2e-17 /= 1
  False
 Let's stop confusing ourselves about this.
 
 Brandon
 ___
 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] [Offtopic] Re: Re: A better syntax for qualified operators?

2006-09-30 Thread Cale Gibbard

What a beautiful world this could be... ;-)) (*)

Cheers,
Ben
(*) Donald Fagen (forgot the name of the song)


I think I.G.Y. (International Geophysical Year) is it:

On that train all graphite and glitter
Undersea by rail
Ninety minutes from New York to Paris
(More leisure time for artists everywhere)
A just machine to make big decisions
Programmed by fellows with compassion and vision
We'll be clean when their work is done
We'll be eternally free yes and eternally young

What a beautiful world this will be
What a glorious time to be free
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Greetings...

2006-09-30 Thread Seth Gordon

jeff p wrote:

Hello,


So before I embark on day 1 of the project, I thought I should check and
see if anyone on this list has used Haskell to munge a ten-million-row
database table, and if there are any particular gotchas I should watch
out for.


One immediate thing to be careful about is how you do IO. Haskell is
not very good, in my experience, at reading files fast. You'll
probably want to skip the standard Haskell IO functions and use the
lazy bytestring library (http://www.cse.unsw.edu.au/~dons/fps.html).


I'm planning to use HSQL, since it's in Debian stable and the API 
resembles what I'm already familiar with.  Database access is slower 
than file access (which is one reason I want to move as much logic as I 
can out of SQL), so if the speed of getting rows out of the database 
turns out to be the bottleneck in my code, I'll either be happy that all 
the other code is so efficient or peeved that HSQL is so inefficient.


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


Re: [Haskell-cafe] Re: Greetings

2006-09-30 Thread Seth Gordon

Paul Johnson wrote:

I've done some stuff with maybe 50k rows at a time.  A few bits and pieces:

1: I've used HSQL 
(http://sourceforge.net/project/showfiles.php?group_id=65248) to talk to 
ODBC databases.  Works fine, but possibly a bit slowly.  I'm not sure 
where the delay is: it might just be the network I was running it over.  
One gotcha: the field function takes a field name, but its not random 
access.  Access the fields in query order or it crashes.


Thanks; that's certainly the sort of thing I like knowing in advance.

2: For large data sets laziness is your friend.  When reading files 
getContents presents an entire file as a list, but its really 
evaluated lazily.  This is implemented using unsafeInterleaveIO.  I've 
never used this, but in theory you should be able to set up a query that 
returns the entire database as a list and then step through it using 
lazy evaluation in the same way.


I assume that the collectRows function in HSQL can produce this kind of 
a lazy list...right?


3: You don't say whether these algorithms are just row-by-row algorithms 
or whether there is something more sophisticated going on.  Either way, 
try to make things into lists and then apply map, fold and filter 
operations.  Its much more declarative and high level when you do it 
that way.


I'm going to need to do some mapping, folding, partitioning...



Let us know how you get on.


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