Re: [Haskell] Haskell 6.4 perfomance

2005-03-25 Thread Alexandre
Keean, thank you.
Does any tests/benchmarks available?
Regards,
/Alexandre.
On Mar 25, 2005, at 00:47, Keean Schupke wrote:
Think this should really go to glasgow-haskell-users...
If this is true - how do I get ghc to use C--, and is it really faster 
than using gcc as a backend with all the bells  whistles turned on 
(for a pentium-III) something like

   -O3 -mcpu=pentium3 -march=pentium3 -pipe -fomit-frame-pointer 
-momit-leaf-frame-pointer -ftracer -fno-crossjumping -mfpmath=sse,387 
-ffast-math -fsched-spec-load -fprefetch-loop-arrays 
-maccumulate-outgoing-args -fmove-all-movables
-freduce-all-givs

   Keean.
Alexandre wrote:
As I heard, 6.4 version of the Haskell using C-- backend and make 
lots of the resulting code perfomance (programs executed faster).
If so, does any test/comparison with other languages available?

Thank you in advance,
Regards,
/Alexandre.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

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


Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Robert van Herk
Hi all,
I need to use duplicate instances. I read in the documentation on GHC 
6.4, that overlapping class instances checks are lazy instead of gready 
in 6.4. However, my code still gives duplicate instance errors when 
compiling in GHC 6.4.

Is the duplicate instance check still gready? Is there a way to 
overwrite that behaviour?

Right now, I have two instance of a class Datasource. Datasource allows 
the user to read (key,value) pairs.

class Datasource ds k v where
...
Now, I wanted to make a special datasource that combines two 
datasources, namely

data JoinedDS left right = JoinedDS left right
instance (Datasource left k v) = Datasource (JoinedDS left right) k v 
where
...

instance (Datasource right k v) = Datasource (JoinedDS left right) k v 
where
...

The idea is that when you combine 2 datasources in one JoinedDS, the 
user can read both types from the JoinedDS. I do not need to allow to 
combine 2 different datasources that have the same types of (key,value) 
pairs, so the duplicate instances will not occur and when they do, this 
will be by mistake. Hence, the two premisses in the instance declaration 
will never be fulfilled both at the same time and I do not want a 
duplicate instance error here.

Is there a  solution to this problem?
Thanks,
Robert
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Biographical Profiling

2005-03-25 Thread Andreas Marth
Hallo!

The ghc user guide says that there are 4 states a heap object may be in.
Unfortunately in my program there are 5 states (inherent_use, use, drag,
lag, void) with inherent_use being the biggest part (many MBs) and the one
not mentioned in the users guide.
My question is what does it mean? What can I do to get rid of it?

Thanks,
Andreas

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


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Robert van Herk wrote:
Hi all,
I need to use duplicate instances. I read in the documentation on GHC 
6.4, that overlapping class instances checks are lazy instead of 
gready in 6.4. However, my code still gives duplicate instance errors 
when compiling in GHC 6.4.

Is the duplicate instance check still gready? Is there a way to 
overwrite that behaviour?

Right now, I have two instance of a class Datasource. Datasource 
allows the user to read (key,value) pairs.

class Datasource ds k v where
...
Now, I wanted to make a special datasource that combines two 
datasources, namely

data JoinedDS left right = JoinedDS left right
instance (Datasource left k v) = Datasource (JoinedDS left right) k v 
where
...

instance (Datasource right k v) = Datasource (JoinedDS left right) k 
v where
...

The idea is that when you combine 2 datasources in one JoinedDS, the 
user can read both types from the JoinedDS. I do not need to allow to 
combine 2 different datasources that have the same types of 
(key,value) pairs, so the duplicate instances will not occur and when 
they do, this will be by mistake. Hence, the two premisses in the 
instance declaration will never be fulfilled both at the same time and 
I do not want a duplicate instance error here.

Is there a  solution to this problem?
To resolve overlap the HEAD of the instance must be different... Might I 
suggest:

-- as value depends on source and key, requires functional dependancy
class Datasource s k v | s k - v ...
data JoinedDS l r = JoinedDS l r
instance (Datasource l k v1,Datasource r k v2) = Datasource (JoinedDS l 
r) k (v1,v2) ...

Now a joined datasource resturns a pair of values instead of a single value.
   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Keean Schupke wrote:
