RE: jhc vs ghc and the surprising result involving ghc generatedassembly.

2005-11-02 Thread Simon Marlow
On 01 November 2005 16:32, Florian Weimer wrote:

 * Simon Marlow:
 
 gcc started generating this rubbish around version 3.4, if I recall
 correctly.  I've tried disabling various optimisations, but can't
 seem to convince gcc not to generate the extra jump.  You don't get
 this from the native code generator, BTW.
 
 But the comparison is present in the C code.  What do you want GCC to
 do?

I didn't mean to sound overly critical of gcc.  But here's what I was
complaining about - the code generated by gcc (3.4.x) is as follows:

Main_zdwfac_info:
.text
.align 8
.text
movq(%rbp), %rdx
cmpq$1, %rdx
jne .L2
movq8(%rbp), %r13
leaq16(%rbp), %rbp
movq(%rbp), %rax
.L4:
jmp *%rax
.L2:
movq%rdx, %rax
imulq   8(%rbp), %rax
movq%rax, 8(%rbp)
leaq-1(%rdx), %rax
movq%rax, (%rbp)
movl$Main_zdwfac_info, %eax
jmp .L4

there's an obvious simplification - the last two instructions should be
replaced by just 

  jmp   Main_zdwfac_info

eliminating one branch and a mov.  This occurs all over the place in our
code.  Whenever a function has more than one computed goto, gcc insists
on commoning up the jmp instructions even when it's a really bad idea,
like above.

Actually if I add -O2, then I get better code, so perhaps this isn't a
real problem.  Although gcc still generates this:

Fac_zdwfac_info:
.text
.align 8
movq(%rbp), %rdx
testq   %rdx, %rdx
jne .L3
movq8(%rbp), %r13
addq$16, %rbp
movq(%rbp), %rax
jmp *%rax
.p2align 4,,7
.L3:
movq8(%rbp), %rax
imulq   %rdx, %rax
decq%rdx
movq%rdx, (%rbp)
movq%rax, 8(%rbp)
movl$Fac_zdwfac_info, %eax
jmp *%rax

and fails to combine the movs with the jmp instruction (we do this
simplification ourselves when post-processing the assembly code).  I'll
compile up gcc 4 and see what happens with that.

Cheers,
Simon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Array operations and pinning

2005-11-02 Thread Rene de Visser

Hello,

Where is the documentation on how pinning works in the GHC garbage collector 
(from a GHC users point of view).


I have copied the following code from array/IO.hs and am thinking that it is 
assuming that the array is pinned? What triggers the pinning?


On a second note.
Why is the type signiture so constricted. The code below works on any 
IOUArray (which is very usefull, not just on Int Word8). Naturally this 
assumes the particular in memory array layout that GHC uses on a particular 
platform, so would not be compatible (probably) with other Haskell 
compilers.


Rene.

hPutArray
:: Handle   -- ^ Handle to write to
- IOUArray Int Word8-- ^ Array to write from
- Int   -- ^ Number of 'Word8's to write
- IO ()

hPutArray handle (IOUArray (STUArray l u raw)) count
 | count == 0
 = return ()
 | count  0 || count  rangeSize (l,u)
 = illegalBufferSize handle hPutArray count
 | otherwise
  = do wantWritableHandle hPutArray handle $
 \ [EMAIL PROTECTED] haFD=fd, haBuffer=ref, haIsStream=stream } - 
do


 [EMAIL PROTECTED] bufBuf=old_raw, bufRPtr=r, bufWPtr=w, bufSize=size 
}

- readIORef ref

 -- enough room in handle buffer?
 if (size - w  count)
-- There's enough room in the buffer:
-- just copy the data in and update bufWPtr.
then do memcpy_baoff_ba old_raw w raw (fromIntegral count)
writeIORef ref old_buf{ bufWPtr = w + count }
return ()

-- else, we have to flush
else do flushed_buf - flushWriteBuffer fd stream old_buf
writeIORef ref flushed_buf
let this_buf =
Buffer{ bufBuf=raw, bufState=WriteBuffer,
bufRPtr=0, bufWPtr=count, bufSize=count }
flushWriteBuffer fd stream this_buf
return ()


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: jhc vs ghc and the surprising result involving ghc generated assembly.

2005-11-02 Thread Tony Finch
On Wed, 2 Nov 2005, skaller wrote:
 On Tue, 2005-11-01 at 19:03 +0100, Florian Weimer wrote:

  BTW, you shouldn't generate identifiers with leading underscores
  because they are reserved for the implementation.

 I AM the implementation :)

You are not the C implementation.

 Generated Identifiers start with underscores,
 so they don't clash with arbitrary C code.

You should prefix them with something else, e.g. felix_.

Tony.
-- 
f.a.n.finch  [EMAIL PROTECTED]  http://dotat.at/
BISCAY: WEST 5 OR 6 BECOMING VARIABLE 3 OR 4. SHOWERS AT FIRST. MODERATE OR
GOOD.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Array operations and pinning

2005-11-02 Thread Simon Marlow
On 02 November 2005 11:15, Rene de Visser wrote:

 Where is the documentation on how pinning works in the GHC garbage
 collector (from a GHC users point of view).
 
 I have copied the following code from array/IO.hs and am thinking
 that it is assuming that the array is pinned? What triggers the
 pinning? 

Actually this code does not assume that any memory is pinned.  It is ok
to pass the underlying ByteArr# directly to C, as long as the C call is
annotated unsafe, which means that GC cannot happen while the call is
running.

If you want to pass ByteArr# to a safe C call, then you have to
allocate the ByteArr# using newPinnedByteArray#.  This is the only way
to get a pinned object in GHC, and the only kind of pinned object that
is supported is a MutByteArr# or ByteArr# (this is to simplify the GC;
it doesn't need to traverse pinned objects because they don't contain
any pointers, all it needs to do is remember that the memory block they
occupy is still alive).

