Re: [Haskell-cafe] HToolkit HSQL on Windows/GHC

2004-03-29 Thread Keith Wansbrough
  Another thought, which I hesitate to even mention, would be to call the
  commandline tool via System.Cmd, pipe the results to a file, and read
  the file, and parse the results. Slow and ugly, but you could have it
  working in an hour.
 
 Hadn't even thought of that, must be my clean upbringing.

No need even to use a file; just have it output to a pipe and read directly from the 
pipe...

--KW 8-)
-- 
Keith Wansbrough [EMAIL PROTECTED]
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


[Haskell-cafe] dimension of arrays

2004-03-29 Thread Fred Nicolier
Is there a way to get the number of dimension of an array ? i.e. 
something like :

dims :: (Ix a) = Array a b - Int
dims = ...
a = listArray (1,10) [1,2..]
b = listArray ((1,1),(10,10)) [1,2..]
dims a -- should be equal to 1
dims b -- should be equal to 2
The key is somewhere in the Ix class but where ?

Fred



--
---
Dr. Frederic Nicolier
Maitre de conferences, laboratoire LAM - URCA
Animateur du projet ANITA : http://f.nicolier.free.fr/recherches/
Dept. GEII, IUT de Troyes
9 rue de Quebec
10026 Troyes Cedex
Tel: 03 25 42 71 01
Std: 03 25 42 46 46
Fax: 03 25 42 46 43
email: [EMAIL PROTECTED]  
-

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


Re: [Haskell-cafe] HToolkit HSQL on Windows/GHC

2004-03-29 Thread Graham Klyne
At 10:59 29/03/04 +0100, Keith Wansbrough wrote:
  Another thought, which I hesitate to even mention, would be to call the
  commandline tool via System.Cmd, pipe the results to a file, and read
  the file, and parse the results. Slow and ugly, but you could have it
  working in an hour.

 Hadn't even thought of that, must be my clean upbringing.
No need even to use a file; just have it output to a pipe and read 
directly from the pipe...
Like POpen for GHC/Posix?  I'm having some trouble getting this to work for 
Hugs/Windows (even though the basic piping code for Windows is demonstrated 
to work).

#g


Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] looking for optimization advice

2004-03-29 Thread Simon Marlow
 I think that adding the extra check to see if the pointers 
 are identical
 sped this up enough that it's probably no longer a major 
 issue--I'm pretty
 certain that the problem was large strings that were 
 identical, so every
 byte had to be checked, so probably scary non-portable home-made
 ForeignPtrs would not be worth the effort.  (Although I'm 
 somewhat curious as to how it would be done...)

A ForeignPtr allocated with mallocForeignPtr in GHC is heap-allocated
garbage-collectable storage, and doesn't need a finalizer.  The other
kind of ForeignPtr created with newForeignPtr is associated with some
external storage and needs a finalizer.  Finalizers are expensive, and
so is malloc(), but mallocForeignPtr is very cheap.

This gives rise to a sum-type in the implementation of ForeignPtr: see
the source code (libraries/base/GHC/ForeignPtr.hs).  You could make a
specialised version by ripping out the non-malloc ForeignPtr bits, and
make an unboxable ForeignPtr type.