Robert van Herk wrote:
Hi all,
I need to use duplicate instances. I read in the documentation on GHC 
6.4, that overlapping class instances checks are lazy instead of 
gready in 6.4. However, my code still gives duplicate instance errors 
when compiling in GHC 6.4.

Is the duplicate instance check still gready? Is there a way to 
overwrite that behaviour?

Right now, I have two instance of a class Datasource. Datasource 
allows the user to read (key,value) pairs.

class Datasource ds k v where
...
Now, I wanted to make a special datasource that combines two 
datasources, namely

data JoinedDS left right = JoinedDS left right
instance (Datasource left k v) = Datasource (JoinedDS left right) k 
v where
...

instance (Datasource right k v) = Datasource (JoinedDS left right) k 
v where
...

The idea is that when you combine 2 datasources in one JoinedDS, the 
user can read both types from the JoinedDS. I do not need to allow to 
combine 2 different datasources that have the same types of 
(key,value) pairs, so the duplicate instances will not occur and when 
they do, this will be by mistake. Hence, the two premisses in the 
instance declaration will never be fulfilled both at the same time 
and I do not want a duplicate instance error here.

Is there a  solution to this problem?
To resolve overlap the HEAD of the instance must be different... Might 
I suggest:

-- as value depends on source and key, requires functional dependancy
class Datasource s k v | s k - v ...
data JoinedDS l r = JoinedDS l r
instance (Datasource l k v1,Datasource r k v2) = Datasource (JoinedDS 
l r) k (v1,v2) ...

Now a joined datasource resturns a pair of values instead of a single 
value.

 
Further to this to get the exact behaviour you want, if a datasource can 
return the result using a type lifted maybe on a lookup failure then:

class Datasource s k v | s k - v ...
data JoinedDS l r = JoinedDS l r
instance (Datasource l k v1,
Datasource r k v2,
JoinDS v1 v2 v) = Datasource (JoinedDS l r) k v

class Fail
data This_should_never_happen

data TNothing = TNothing
data TJust a = TJust a

class JoinDS l r t | l r - t
instance JoinDS TNothing TNothing TNothing
instance JoinDS TNothing (TJust v) (TJust v)
instance JoinDS (TJust u) TNothing (TJust u)
instance Fail This_should_never_happen = JoinDS (TJust u) (TJust v) 
TNothing

Now you datasources just need to return the type TJust v on success 
and TNothing on failure.

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


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Robert van Herk
Keean Schupke wrote:
Robert van Herk wrote:
Hi all,
I need to use duplicate instances. I read in the documentation on GHC 
6.4, that overlapping class instances checks are lazy instead of 
gready in 6.4. However, my code still gives duplicate instance errors 
when compiling in GHC 6.4.

Is the duplicate instance check still gready? Is there a way to 
overwrite that behaviour?

Right now, I have two instance of a class Datasource. Datasource 
allows the user to read (key,value) pairs.

class Datasource ds k v where
...
Now, I wanted to make a special datasource that combines two 
datasources, namely

data JoinedDS left right = JoinedDS left right
instance (Datasource left k v) = Datasource (JoinedDS left right) k 
v where
...

instance (Datasource right k v) = Datasource (JoinedDS left right) k 
v where
...

The idea is that when you combine 2 datasources in one JoinedDS, the 
user can read both types from the JoinedDS. I do not need to allow to 
combine 2 different datasources that have the same types of 
(key,value) pairs, so the duplicate instances will not occur and when 
they do, this will be by mistake. Hence, the two premisses in the 
instance declaration will never be fulfilled both at the same time 
and I do not want a duplicate instance error here.

Is there a  solution to this problem?
To resolve overlap the HEAD of the instance must be different... Might 
I suggest:

-- as value depends on source and key, requires functional dependancy
class Datasource s k v | s k - v ...
Yes, I already had that, forgot to mention it though...
data JoinedDS l r = JoinedDS l r
instance (Datasource l k v1,Datasource r k v2) = Datasource (JoinedDS 
l r) k (v1,v2) ...

Now a joined datasource resturns a pair of values instead of a single 
value.
Yes, but this is not what I want. I want to be able to give a key that 
either the left or the right data source would take, and then return the 
appropriate value. Thus: if I pass it a key that would normally go into 
l, I want the value l returns me to be returned, and if I pass it the 
key that would normally go into r, I want to return the value r returns me.