Note that all this is GHC-specific; the right high-level interface to
allocating pinned memory is mallocForeignPtr.

 On a second note.
 Why is the type signiture so constricted. The code below works on any
 IOUArray (which is very usefull, not just on Int Word8). Naturally
 this assumes the particular in memory array layout that GHC uses on a
 particular platform, so would not be compatible (probably) with other
 Haskell compilers.

I think the type is right - it makes it clear that the representation
being written to the file is an array of bytes.  You can use
castIOUArray, although that isn't ideal (it doesn't change the bounds).
We should do something better here.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: jhc vs ghc and the surprising result involving ghc generatedassembly.

2005-11-02 Thread Florian Weimer
* Simon Marlow:

 gcc started generating this rubbish around version 3.4, if I recall
 correctly.  I've tried disabling various optimisations, but can't
 seem to convince gcc not to generate the extra jump.  You don't get
 this from the native code generator, BTW.
 
 But the comparison is present in the C code.  What do you want GCC to
 do?

 I didn't mean to sound overly critical of gcc.

It didn't come across that way.  I just want to construct a test case,
so it can be fixed on the GCC side, and see if I can suggest
alternatives.

 Actually if I add -O2, then I get better code, so perhaps this isn't a
 real problem.  Although gcc still generates this:

   movl$Fac_zdwfac_info, %eax
   jmp *%rax

 and fails to combine the movs with the jmp instruction (we do this
 simplification ourselves when post-processing the assembly code).  

I agree, GCC should optimize this case.  A minimal test case is:

extern void bar();

void foo()
{
  void *p = bar;
  goto *p;
}

None of the GCC versions I have tried optimizes away the indirect
call.

 I'll compile up gcc 4 and see what happens with that.

The jump target is not propagated, either.  Same with 4.1.

However, beginning with GCC 3.4, you can use:

extern void bar();

void foo()
{
  void (*p)(void) = bar;
  p();
}

And the indirect call is turned into a direct jump.  Tail recursive
calls and really indirect tail calls are also optimzed.  Together with
-fomit-frame-pointer, this could give you what you need, without
post-processing the generated assembler code (which is desirable
because the asm volatile statements inhibit further optimization).

Is it correct that you use indirect gotos across functions?  Such
gotos aren't supported by GCC and work only by accident.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: jhc vs ghc and the surprising result involving ghcgeneratedassembly.

2005-11-02 Thread Simon Marlow
On 02 November 2005 13:59, Florian Weimer wrote:

 However, beginning with GCC 3.4, you can use:
 
 extern void bar();
 
 void foo()
 {
   void (*p)(void) = bar;
   p();
 }

Interesting.. though I'm not sure I'm comfortable with relying on gcc's
tail call optimisation to do the right thing.  Aren't there side
conditions that might prevent it from kicking in?
 
 And the indirect call is turned into a direct jump.  Tail recursive
 calls and really indirect tail calls are also optimzed.  Together with
 -fomit-frame-pointer, this could give you what you need, without
 post-processing the generated assembler code (which is desirable
 because the asm volatile statements inhibit further optimization).
 
 Is it correct that you use indirect gotos across functions?  Such
 gotos aren't supported by GCC and work only by accident.

Yes, but cross-function gotos are always to the beginning of a function.
Also, our post-processor removes the function prologue from the asm.

GHC via C has always worked by accident :-)  But it has worked for a
long time with careful tweaking of the post-processor (known as the
mangler) for each new version of gcc.  Yes, we're living dangerously,
and it's getting harder, but we're still alive (just).

Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: jhc vs ghc and the surprising result involving ghcgeneratedassembly.

2005-11-02 Thread Florian Weimer
* Simon Marlow:

 However, beginning with GCC 3.4, you can use:
 
 extern void bar();
 
 void foo()
 {
   void (*p)(void) = bar;
   p();
 }

 Interesting.. though I'm not sure I'm comfortable with relying on gcc's
 tail call optimisation to do the right thing.  Aren't there side
 conditions that might prevent it from kicking in?