A mallocForeignPtr-style ForeignPtr is essentially the same as an
IOUArray.  In fact, the underlying implementation type is the same
(MutableByteArray#), except that a ForeignPtr is allocated in pinned
(immovable) storage so that it can be passed to foreign functions.
There could easily be a conversion from a malloc ForeignPtr to
IOUArray.

There is also some overlap with the StorableArray type.  A StorableArray
has a ForeignPtr inside it.  

It really looks like the framework could be simplified here, but I
remember putting some thought into it and not coming up with a simple
solution.

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


Re: [Haskell-cafe] dimension of arrays

2004-03-29 Thread Josef Svenningsson
On Mon, 29 Mar 2004, Fred Nicolier wrote:

 Is there a way to get the number of dimension of an array ? i.e.
 something like :

  dims :: (Ix a) = Array a b - Int
  dims = ...
  a = listArray (1,10) [1,2..]
  b = listArray ((1,1),(10,10)) [1,2..]
  dims a -- should be equal to 1
  dims b -- should be equal to 2

 The key is somewhere in the Ix class but where ?

In a sense Haskell arrays are always one dimensional. But as you noted
tuples are used to achieve higher dimensionality. As far as I know there
is no way of asking for the dimension of an array. You could write your
own class for that though. Here's a suggestion:

\begin{code}
dims :: (Ix a, HasDimension a) = Array a b - Int
dims arr = dimension (head (range arr))

class HasDimension a where
  dimension :: a - Int

instance HasDimension Int where
  dimension _ = 1

instance HasDimension Float where
  dimension _ = 1

instance HasDimension (a,b) where
  dimension _ = 2

instance HasDimension (a,b,c) where
  dimension _ = 3
\end{code}

And so forth. Beware. The code is untested.

Hope this helps.

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


Re: [Haskell-cafe] dimension of arrays

2004-03-29 Thread Fred Nicolier
Josef Svenningsson wrote:

In a sense Haskell arrays are always one dimensional. But as you noted
tuples are used to achieve higher dimensionality. As far as I know there
is no way of asking for the dimension of an array. You could write your
own class for that though. Here's a suggestion:
\begin{code}
dims :: (Ix a, HasDimension a) = Array a b - Int
dims arr = dimension (head (range arr))
 

with the following correction, it is ok.

dims arr = dimension (head (range $ bounds arr))

thanks at lot
Fred




--
---
Dr. Frederic Nicolier
Maitre de conferences, laboratoire LAM - URCA
Animateur du projet ANITA : http://f.nicolier.free.fr/recherches/
Dept. GEII, IUT de Troyes
9 rue de Quebec
10026 Troyes Cedex
Tel: 03 25 42 71 01
Std: 03 25 42 46 46
Fax: 03 25 42 46 43
email: [EMAIL PROTECTED]  
-

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


[Haskell-cafe] Context for type parameters of type constructors

2004-03-29 Thread Henning Thielemann

Sorry for sending this twice, but it seems to me that the newsgroup
fa.haskell only logs the discussion of haskell and haskell-cafe.

-- Forwarded message --
Date: Mon, 29 Mar 2004 01:18:27 -0800
From: [EMAIL PROTECTED] (Henning Thielemann)
Newsgroups: fa.haskell
Subject: Context for type parameters of type constructors
NNTP-Posting-Host: 134.102.210.249
Message-ID: [EMAIL PROTECTED]


I have a problem with type classes that can be illustrated
with the following example:
I want to declare a class for vector like data.
'Vector' is not meant as a synonyme for 'array'
but a 'vector' shall be a mathematical object
that allows for some linear operations,
namely summing and scaling.

Thus I setup a type constructor VectorSpace
in the following way:

 module VectorSpace
where

 class VectorSpace v where
zero  :: v a
add   :: v a - v a - v a
scale :: a - v a - v a

I haven't added context requirements like (Num a)
to the signatures of 'zero', 'add', 'scale'
because I cannot catch all requirements
that instances may need.

The problematic part is the 'scale' operation
because it needs both a scalar value and a vector.
Without the 'scale' operation
'v' could be simply a type (*)
rather than a type constructor (* - *).

Now let's try some instances:

 data (Num a) = VList a = VList [a]

 instance VectorSpace VList where
zero  = VList (repeat 0)
add   (VList x) (VList y) = VList (zipWith (+) x y)
scale s (VList x) = VList (map (s*) x)

 data (Num a) = VFunc b a = VFunc (b-a)

 instance VectorSpace (VFunc b) where
zero  = VFunc (\_ - 0)
add   (VFunc f) (VFunc g) = VFunc (\x - (f x) + (g x))
scale s (VFunc f) = VFunc (\x - s*(f x))

But now GHC complains:

$ ghc -c VectorSpace.lhs

VectorSpace.lhs:37:
Could not deduce (Num a) from the context (VectorSpace VList)
  arising from the literal `0' at VectorSpace.lhs:30
Probable fix:
Add (Num a) to the class or instance method `zero'
In the first argument of `repeat', namely `0'
In the first argument of `VList', namely `(repeat 0)'
In the definition of `zero': zero = VList (repeat 0)

...

I hoped that when I declare VList within the context (Num a)
then it is always asserted
that a VList is built on a Num type.

If it is necessary to add (Num a) somewhere in the instance declaration -
then where?


Btw. I'm using

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.0



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


Re: [Haskell-cafe] Context for type parameters of type constructors

2004-03-29 Thread MR K P SCHUPKE

Could not deduce (Num a) from the context (VectorSpace VList)

The problem is in the definition: 

zero  = VList (repeat 0)

Is 0 an Int or an Integer? 

To define zero, instances need to be parameterised by 
vector type:

EG:

class VectorSpace v a where
   zero  :: v a
   add   :: v a - v a - v a
   scale :: a - v a - v a

instance VectorSpace VList Int where
   zero  = VList (repeat 0)
...

instance VectorSpace VList Float where
   zero  = VList (repeat 0.0)

etc...


Could not deduce (Num a) from the context (VectorSpace VList)

The problem is in the definition: 

zero  = VList (repeat 0)

Is 0 an Int or an Integer? 

To define zero, instances need to be parameterised by 
vector type:

EG:

class VectorSpace v a where
   zero  :: v a
   add   :: v a - v a - v a
   scale :: a - v a - v a

instance VectorSpace VList Int where
   zero  = VList (repeat 0)
...

instance VectorSpace VList Float where
   zero  = VList (repeat 0.0)

etc...

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


Re: [Haskell-cafe] Context for type parameters of type constructors

2004-03-29 Thread Dylan Thurston
On Mon, Mar 29, 2004 at 06:00:57PM +0200, Henning Thielemann wrote:
 Thus I setup a type constructor VectorSpace
 in the following way:
 
  module VectorSpace
 where
 
  class VectorSpace v where
 zero  :: v a
 add   :: v a - v a - v a
 scale :: a - v a - v a
 
 I haven't added context requirements like (Num a)
 to the signatures of 'zero', 'add', 'scale'
 because I cannot catch all requirements
 that instances may need.
 
 The problematic part is the 'scale' operation
 because it needs both a scalar value and a vector.
 Without the 'scale' operation
 'v' could be simply a type (*)
 rather than a type constructor (* - *).

Right.

I recommend you use multi-parameter type classes, with a type of the
scalars and the type of the vectors.  For the method you're using, you
need to add a 'Num a' context.  You say that you 'cannot catch all
requirements that instances may need', but certainly any instance will
need that context.

If you use multi-parameter type classes, then in your instance
declaration you can specify exactly what requirements you need.  For
instance:

 class VectorSpace v a where
   zero :: v
   add :: v - v - v
   scale :: a - v - v

 instance VectorSpace IntArray Int where ...

 instance (Num a) = VectorSpace (GenericArray a) a where ...

Peace,
Dylan


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