The datasource class has a function dsread :: ds - k - (ds, v) -- read 
may have a side effect
Thus I want want to do something like:
instance (Datasource l k v) = Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) = Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)

It would be perfectly okay to me when the compiler would complain if the 
key and value that go into l and r are the same, but for any useful 
purpose I can think of (e.g. glueing two database couplings together, 
since I also made a Datasource instance for database access), this will 
not happen and the duplicate instances should not really occur, since 
the context of the instances makes sure only 1 will be possible.

However, GHC only looks at the RHS (thus: Datasource (JoinedDS l r) k v) 
and then decides that both instances are the same.

So, my question was: how to overcome this.
Thanks,
Robert
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
There was a typo in the code I posted:

class Fail
data This_should_never_happen

should read:

class Fail x
data This_should_never_happen

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


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Just thought I ought to point out that all this is only necessary if the 
datasources may return different types... If you want them to return the 
same type you only need:

instance (Datasource l k v,Datasource r k v) = Datasource (JoinedDS l 
r) k v ...

As both datasources have the same key and value types, you then choose 
which 'v' to return at the value level.

I am not sure whether you intended Datasources to contain heterogeneous 
key or value types, and whether the loolup is supposed to be value or 
type driven. My original answer assumed a single Datasource contains 
values of different types, selected by the type of the key...

   Keean.

Robert van Herk wrote:
Yes, but this is not what I want. I want to be able to give a key that 
either the left or the right data source would take, and then return 
the appropriate value. Thus: if I pass it a key that would normally go 
into l, I want the value l returns me to be returned, and if I pass it 
the key that would normally go into r, I want to return the value r 
returns me.

The datasource class has a function dsread :: ds - k - (ds, v) -- 
read may have a side effect
Thus I want want to do something like:
instance (Datasource l k v) = Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) = Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)

It would be perfectly okay to me when the compiler would complain if 
the key and value that go into l and r are the same, but for any 
useful purpose I can think of (e.g. glueing two database couplings 
together, since I also made a Datasource instance for database 
access), this will not happen and the duplicate instances should not 
really occur, since the context of the instances makes sure only 1 
will be possible.

However, GHC only looks at the RHS (thus: Datasource (JoinedDS l r) k 
v) and then decides that both instances are the same.

So, my question was: how to overcome this.
Thanks,
Robert

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


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Robert van Herk
Keean Schupke wrote:
Just thought I ought to point out that all this is only necessary if 
the datasources may return different types... If you want them to 
return the same type you only need:

instance (Datasource l k v,Datasource r k v) = Datasource (JoinedDS l 
r) k v ...

As both datasources have the same key and value types, you then choose 
which 'v' to return at the value level.
Nono, the datasources I have implemented are a type safe means to 
extract (key,value) pairs from a data store. The idea is that this way, 
in a type safe fashion, e.g. database access can be abstract.

I use HaskellDB as the database access layer, and then define a 
datasource instance for any given database, so that the user does not 
need to think about the details of the actual database access: he can 
just read and write from the datasource, and the datasource will make 
sure the actual queries will be executed.

My idea now was that if I have 2 databases, and I construct datasources 
for them, it would be really cool if I was able to unite them, so that 
the programmer in the end could talk two 1 datasource, that allowed for 
accessing the 2 databases at one entry point. This was what I was making 
the JoinedDS for.

So, suppose I have 2 datasources for two different databases. One may 
have keys:
data KeysOfDS1 = KDB1_Table1 Int
   |  KDB1_Table2 Int

and values
data ValuesOfDS1 = VDB1_Table1 (Int,Int,String)
   | VDB2_Table2 (Int,Int,String)
and the other one:
data KeysOfDS2 = KDB2_Table1 String
   |  KDB2_Table2 String
data ValuesOfDS2 = VDB2_Table1 (String, Float)
   | VDB2_Table2 (String, Float, Int)
Now, these datastructures correspond to the actual tables in the 
database. My toolset will generate datasources for these types, thus we 
have instances:

instance Datasource Database1 KeysOfDS1 ValuesOfDS1
instance Datasource Database2 KeysOfDS2 ValuesOfDS2
and the cool thing would be, to combine these two datasources at a 
higher level in my datasources graph, so that I would have 1 datasource 
that found out by itself which actual datasource to use, thus:

x::JoinedDS
x = JoinedDS  db1 db2 -- where dbx is a datasource Databasex KeysOfDSx 
ValuesOfDSx