It's a target-specific optimization.  For i386, the requirements are
roughly speaking, (a) it works with -fPIC only for very special cases
(direct calls within the same module), (b) the return values must be
the same, (c) for indirect calls, there must be a free register
(currently, this means that regparam must be less than 3; irrelevant
if you don't pass any arguments).

AMD64 has only very few restrictions, none of which seem particularly
relevant.

ia64 may need additional hints before the optimization is performed
(non-default visibility of the target function), otherwise the
optimization is only performed within the same translation unit.
PowerPC and SPARC cannot optimize indirect calls.

Common MIPS targets should be fine.

So your concern is valid; this optimization is not always available.
It might be possible to extend GCC with something that violates the
ABI and fits your needs, though, in case the current goto hack no
longer works.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: jhc vs ghc and the surprising result involving ghc generatedassembly.

2005-11-02 Thread skaller
On Wed, 2005-11-02 at 14:59 +0100, Florian Weimer wrote:


 Is it correct that you use indirect gotos across functions?  Such
 gotos aren't supported by GCC and work only by accident.

Even direct gotos aren't universally supported. Some info
in Fergus Henderson's paper may be of interest

http://felix.sourceforge.net/papers/mercury_to_c.ps


-- 
John Skaller skaller at users dot sf dot net
Felix, successor to C++: http://felix.sf.net

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: jhc vs ghc and the surprising result involving ghc generatedassembly.

2005-11-02 Thread Florian Weimer
 Is it correct that you use indirect gotos across functions?  Such
 gotos aren't supported by GCC and work only by accident.

 Even direct gotos aren't universally supported. Some info
 in Fergus Henderson's paper may be of interest

 http://felix.sourceforge.net/papers/mercury_to_c.ps

This paper seems to be from 1995 or so:

%DVIPSSource:  TeX output 1995.11.29:1656

(Why is it so uncommon to put the publication date on the first page?)

GCC's IL has changed significantly since then; it's not clear if it
still applies.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: jhc vs ghc and the surprising result involving ghcgeneratedassembly.

2005-11-02 Thread Lennart Augustsson

Simon Marlow wrote:

Is it correct that you use indirect gotos across functions?  Such
gotos aren't supported by GCC and work only by accident.



Yes, but cross-function gotos are always to the beginning of a function.


Is that enough to ensure that the constant pool base register
is reloaded on the Alpha?

-- Lennart
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: jhc vs ghc and the surprising result involving ghcgeneratedassembly.

2005-11-02 Thread Florian Weimer
* Lennart Augustsson:

 Simon Marlow wrote:
Is it correct that you use indirect gotos across functions?  Such
gotos aren't supported by GCC and work only by accident.
 Yes, but cross-function gotos are always to the beginning of a
 function.

 Is that enough to ensure that the constant pool base register
 is reloaded on the Alpha?

Good point, most of the restrictions I mentioned result from the need
to update the GP pointer.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: jhc vs ghc and the surprising result involving ghc generatedassembly.

2005-11-02 Thread skaller
On Wed, 2005-11-02 at 18:05 +0100, Florian Weimer wrote:
  Is it correct that you use indirect gotos across functions?  Such
  gotos aren't supported by GCC and work only by accident.
 
  Even direct gotos aren't universally supported. Some info
  in Fergus Henderson's paper may be of interest
 
  http://felix.sourceforge.net/papers/mercury_to_c.ps
 
 This paper seems to be from 1995 or so:
 
 %DVIPSSource:  TeX output 1995.11.29:1656
 
 (Why is it so uncommon to put the publication date on the first page?)
 
 GCC's IL has changed significantly since then; it's not clear if it
 still applies.

I am using some of it in Felix, that part I am using
seems to work fine on all platforms tested: various versions
of g++ and under Linux, OSX, Cygwin, and MinGW, possibly more.

The config script checks assembler labels are supported,
if they are the indirect jumps 'just work'.  Of course
the config would have to be built by hand for cross 
compilation ;(

However my system obeys a constraint: the runtime conspires
to ensure the function containing the target label is
entered before the jump is done. The address is calculated
by the caller though. So I don't run into any problems
loading the right data section pointer. I suspect Haskell
cannot do that, since it would defeat the intended optimisation.

[More precisely, in Felix the technique is used to implement
non-local gotos, and which can only occur in procedures,
not in functions]

-- 
John Skaller skaller at users dot sf dot net
Felix, successor to C++: http://felix.sf.net

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: jhc vs ghc and the surprising result involving ghc generated assembly.

2005-11-02 Thread skaller
On Wed, 2005-11-02 at 19:47 +0100, Florian Weimer wrote:
  It seems that the goto-based version leads to different static branch
  prediction results, which happen to be favorable. 
 
  It has nothing to do with branch prediction. I know 
  it is determined ENTIRELY by stack use.
 
 In both cases, The C compiler emits code which doesn't use the stack.

huh? how can a recursive call not use the stack??

-- 
John Skaller skaller at users dot sf dot net
Felix, successor to C++: http://felix.sf.net

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Silly IO problem

2005-11-02 Thread skaller
This code doesn't work:

import System(getArgs)

main = do n - getArgs = readIO.head
  putStrLn (show (tak (3*n) (2*n) n))

tak :: Float - Float - Float - Float
tak x y z | y=x  = z
  | otherwise = tak (tak (x-1) y z) (tak (y-1) z x) (tak (z-1) x
y)
--
It prints n, rather than tak(3n,2n,n). Can someone give me
the right encoding please?

-- 
John Skaller skaller at users dot sf dot net
Felix, successor to C++: http://felix.sf.net

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Haskell] Haskell Workshop Steering Committee

2005-11-02 Thread Johan Jeuring
At the Haskell workshop in Tallinn in September it was decided to set  
up a Haskell Workshop Steering Committee.


The main purpose of the Haskell Workshop Steering Committee is to  
provide continuity of the workshop and to offer help and advice to  
the current organizer(s) of the workshop.


I'm pleased to announce the Haskell Workshop Steering Committee,  
which has been approved by ACM SIGPLAN.


You can find more information about the Haskell Workshop and its  
Steering Committee on


http://www.haskell.org/haskell-workshop/

-- Johan Jeuring



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


RE: [Haskell] specification of sum

2005-11-02 Thread Simon Marlow
On 02 November 2005 00:20, Lennart Augustsson wrote:

 Furthermore, ghc has a WRONG definition of sum.

Surely not... sum is defined by Haskell 98 as:

 sum = foldl (+) 0

and this is exactly what GHC provides.  Furthermore we have specialised
strict versions for Int and Integer.

Also, we shouldn't be turning overloaded functions into class methods
purely for the purposes of providing optimised versions; that's what the
SPECIALISE pragma is for.

Cheers,
Simon
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] why don't we have const Ptrs?

2005-11-02 Thread David Roundy
Hello all,

I was thinking this morning as I lay on the floor (where I sleep) about
static typechecking, and how much more wonderful Haskell is than any other
language, when it occurred to me that when working with pointers, Haskell
actually has *less* static typechecking than C or C++.  It was a very
disturbing thought, so much so that I was almost compelled to arise early
to place this question before this learned audience.

Why is it that in C++ I can write

void strcpy(char *dest, const char *src);

but in Haskell I must import this function as

 foreign import ccall unsafe static string.h strcpy
  strcpy :: Ptr CChar - Ptr CChar - IO ()

and lose that wonderful information that the function doesn't modify the
contents of its second argument?

One could pretty easily create a ConstPtr type which one could peek into,
but not poke to, but then you'd have to explicitely convert a Ptr into a
ConstPtr when passing it as an argument.  That feels a bit silly.

One could get around this by introducing a class to get around this

 class ReadablePtr p where
peek :: p a - IO a
peekOff ...

and then make both Ptr and ConstPtr instances of this class, but this still
seems like a very hackish solution.

Moreover, I'd like to be able to have const objects quite apart from Ptrs,
such as a const Handle, which I can read from, but cannot write to, or a
const IORef--and we wouldn't want to leave out const ForeignPtrs.  Of
course, even reading affects a Handle's internal state, so one would need
to be explicit about what const indicates.  But it seems to me that in
the IO world there are a whole slew of things that refer to other things
which could all be grouped together.

And a const attribute ought to be derived, so that if I create a data
type

 data FooPtr = FooPtr String (Ptr Foo)

one should ideally be able to automatically understand that a const FooPtr
holds a const (Ptr Foo).

One could go further, at least when dealing with Ptrs, and create a way of
handling restricted pointers--which we could interpret as a const pointer
to an object that cannot be changed by anyone else either.  One could
safely create restricted pointers with a function of the type

 mallocRestrictedPtr :: (Ptr a - IO ()) - RestrictedPtr a

which would allow one to ensure at the typechecking level that
RestrictedPtrs point to memory that cannot be modified.  There's still some
unstafety involved, in that you could read out of bounds, but you would
know that apart from that possibility the contents of a RestrictedPtr truly
will never change.

So my question is, how would one implement such an annotation extension?
I'd like to be able to pass a (Ptr a) as a (Const (Ptr a)) without an
explicit typecast, since the Const really isn't changing the type of the
pointer, it's just marking it as one that can't be modified.  A function
that accepts a (Const (Ptr a)) should also accept a (Restricted (Ptr
a))--but Restricted pointers are really just pudding, as they only differ
from Const pointers in what optimizations are allowed.  On the other hand,
it's not just compiler optimizations that they would allow, but also
user-code optimizations, which could be much more useful.  They also have
the advantage of making certain unsafe functions safe.

The hard part seems to be the lack of a conversion.  One could quite easily
implement a

 data Const a = Const a  -- this constructor is *not exported*
 toConst :: x - Const x
 unsafeAccessConst :: Const x - x

 peek :: Const (Ptr a) - IO a
 peekOff ...

etc, and everything would work fine, except that you'd always need to
explicitely convert from Ptr to Const Ptr.  Perhaps one could make Const be
a class as well as a data type:

 class (Const a) x where
 toConst :: x - Const a
 instance (Const x) x where
 toConst = Const
 instance (Const x) (Const x) where
 toConst = id

and then one could write code like

 peek :: Const (cp a) = cp a - IO a

which would move the typecasting burden out of the calling function and
into the function that accepts a const argument.  Perhaps this would be
sufficient, as many data types have only a limited number of primitive
const functions, and all the other const functions wouldn't actually
need to call toConst.

What this doesn't allow is deriving of constness, so that a Const
ForeignPtr would automatically hold a Const Ptr.

This whole class+data type scheme seems like it might be useful, but is
pretty ugly.  Is there a better way this could be done?

Might one be able to extend the language so that one could add attribute
such as Const to data type without changing the the type itself (which
would be analogous to what one does in C/C++)?
-- 
David Roundy
http://www.darcs.net
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] pattern matching on record fields and position

2005-11-02 Thread David Roundy
Hello fellow haskellers,

I have a couple of related (almost conjugate) proposals/questions.
Basically, I've been thinking about how to make code more robust with
respect to changes in the data types.

Pattern matching based on positions is very fragile (I don't think this is
a surprise to anyone).  When you add a new field to a data type, you have
to modify every bit of code that uses positional pattern matching, such as

lengthPS (PS _ _ l) = l

I'd like to be able export a data type with constructors in such a way that
positional pattern matching isn't possible--but field-based pattern
matching *is* possible.  One could just use a coding policy, but I like the
compiler enforcing things like this for me.  Perhaps there's already a
trick to do this?

In particular, this would be relevant if I had the following data type:

data FPS = PS { fp :: ForeignPtr Word8, my_start :: Int, my_length :: Int }

I would like to be able to export this data constructor (in actual
FastPackedString, the constructor isn't exported at all--and shouldn't
be--but I'm taking this as a simple hypothetical example).

I would like users (who import this module) to be able to write

case fps of { PS { my_start = s } - print s }

but not to write

case fps of { PS _ s _ - print s }

If I could enforce this, then I could change the definition of FPS to

data FPS = PS { fp :: ForeignPtr Word8, my_start :: Int, my_length :: Int,
extra_argument :: String }

or

data FPS = PS { fp :: ForeignPtr Word8, my_length :: Int, my_start :: Int }

and have a guarantee that no code that imports the module will be broken.
In the first example, all positional-matching code would fail to compile.
The second is even more insidious, since code would continue to compile,
but would be wrong!


The second feature I'd like (and even better if it's something that already
exists, although I've been told that it isn't) would be to be able to have
record field names that are exported so as to not allow them to be used as
accessor functions if those functions might lead to failure.  For example:

data Foo = AB { a :: String, b :: Int } | B { b :: Int }

I would like a to be useable for pattern matching, but not as the
function a :: Foo - String, which is dangerous, in that it really ought
(in my opinion) to have the type Foo - Maybe String.

Actually, a compiler warning when using dangerous functions of this sort
(as we can get when we use non-comprehensive pattern-matching) would
satisfy me, although I'd really prefer to be able to have these accessor
functions not be generated, or at least have an option to not export them.

As you can probably tell, I've been thinking about how one can export
constructors and yet still maintain flexibility in the implementation of
data structures.  Pattern matching is very nice, and often one wouldn't
want to give it up, but it seems to completely tie down the implementation
of data type, which is annoying, and seems to be a tradeoff that we could
avoid by a combination of using field descriptors for pattern matching
constructors.  The catch being that for data types with multiple
constructors, field descriptors always introduce unsafe functions that
I'd really prefer didn't exist.
-- 
David Roundy
http://www.darcs.net
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] pattern matching on record fields and position

2005-11-02 Thread Malcolm Wallace
David Roundy [EMAIL PROTECTED] writes:

 I have a couple of related (almost conjugate) proposals/questions.
 Basically, I've been thinking about how to make code more robust with
 respect to changes in the data types.