Now, I would want the user to be able to read both KeysOfDS1 (which 
would yield a ValuesOfDS1) as well as KeysOfDS2 (which would yield a 
ValuesOfDS2) from x.

Herefore, I need the instances mentioned before:
instance (Datasource l k v) = Datasource (JoinedDS l r) k v where
dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) = Datasource (JoinedDS l r) k v where
dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)
But this, thus, yields duplicate instance errors, which I don't like :-).
Robert
P.S. Sorry for any typos, I am enjoying a rather nice bottle of wine :-).
I am not sure whether you intended Datasources to contain 
heterogeneous key or value types, and whether the loolup is supposed 
to be value or type driven. My original answer assumed a single 
Datasource contains values of different types, selected by the type of 
the key...

   Keean.

Robert van Herk wrote:
Yes, but this is not what I want. I want to be able to give a key 
that either the left or the right data source would take, and then 
return the appropriate value. Thus: if I pass it a key that would 
normally go into l, I want the value l returns me to be returned, and 
if I pass it the key that would normally go into r, I want to return 
the value r returns me.

The datasource class has a function dsread :: ds - k - (ds, v) -- 
read may have a side effect
Thus I want want to do something like:
instance (Datasource l k v) = Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) = Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)

It would be perfectly okay to me when the compiler would complain if 
the key and value that go into l and r are the same, but for any 
useful purpose I can think of (e.g. glueing two database couplings 
together, since I also made a Datasource instance for database 
access), this will not happen and the duplicate instances should not 
really occur, since the context of the instances makes sure only 1 
will be possible.

However, GHC only looks at the RHS (thus: Datasource (JoinedDS l r) k 
v) and then decides that both instances are the same.

So, my question was: how to overcome this.
Thanks,
Robert


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


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Robert van Herk wrote:
Keean Schupke wrote:
Just thought I ought to point out that all this is only necessary if 
the datasources may return different types... If you want them to 
return the same type you only need:

instance (Datasource l k v,Datasource r k v) = Datasource (JoinedDS 
l r) k v ...

As both datasources have the same key and value types, you then 
choose which 'v' to return at the value level.

Nono, the datasources I have implemented are a type safe means to 
extract (key,value) pairs from a data store. The idea is that this 
way, in a type safe fashion, e.g. database access can be abstract.

I use HaskellDB as the database access layer, and then define a 
datasource instance for any given database, so that the user does not 
need to think about the details of the actual database access: he can 
just read and write from the datasource, and the datasource will make 
sure the actual queries will be executed.

My idea now was that if I have 2 databases, and I construct 
datasources for them, it would be really cool if I was able to unite 
them, so that the programmer in the end could talk two 1 datasource, 
that allowed for accessing the 2 databases at one entry point. This 
was what I was making the JoinedDS for.

So, suppose I have 2 datasources for two different databases. One may 
have keys:
data KeysOfDS1 = KDB1_Table1 Int
   |  KDB1_Table2 Int

and values
data ValuesOfDS1 = VDB1_Table1 (Int,Int,String)
   | VDB2_Table2 (Int,Int,String)
and the other one:
data KeysOfDS2 = KDB2_Table1 String
   |  KDB2_Table2 String
data ValuesOfDS2 = VDB2_Table1 (String, Float)
   | VDB2_Table2 (String, Float, Int)
Now, these datastructures correspond to the actual tables in the 
database. My toolset will generate datasources for these types, thus 
we have instances:

instance Datasource Database1 KeysOfDS1 ValuesOfDS1
instance Datasource Database2 KeysOfDS2 ValuesOfDS2
and the cool thing would be, to combine these two datasources at a 
higher level in my datasources graph, so that I would have 1 
datasource that found out by itself which actual datasource to use, thus:

x::JoinedDS
x = JoinedDS  db1 db2 -- where dbx is a datasource Databasex KeysOfDSx 
ValuesOfDSx

Now, I would want the user to be able to read both KeysOfDS1 (which 
would yield a ValuesOfDS1) as well as KeysOfDS2 (which would yield a 
ValuesOfDS2) from x.