This sounds a bit like views, proposals for which have been around
for years, but never adopted.  There is a related language feature
(extension) called pattern guards which /is/ implemented in ghc,
and gives most of the power of views.

 I'd like to be able export a data type with constructors in such a way that
 positional pattern matching isn't possible--but field-based pattern
 matching *is* possible.  One could just use a coding policy, but I like the
 compiler enforcing things like this for me.  Perhaps there's already a
 trick to do this?

So, you could export just the field names, but not the constructors.
Instead of patterns, use pattern guards.

 I would like users (who import this module) to be able to write
 
 case fps of { PS { my_start = s } - print s }

This would become
  case fps of { _ | s - my_start fps   - print s }

It slightly abuses the pattern guard notation, because the pattern
is a degenerate one - just a variable name - so it always succeeds.
Thus, for a type with more than one constructor, like this:

 data Foo = AB { a :: String, b :: Int } | B { b :: Int }

the similar construct
  case foo of { _ | x - a foo   - print x
  | otherwise- putStrLn error }
would never reach the otherwise clause, even when given a B constructor.
Instead, it would crash the program.

One common style people use today to enable the later extension of a datatype
is empty-record patterns:

  case foo of { A{} - print (a foo)
  ; B{} - putStrLn error }

but as you no doubt have immediately realised, this forces the
constructors to be visible, and therefore does not prevent the
programmer from using explicit positional patterns.  It is just a
convention, not enforceable.

 The second feature I'd like (and even better if it's something that already
 exists, although I've been told that it isn't) would be to be able to have
 record field names that are exported so as to not allow them to be used as
 accessor functions if those functions might lead to failure.  For example:
 
 data Foo = AB { a :: String, b :: Int } | B { b :: Int }
 
 I would like a to be useable for pattern matching, but not as the
 function a :: Foo - String, which is dangerous, in that it really ought
 (in my opinion) to have the type Foo - Maybe String.

Probably you really want extensible records, with all the rho-typing
trickery that makes it possible to decide statically whether a
particular field exists when an accessor is applied to the record.
There are several competing proposals for this - the OOHaskell one
requires no extensions to Haskell'98.

Regards,
Malcolm
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] The next langauage definition version will be ``Haskell 1.6''

2005-11-02 Thread kahl
Hi all,

  somebody wrote something which reminds me:


  
  *  *
  *  The ``next stable version'' of the Haskell language definition  *
  *  should be called ``Haskell 1.6''.   *
  *  *
  


This follows the numbering scheme used before the current stable version.

Some will still remember that
during the discussion for the name of that version,
a ballot was put out, and ``somehow'' the logical name
``Haskell 1.5'' was missing from that ballot ---
it still received the second-most votes after ``Haskell 98'':
as a free-form fill-in choice!
But ``somehow'' nobody drew the consequence
to do a corrected ballot...


Add to that, that ``Haskell 98'' did of course not come out
at a point of time that had any obvious relation with the number 98.

Choosing ``Haskell 2006'' would therefore be equally unwise.

And choosing something like ``Haskell 06'' would send a message
that is completely wrong for a language
that actually provides arbitrary-precision integers
as its default integer number type.
(It would also make version comparison even harder...)

I therefore encourage everybody
to refer to the current stable version as ``Haskell 1.5'',
and stick with ``Haskell 1.6'' as the name for the next stable version.


Wolfram

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


Re: [Haskell] why don't we have const Ptrs?

2005-11-02 Thread Daan Leijen

Hi David,

 One could pretty easily create a ConstPtr type which one could peek into,
 but not poke to, but then you'd have to explicitely convert a Ptr into a
 ConstPtr when passing it as an argument.  That feels a bit silly.

One way of dealing with constant pointer is to introduce (yet another)
phantom type variable 'r' to pointers:

 data Ptr r a = ...

and introduce a read access hierarchy:

 data Read a
 data Write

A constant pointer has type  Ptr (Read ()) a
A normal pointer has typePtr (Read Write) a
At least read pointerPtr (Read r) a
And a 'don't care' pointer   Ptr r a

 peek :: Ptr (Read r) a - IO a
 poke :: Ptr (Read Write) a - a - IO ()
 alloc:: IO (Ptr (Read Write) a)

So, the type signature for strcat is:

 foreign import strcat :: Ptr (Read Write) CChar - Ptr (Read a) CChar - IO ()

And we can derive the const attribute too:

 data FooPtr r = FooPtr String (Ptr r Foo)

Since the read-write restrictions of Ptr carry over to FooPtr.

The design can be refined since four kinds of pointers is a bit too much.
We could use for example:

 type Const   = ()
 data Write

and say:

 Ptr Const a  == constant pointer
 Ptr Write a  == read-write pointer
 Ptr r a  == at least readable

And strcat would be:

  foreign import strcat :: Ptr Write CChar - Ptr r CChar - IO ()

and we would have:

  constantMalloc :: (Ptr Write a - IO ()) - Ptr Const a
  malloc :: Ptr Write a

  peek :: Ptr r a - IO a
  poke :: Ptr Write a - a - IO ()

So, this is another solution, although I am not sure if it is worth the
trouble making the distinction between normal and constant pointers.

All the best,
-- Daan.

David Roundy wrote:

Hello all,

I was thinking this morning as I lay on the floor (where I sleep) about
static typechecking, and how much more wonderful Haskell is than any other
language, when it occurred to me that when working with pointers, Haskell
actually has *less* static typechecking than C or C++.  It was a very
disturbing thought, so much so that I was almost compelled to arise early
to place this question before this learned audience.

Why is it that in C++ I can write

void strcpy(char *dest, const char *src);

but in Haskell I must import this function as


foreign import ccall unsafe static string.h strcpy
 strcpy :: Ptr CChar - Ptr CChar - IO ()


and lose that wonderful information that the function doesn't modify the
contents of its second argument?

One could pretty easily create a ConstPtr type which one could peek into,
but not poke to, but then you'd have to explicitely convert a Ptr into a
ConstPtr when passing it as an argument.  That feels a bit silly.

One could get around this by introducing a class to get around this


class ReadablePtr p where
   peek :: p a - IO a
   peekOff ...


and then make both Ptr and ConstPtr instances of this class, but this still
seems like a very hackish solution.

Moreover, I'd like to be able to have const objects quite apart from Ptrs,
such as a const Handle, which I can read from, but cannot write to, or a
const IORef--and we wouldn't want to leave out const ForeignPtrs.  Of
course, even reading affects a Handle's internal state, so one would need
to be explicit about what const indicates.  But it seems to me that in
the IO world there are a whole slew of things that refer to other things
which could all be grouped together.

And a const attribute ought to be derived, so that if I create a data
type


data FooPtr = FooPtr String (Ptr Foo)


one should ideally be able to automatically understand that a const FooPtr
holds a const (Ptr Foo).

One could go further, at least when dealing with Ptrs, and create a way of
handling restricted pointers--which we could interpret as a const pointer
to an object that cannot be changed by anyone else either.  One could
safely create restricted pointers with a function of the type


mallocRestrictedPtr :: (Ptr a - IO ()) - RestrictedPtr a


which would allow one to ensure at the typechecking level that
RestrictedPtrs point to memory that cannot be modified.  There's still some
unstafety involved, in that you could read out of bounds, but you would
know that apart from that possibility the contents of a RestrictedPtr truly
will never change.

So my question is, how would one implement such an annotation extension?
I'd like to be able to pass a (Ptr a) as a (Const (Ptr a)) without an
explicit typecast, since the Const really isn't changing the type of the
pointer, it's just marking it as one that can't be modified.  A function
that accepts a (Const (Ptr a)) should also accept a (Restricted (Ptr
a))--but Restricted pointers are really just pudding, as they only differ
from Const pointers in what optimizations are allowed.  On the other hand,
it's not just compiler optimizations that they would allow, but also
user-code optimizations, which could be much more useful.  They also have
the advantage of making certain unsafe functions safe.

The hard part seems to be the lack of a conversion.  

Re: [Haskell] why don't we have const Ptrs?

2005-11-02 Thread Bjorn Lisper
Hi,

Annotated type systems have been around for some time in static program
analysis. I think this is what you want. For instance, you can design such a
system to record possible side effects from a function call, as annotations
on the type of the function.

See the book Principles of Program Analysis,
http://www2.imm.dtu.dk/~riis/PPA/ppa.html.

Björn Lisper


David Roundy:
Hello all,

I was thinking this morning as I lay on the floor (where I sleep) about
static typechecking, and how much more wonderful Haskell is than any other
language, when it occurred to me that when working with pointers, Haskell
actually has *less* static typechecking than C or C++.  It was a very
disturbing thought, so much so that I was almost compelled to arise early
to place this question before this learned audience.

Why is it that in C++ I can write

void strcpy(char *dest, const char *src);

but in Haskell I must import this function as

 foreign import ccall unsafe static string.h strcpy
  strcpy :: Ptr CChar - Ptr CChar - IO ()

and lose that wonderful information that the function doesn't modify the
contents of its second argument?

One could pretty easily create a ConstPtr type which one could peek into,
but not poke to, but then you'd have to explicitely convert a Ptr into a
ConstPtr when passing it as an argument.  That feels a bit silly.

One could get around this by introducing a class to get around this

 class ReadablePtr p where
peek :: p a - IO a
peekOff ...

and then make both Ptr and ConstPtr instances of this class, but this still
seems like a very hackish solution.

Moreover, I'd like to be able to have const objects quite apart from Ptrs,
such as a const Handle, which I can read from, but cannot write to, or a
const IORef--and we wouldn't want to leave out const ForeignPtrs.  Of
course, even reading affects a Handle's internal state, so one would need
to be explicit about what const indicates.  But it seems to me that in
the IO world there are a whole slew of things that refer to other things
which could all be grouped together.

And a const attribute ought to be derived, so that if I create a data
type

 data FooPtr = FooPtr String (Ptr Foo)

one should ideally be able to automatically understand that a const FooPtr
holds a const (Ptr Foo).

One could go further, at least when dealing with Ptrs, and create a way of
handling restricted pointers--which we could interpret as a const pointer
to an object that cannot be changed by anyone else either.  One could
safely create restricted pointers with a function of the type

 mallocRestrictedPtr :: (Ptr a - IO ()) - RestrictedPtr a

which would allow one to ensure at the typechecking level that
RestrictedPtrs point to memory that cannot be modified.  There's still some
unstafety involved, in that you could read out of bounds, but you would
know that apart from that possibility the contents of a RestrictedPtr truly
will never change.

So my question is, how would one implement such an annotation extension?
I'd like to be able to pass a (Ptr a) as a (Const (Ptr a)) without an
explicit typecast, since the Const really isn't changing the type of the
pointer, it's just marking it as one that can't be modified.  A function
that accepts a (Const (Ptr a)) should also accept a (Restricted (Ptr
a))--but Restricted pointers are really just pudding, as they only differ
from Const pointers in what optimizations are allowed.  On the other hand,
it's not just compiler optimizations that they would allow, but also
user-code optimizations, which could be much more useful.  They also have
the advantage of making certain unsafe functions safe.

The hard part seems to be the lack of a conversion.  One could quite easily
implement a

 data Const a = Const a  -- this constructor is *not exported*
 toConst :: x - Const x
 unsafeAccessConst :: Const x - x

 peek :: Const (Ptr a) - IO a
 peekOff ...

etc, and everything would work fine, except that you'd always need to
explicitely convert from Ptr to Const Ptr.  Perhaps one could make Const be
a class as well as a data type:

 class (Const a) x where
 toConst :: x - Const a
 instance (Const x) x where
 toConst = Const
 instance (Const x) (Const x) where
 toConst = id