Herefore, I need the instances mentioned before:
instance (Datasource l k v) = Datasource (JoinedDS l r) k v where
dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) = Datasource (JoinedDS l r) k v where
dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)
But this, thus, yields duplicate instance errors, which I don't like :-).
Robert
P.S. Sorry for any typos, I am enjoying a rather nice bottle of wine :-).
Thats because they overlap in 'k'. However you can change the fundep:
class Datasource s k v | s - k v
instance Datasource DB1 K1 V1
instance Datasource DB2 K2 V2
instance (Datasource l k' v',TypeEq k k' z,Datasource' z l r k v) = 
Datasource (JoinedDS l r) k v where

class Datasource' z l r k v | z l r - k v
instance Datasource l k v = Datasource' TTrue l r k v
instance Datasource r k v = Datasource' TFalse l r k v

Here I have used TypeEq from the HList library to determine if the type 
parameter k is the same type as the k' from datasource l. This lets k 
determine which instance from the other class gets used.

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


Re: [Haskell] The FunctorM library

2005-03-25 Thread Thomas Hallgren
Simon Peyton-Jones wrote:
| 
|  class Functor f where fmap :: ...
|  class Functor m = Monad m where
| ...the usual stuff...
| fmap = liftM
| 
It seems overkill to have a whole new language feature to deal with one
library issue. 

Perhaps it is...
For example, what if Functor T *is* defined explicitly, but in a later module?
 

I guess it would be the same as what happens now if you accidentally 
declare the same instance in different modules, i.e., the system would 
complain about overlapping instances.

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


[Haskell] Profiling strategies

2005-03-25 Thread Andreas Marth
Hallo!

Does anybody have some profiling strategies other than from the ghc user
guide?

Any references, suggestions and so on are very welcome.

Thanks,
Andreas

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


Re: [Haskell-cafe] Question on leazy evaluation

2005-03-25 Thread Pierre Barbier de Reuille
Still on the same subject, I solved one problem but don't really 
understand why it didn't work in the first place ! Although it seems to 
be a difference between newtype and data !

I have a newtype defined as :
data Fct s a = Fct (s - [a])
and a function defined by :
plus :: Fct a b - Fct a b - Fct a b
plus (Fct f1) (Fct f2) = Fct ( \ a - (f1 a) ++ (f2 a) )
For some reason, this function does not use leazy evaluation ! I can 
test it using :

test_fct :: Fct Int Int
test_fct = Fct( \ i - [i] )
value = head $ apply (foldr plus test_fct $ repeat test_fct) 12
... trying to get value does not terminate !
But if I change the type declaration into :
newtype Fct s a = Fct (s - [a])
... it works ! The plus function uses leazy evaluation and value can 
be computed.

Now, I didn't really understood the difference between newtype and data. 
Can anyone explain that behaviour ?

Thank you,
Pierre
--
Pierre Barbier de Reuille
INRA - UMR Cirad/Inra/Cnrs/Univ.MontpellierII AMAP
Botanique et Bio-informatique de l'Architecture des Plantes
TA40/PSII, Boulevard de la Lironde
34398 MONTPELLIER CEDEX 5, France
tel   : (33) 4 67 61 65 77fax   : (33) 4 67 61 56 68
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Question on leazy evaluation

2005-03-25 Thread Tomasz Zielonka
On Fri, Mar 25, 2005 at 03:13:48PM +0100, Pierre Barbier de Reuille wrote:
 plus :: Fct a b - Fct a b - Fct a b
 plus (Fct f1) (Fct f2) = Fct ( \ a - (f1 a) ++ (f2 a) )
 
 For some reason, this function does not use leazy evaluation ! I can 
 test it using :
 
 test_fct :: Fct Int Int
 test_fct = Fct( \ i - [i] )
 
 value = head $ apply (foldr plus test_fct $ repeat test_fct) 12
 
 ... trying to get value does not terminate !

That's because you pattern match on (Fct f2) in plus. If Fct is defined
with 'data', this causes the second argument of plus to be evaluated.

 But if I change the type declaration into :
 
 newtype Fct s a = Fct (s - [a])
 
 ... it works ! The plus function uses leazy evaluation and value can 
 be computed.

If Fct is defined with 'newtype', it doesn't cause evaluation, because
Fct is a kind of virtual / non-existent / zero-cost data constructor,
so there is nothing to evaluate.

Try these definitions:

plus (Fct f1) ~(Fct f2) = Fct ( \ a - (f1 a) ++ (f2 a) )

plus (Fct f1) f2 = Fct ( \ a - (f1 a) ++ (apply f2 a) )

The first uses an irrefutable pattern, the second doesn't pattern
match on Fct in the second argument.

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