and then one could write code like

 peek :: Const (cp a) = cp a - IO a

which would move the typecasting burden out of the calling function and
into the function that accepts a const argument.  Perhaps this would be
sufficient, as many data types have only a limited number of primitive
const functions, and all the other const functions wouldn't actually
need to call toConst.

What this doesn't allow is deriving of constness, so that a Const
ForeignPtr would automatically hold a Const Ptr.

This whole class+data type scheme seems like it might be useful, but is
pretty ugly.  Is there a better way this could be done?

Might one be able to extend the language so that one could add attribute
such as Const to data type without changing the the 

Re: [Haskell] why don't we have const Ptrs?

2005-11-02 Thread Josef Svenningsson
Hi,

Here's a way to do pretty much what you're after. The idea is to add an
extra parameter to the Ptr type to indicate if it is a const pointer or
not.

 data Ptr const a

To indicate the constness we create a dummy data type which will show when the pointer type is *not* const.

 data NotConst

Now we can give more refined types to peek and poke like so:

 peek :: Ptr const a - IO a
 poke :: Ptr NotConst a - a - IO ()

With this setup peek will work with both kinds of pointers without any
casting. Constness will also be inferred. If a function is polymorphic
in a const argument that means that it doesn't change to pointer. The
use of higher rank polymorphism can be used to enforce that a pointer
is const.

This way of doing it is perhaps not the most beautiful. It would be a
little nicer if we had data kinds as Omega has. And its a shame that we
need to go outside Haskell98 if we want to enforce constness, since we
need to use higher rank polymorphism. Nevertheless this solution
adresses most of issues that you considered.

Cheers,

/JosefOn 11/2/05, David Roundy [EMAIL PROTECTED] wrote:
Hello all,I was thinking this morning as I lay on the floor (where I sleep) aboutstatic typechecking, and how much more wonderful Haskell is than any otherlanguage, when it occurred to me that when working with pointers, Haskell
actually has *less* static typechecking than C or C++.It was a verydisturbing thought, so much so that I was almost compelled to arise earlyto place this question before this learned audience.Why is it that in C++ I can write
void strcpy(char *dest, const char *src);but in Haskell I must import this function as foreign import ccall unsafe static string.h strcpystrcpy :: Ptr CChar - Ptr CChar - IO ()
and lose that wonderful information that the function doesn't modify thecontents of its second argument?One could pretty easily create a ConstPtr type which one could peek into,but not poke to, but then you'd have to explicitely convert a Ptr into a
ConstPtr when passing it as an argument.That feels a bit silly.One could get around this by introducing a class to get around this class ReadablePtr p wherepeek :: p a - IO apeekOff ...
and then make both Ptr and ConstPtr instances of this class, but this stillseems like a very hackish solution.Moreover, I'd like to be able to have const objects quite apart from Ptrs,such as a const Handle, which I can read from, but cannot write to, or a
const IORef--and we wouldn't want to leave out const ForeignPtrs.Ofcourse, even reading affects a Handle's internal state, so one would needto be explicit about what const indicates.But it seems to me that in
the IO world there are a whole slew of things that refer to other thingswhich could all be grouped together.And a const attribute ought to be derived, so that if I create a data
type data FooPtr = FooPtr String (Ptr Foo)one should ideally be able to automatically understand that a const FooPtrholds a const (Ptr Foo).One could go further, at least when dealing with Ptrs, and create a way of
handling restricted pointers--which we could interpret as a const pointerto an object that cannot be changed by anyone else either.One couldsafely create restricted pointers with a function of the type
 mallocRestrictedPtr :: (Ptr a - IO ()) - RestrictedPtr awhich would allow one to ensure at the typechecking level thatRestrictedPtrs point to memory that cannot be modified.There's still some
unstafety involved, in that you could read out of bounds, but you wouldknow that apart from that possibility the contents of a RestrictedPtr trulywill never change.So my question is, how would one implement such an annotation extension?
I'd like to be able to pass a (Ptr a) as a (Const (Ptr a)) without anexplicit typecast, since the Const really isn't changing the type of thepointer, it's just marking it as one that can't be modified.A function
that accepts a (Const (Ptr a)) should also accept a (Restricted (Ptra))--but Restricted pointers are really just pudding, as they only differfrom Const pointers in what optimizations are allowed.On the other hand,
it's not just compiler optimizations that they would allow, but alsouser-code optimizations, which could be much more useful.They also havethe advantage of making certain unsafe functions safe.The hard part seems to be the lack of a conversion.One could quite easily
implement a data Const a = Const a-- this constructor is *not exported* toConst :: x - Const x unsafeAccessConst :: Const x - x peek :: Const (Ptr a) - IO a peekOff ...
etc, and everything would work fine, except that you'd always need toexplicitely convert from Ptr to Const Ptr.Perhaps one could make Const bea class as well as a data type: class (Const a) x where
 toConst :: x - Const a instance (Const x) x where toConst = Const instance (Const x) (Const x) where toConst = idand then one could write code like peek :: Const (cp a) = cp a - IO a
which would move the typecasting burden out of the calling function andinto the 

RE: [Haskell] specification of sum

2005-11-02 Thread Scherrer, Chad


 Surely not... sum is defined by Haskell 98 as:
 
  sum = foldl (+) 0
 
 and this is exactly what GHC provides.  Furthermore we have 
 specialised strict versions for Int and Integer.
 

I'd been using ghci for testing along the way and getting terrible
results; does the specialization only apply to ghc per se?

 
 Cheers,
   Simon
 

Also, Cale, I was thinking about your comment about formal power series,
and I don't see that (+) should not be strict in this case. In
particular, if they are represented as infinite lists, I agree that
zipWith (+) works just fine, though it is strict but lazy.

Here is the strictness:
zipWith (+) undefined [1,2,3] == undefined
zipWith (+) [1,2,3] undefined == undefined

And here is the laziness:
head $ zipWith (+) (1:undefined) (2:undefined) == 3

Or am I missing something?

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


Re: [Haskell] specification of sum

2005-11-02 Thread Cale Gibbard
On 02/11/05, Scherrer, Chad [EMAIL PROTECTED] wrote:


  Surely not... sum is defined by Haskell 98 as:
 
   sum = foldl (+) 0
 
  and this is exactly what GHC provides.  Furthermore we have
  specialised strict versions for Int and Integer.
 

 I'd been using ghci for testing along the way and getting terrible
 results; does the specialization only apply to ghc per se?

 
  Cheers,
Simon
 

 Also, Cale, I was thinking about your comment about formal power series,
 and I don't see that (+) should not be strict in this case. In
 particular, if they are represented as infinite lists, I agree that
 zipWith (+) works just fine, though it is strict but lazy.

 Here is the strictness:
 zipWith (+) undefined [1,2,3] == undefined
 zipWith (+) [1,2,3] undefined == undefined

 And here is the laziness:
 head $ zipWith (+) (1:undefined) (2:undefined) == 3

 Or am I missing something?

 -Chad


Oh, well that's true, but I suppose that by strictness I mean that it
doesn't completely force the evaluation of its arguments to normal
form, as shown in the second example. If it was more strict, that
would also be undefined, as would be the sum of any two infinite
lists. I suppose it's somewhat of a matter of perspective: are you
passing it a list, or a cons cell? In the case of power series, I was
thinking of the whole power series as the parameter, not just the
outermost data constructor.

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


Re: [Haskell] specification of sum

2005-11-02 Thread Lennart Augustsson

Simon Marlow wrote:

On 02 November 2005 00:20, Lennart Augustsson wrote:



Furthermore, ghc has a WRONG definition of sum.



Surely not... sum is defined by Haskell 98 as:

 sum = foldl (+) 0

and this is exactly what GHC provides.  Furthermore we have specialised
strict versions for Int and Integer.

Also, we shouldn't be turning overloaded functions into class methods
purely for the purposes of providing optimised versions; that's what the
SPECIALISE pragma is for.


You are absolutly right, sum is defined with foldl.
I wonder why my hbc prelude had it defined with foldr?
(This should teach me not to look at bit rotted code.)

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


Re: [Haskell] pattern matching on record fields and position

2005-11-02 Thread John Meacham
You might want to look at the 'get', 'set' and 'update' rules that DrIFT
can derive. i made them to addres a lot of the same issues you
mentioned.

I personally think it is a travesty that 

data Foo = Foo { a :: Int, b :: Char } | Bar { a :: Int }

let x = Bar { a = 4 }
y = x { b = 'x'} 

results in bottom rather than just leaving x unchanged.

well, travesty is too strong. but it bugs the heck out of me.

but yeah, the DrIFT code derives functions that pull out fields but
returns them in a possibly failing monad so you can properly handle a
data type with no appropriate field.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] The next langauage definition version will be ``Haskell 1.6''

2005-11-02 Thread John Meacham
Long ago I determined I spent much more time deciding on the name of
projects and what I should call releases than working on code so I
decided to solve the issue once and for all and just started using a
random password generator to generate release versions and project
names. therefore, I suggest the next release of haskell be called one of 

   saticshicda sat-ic-shic-da
  adlibduebgi ad-lib-dueb-gi
  tekavwesgha tek-av-wes-gha
 nuidhaib nu-id-haib
  frovhicgixo frov-hic-gix-o
  scudhiolento scud-hi-ol-ent-o
dorsh dorsh
poluc pol-uc
cilye cil-ye
bliaktizo bliak-tiz-o
 dyshropveast dy-shrop-veast
  etpevof et-pev-of
 queo queo
   mehasixcyn me-has-ix-cyn
 webgexju web-gex-ju

Am I serious? perhaps not, but it actually is how I name my darcs tags
and projects without an obvious name. (if anyone was wondering where I
got my jhc tag names from) Perhaps I just dislike dogshed discussions
(even when taking place internally)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] specification of sum

2005-11-02 Thread John Meacham
On Wed, Nov 02, 2005 at 11:18:13AM -, Simon Marlow wrote:
 Also, we shouldn't be turning overloaded functions into class methods
 purely for the purposes of providing optimised versions; that's what the
 SPECIALISE pragma is for.

I am a little torn on the issue, on one hand, if it is purely for
performance, then yeah, that makes sense, and SPECIALISE is a pretty key
pragma for any compiler. (so much so that I have 5 variations on it in
jhc :) ). however, having a default of (+) a b = sum [a,b] might be
useful if sum and product are more straightforward to define for an
instance than + and *. however, I don't know if this ever actually
occurs in practice.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] Vector/matrix arithmetic

2005-11-02 Thread James McNeill








Im attempting to learn Haskell by writing some orbital
mechanics code. Id like to use vector and matrix arithmetic to
simplify it. The Haskell book Ive got, Simon Thompsons Haskell:
The Craft of Functional Programming, has one approach, which is to alias
a list of numbers to Vector, and a list of vectors to Matrix, and then define
functions to perform inner and outer products (dot/cross products) and so
forth.



On http://haskell.org/hawiki/FunDeps another approach is
sketched out that looks far more appealing to me. This is to create Vector and
Matrix types that can use overloaded arithmetic operators. It uses functional
dependencies, and the resulting syntax looks a lot like what you can do using
C++ or Matlab.



I dont know enough Haskell to finish out the code
that is started there, and I havent been able to find any vector/matrix
libraries for Haskell that look like this. I did find a port of a linear
algebra library (BLAS) to Haskell, but it looked like it did everything in
imperative style. Performance is not a major concern for me at this point
so Id prefer to do things functionally.



Does anyone know what the best way to do vector/matrix
arithmetic in Haskell might be? I dont need arbitrary dimension; all
my work will be confined to 2D and 3D space.



Thanks!








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