[Haskell-cafe] Re: Why can't Haskell be faster?

2007-10-31 Thread Jeff . Harper
Peter Hercek wrote:
 * it is easy to mark stuff strict (even in function signatures
  etc), so it is possible to save on unnecessary CAF creations

Also, the Clean compiler has a strictness analyzer.  The compiler will 
analyze code and find many (but not all) cases where a function argument 
can be made strict without changing the behavior of the program.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Inferring types from functional dependencies

2006-06-16 Thread Jeff . Harper

Thank you. I followed your suggestion
and implemented my default Divide as you've shown below.

[EMAIL PROTECTED] wrote:
 If we assume that we need Reciprocate
only if we are going to use the 
 'default' method, the solution becomes obvious. It does involve
 overlapping and undecidable instances, sorry. These extensions are
 really useful in practice. Here's the solution:
 
  class Divide a b c | a b - c where
(/) :: a - b - c
 
 
 Here's the most general instance. It applies when nothing more
 specific does. It is in this case that we insist on being able
to
 take the reciprocal:
 
  instance (Reciprocate b recip, Multiply a recip c) =
Divide a b c where
(/) x y = x * (recip y)

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


[Haskell-cafe] Inferring types from functional dependencies

2006-06-09 Thread Jeff . Harper

The following message is in a Haskell
module. It will be easier to read in a fixed point font.

{-# OPTIONS -fglasgow-exts #-}

-- Hi,
-- 
-- I ran into an issue while working
with functional dependencies.
-- Consider the following code. I'm
rewriting many of the prelude
-- operators using functional dependencies.
The type of he return value
-- is determined by the operators parameters.


-- Use P. in front of functions
to access the preludes version of these 
-- functions.
import qualified Prelude as P 

-- I override prelude operators with
my own operators.
import Prelude hiding ( (*), recip
)

import Ratio

-- recip returns the reciprocal of
its parameter. I've given the 
-- Reciprocate class the ability to
return a type that is different from 
-- its argument.

class Reciprocate a b | a - b where
  recip :: a -
b

-- Here are some example instances
of Reciprocate. In most cases,
-- recip will return the same type
as it's argument. However, taking
-- the reciprocal of an Integer returns
a (Ratio Integer).

instance Reciprocate Double Double
where
  recip = P.recip
-- I call prelude's recip here.

instance Reciprocate (Ratio Integer)
(Ratio Integer) where
  recip = P.recip
-- I call prelude's recip here.

instance Reciprocate Integer (Ratio
Integer) where
  recip x = (1::Integer)
% x



-- (*) multiplies its parameters. The
resulting type is determined by
-- the type of the arguments

class Multiply a b c | a b -
c where
  (*) :: a - b -
c

-- Here are some example instances
of Multiply.

instance Multiply Double Double Double
where
  (*) = (P.*)

-- Multiplying Integer by Double returns
a Double

instance Multiply Integer Double Double
where
  (*) x y = (P.*) (fromIntegral
x) y

instance Multiply Double Integer Double
where
  (*) x y = (P.*) x (fromIntegral
y)

instance Multiply Integer (Ratio Integer)
(Ratio Integer) where
  (*) x y = (P.*) (x%1)
y

-- Now, this is where I ran into some
trouble I define a Divide class
-- as follows. Here I define
a default (/) operator that uses the
-- Reciprocate and Multiply class to
perform division. However, this code
-- produces error messages. So,
I commented it out. Even if I don't want
-- to implement (/) with recip and
(*), requiring this relationship --
-- 
  
  
 |
-- 
 --
-- 
 |
-- 
 v 
   is consistent with defining
--   _
 the divide operation in
--   |   
  
|  terms of the multiplicative
--   |   
  
|  inverse
{-
class (Reciprocate b recip, Multiply
a recip c) = Divide a b c | a b - c where
  (/) :: a - b -
c
  (/) x y = x * (recip
y)
-}

-- This definition of (/) works. However,
taking the reciprocal and then 
-- multiplying may not always be the
best way of dividing. So, I'd like to
-- put this into a divide class, so
(/) can be defined differently for
-- different types.
{-

(/) :: (Reciprocate b recip, Multiply
a recip c) = a - b - c
(/) a b = a * (recip b)

-}

-- I finally discovered that the following
definition of a Divide 
-- class works
class (Reciprocate b recip_of_b, Multiply
a recip_of_b c) 

   = Divide a b c recip_of_b | a b - c
recip_of_b where
  (/) :: a - b -
c
  (/) a b = a * (recip
b) -- Default definition can be overridden


-- The thing I don't like is that when
defining a new Divide class, I have
-- to place the reciprocal of the b
type into the class definition.

-- Here are some examples of Divide:
--
-- This type 
-- must be the type that is 
 |
-- returned when this  
   |
-- type --  
|
-- is passed to recip.  | 
 |
-- 
  |
  |
-- 
  v
  v
instance Divide Double Double Double
Double where
 (/) x y = (P./) x y --
For Doubles

-- Another example:
--
-- This type --
-- must be the type that is 
  
 |
-- returned when this  
  
   |
-- type --- 
  
 |
-- is passed to recip.  |
  
  |
-- 
  |   
  |
-- 
  v   
  v
instance Divide Integer Integer (Ratio
Integer) (Ratio Integer) where
 (/) x y = x % y

-- The reason I don't like it is there
is enough information available to infer
-- the type of recip_of_b in the following
class. The Reciprocate class is 
-- defined with functional dependencies,
so that recip_of_b can be determined
-- by the type of b.--
-- 
|
-- 
 __
-- 
| 
 |
--
--   class (Reciprocate
b recip_of_b, Multiply a recip_of_b c) 
-- 
 = Divide a b c recip_of_b
| a b - c recip_of_b where
-- (/)
:: a - b - c
-- (/)
a b = a * (recip b)
--


-- Respecifying the recip_of_b when
I declare an instance of Divide
-- seem redundant. I'm wondering
if there is a better way to
-- define this. I also, wonder
if it would be appropriate to include
-- in future versions of Haskell, the
ability to infer functional

[Haskell-cafe] Dropping trailing nulls from a list of list

2006-03-08 Thread Jeff . Harper

Today, I reviewed a function I wrote
a few months ago. The function, dropTrailNulls, takes a list of lists
and drops trailing null lists. For instance:

*Main dropTrailNulls [[1],[2,3],[],[]]
[[1],[2,3]]

My original implementation was terrible.
It was recursive, overly bulky, and difficult to understand. It
embarrasses me. I won't post it here.

Today, it occurred to me this would
do the trick:

dropTrailNulls list = reverse (dropWhile
null (reverse list))

The problem is 20 years of experience
writing efficient imperative programs says to me, You don't drop
things off the end of a structure by reversing the structure, dropping
stuff from the beginning, then reversing again. I suspect this
imperative bias prevented me from coming up with the simple solution when
I first wrote my function.

On the other hand, it is conceivable
to me that my new implementation may actually be relatively efficient since
Haskell uses lazy evaluation, and Haskell lists are constructed from the
tail to the beginning.

I'm sure there are many problems that
are encountered in Haskell where it is necessary to operate on the end
of a list. So, I'm wondering if the idiom, reverse, operate, then
reverse is something I should add to my toolbox. Or, is there a more
efficient idiom for addressing these problems?___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Overlapping instance problem

2006-02-13 Thread Jeff . Harper

Hi,

I've posted a couple messages to the
Haskell Cafe in the last few months. I'm new to Haskell. But,
I've set out to implement my own vectors, matrices, complex numbers, etc.

One goal I have, is to overload operators
to work with my new types. The pursuit of this goal, has pushed me
to learn a lot about the
Haskell type system. When I get stuck
from time-to-time, the kind folks on this list have pointed me in the right
direction.

I'm stuck now. One thing I want
to avoid is adding new multiplication operators to handle multiplication
of dissimilar types. For instance, I'd like to be able to have an
_expression_ like k * m where k is a Double and m is a Matrix. This
doesn't work with the prelude's (*) operator because the prelude's (*)
has signature:

(*) :: (Num a) = a - a -
a.

To get around this, I wrote my own versions
of a Multiply class that allows dissimilar types to be multiplied. You
can see my Multiply class in the module at the end of this Email.

At the bottom of the module, I've attempted
to implement multiplication of the forms:

scalar * matrix
matrix * scalar
matrix * matrix

The problem is that when I try to do
matrix * matrix at the interpreter, I get an error message from Glaskgow:

*My_matrix m1 * m2

interactive:1:3:
  Overlapping instances
for Multiply (Matrix Double) (Matrix Double) (Matrix c)
   arising from use
of `*' at interactive:1:3
  Matching instances:
   My_matrix.hs:63:0:
instance
(Multiply a b c, Add c c c, Num a, Num b, Num c) =
 
  Multiply (Matrix a) (Matrix b) (Matrix c)
   My_matrix.hs:57:0:
instance
(Multiply a b c, Num a, Num b, Num c) =
 
  Multiply (Matrix a) b (Matrix c)
   My_matrix.hs:51:0:
instance
(Multiply a b c, Num a, Num b, Num c) =
 
  Multiply a (Matrix b) (Matrix c)
  In the definition of `it':
it = m1 * m2


I don't understand how m1 * m2 can match
the scalar multiplication instances. For instance, the scalar * matrix
instance has signature:

instance (Multiply a b c, Num a, Num
b, Num c) 
 
 =
Multiply a (Matrix b) (Matrix c) where

m1 in my _expression_ would correspond
to the 'a' type variable. But, 'a' is constrained to be a Num. However,
I never made my Matrix type an instance of Num.

Is there a work around for this? In
my first implementation, I did not have the Num constraints in the matrix
Multiply instances. I added the Num constraints specifically, to
remove the ambiguity of the overlapping instance. Why didn't this
work?

Thanks,

Jeff Harper

 Begining of code for My_matrix.hs
--

{-# OPTIONS -fglasgow-exts #-}


module My_matrix where

import qualified Prelude as P
import Prelude hiding ( (*), (+), (-),
negate)

default ( )

class Add a b c | a b - c
where
  (+) :: a - b -
c

class Multiply a b c | a b -
c where
  (*) :: a - b -
c

class Coerce a b where
  coerce :: a - b

infixl 7 *
infixl 6 +

instance Coerce Float Float where {
coerce x = x }
instance Coerce Float Double where {
coerce x = realToFrac x }
instance Coerce Double Double where
{ coerce x = x }

instance Add Float Float Float where
{ (+) x y = ( x) P.+ ( y) }
instance Add Float Double Double where
{ (+) x y = (coerce x) P.+ ( y) }
instance Add Double Float Double where
{ (+) x y = ( x) P.+ (coerce y) }
instance Add Double Double Double where
{ (+) x y = ( x) P.+ ( y) }

instance Multiply Float Float Float
where { (*) x y = ( x) P.* ( y) }
instance Multiply Float Double Double
where { (*) x y = (coerce x) P.* ( y) }
instance Multiply Double Float Double
where { (*) x y = ( x) P.* (coerce y) }
instance Multiply Double Double Double
where { (*) x y = ( x) P.* ( y) }


-- Matrices are stored in a list of
list. For now, I can create a
-- matrix of Float, or Double. Later,
I'd like to extend this and
-- make it possible to create a matrix
of other number types. For
-- instance, it might be possible to
have a matrix of complex or
-- imaginary numbers.

data Matrix a = Matrix [[a]] deriving
Show

-- For simplicity, the instances below
omit the implementation for (*).

-- This instance of Multiply is for
doing multiplication of the form
-- k * m where k is a scalar and m is
a matrix.

instance (Multiply a b c, Num a, Num
b, Num c) = Multiply a (Matrix b) (Matrix c) where
  (*) x y = Matrix [[]]

-- This instance of Multiply is for
doing multiplication of the form
-- m * k where k is a scalar and m is
a matrix.

instance (Multiply a b c, Num a, Num
b, Num c) = Multiply (Matrix a) b (Matrix c) where
  (*) x y = Matrix [[]]

-- This instance of Multiply is for
doing multiplication of the form
-- m1 * m2 where m1 and m2 are both
matrices

instance (Multiply a b c, Add c c c,
Num a, Num b, Num c) = Multiply (Matrix a) (Matrix b) (Matrix c) where
  (*) x y = Matrix [[]]

-- Some test variables to use in the
interpreter

k = (3.0::Double)
m1 = Matrix [[1.0::Double]]
m2 = Matrix [[2.0::Double]]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http

[Haskell-cafe] Re: Haskell-Cafe Digest, Vol 29, Issue 36

2006-01-13 Thread Jeff . Harper


Christian Maeder wrote:
 Jared Updike wrote:
  http://www.haskell.org/onlinereport/decls.html#default-decls
  http://www.haskell.org/tutorial/numbers.html#sect10.4
 
 I still don't see, why it works for show but not for my_show.
 
  On 1/12/06, [EMAIL PROTECTED] [EMAIL PROTECTED]
wrote:
 [...]
  class (Show a) = My_show a where
   my_show :: a - String
 
 If I let this be
 
  class My_show a where
my_show :: a - String
 
  instance My_show Int where
   my_show a = show a ++  :: Int
 
  instance My_show Integer where
   my_show a = show a ++  :: Integer
 
 What is the difference to the builtin Show class?

I was wondering the same thing myself. Then,
I reread the online Haskell report link. 

From http://www.haskell.org/onlinereport/decls.html#default-decls:
where n=0, and each ti must be a type for which
Num ti holds. In situations where an ambiguous type is discovered, an ambiguous
type variable, v, is defaultable if: 
  o v appears only in constraints
of the form C v, where C is a class, and 
  o at least one of these classes
is a numeric class, (that is, Num or a subclass of Num), and 
  o all of these classes are defined
in the Prelude or a standard library (Figures 6.2--6.3, pages -- show the
numeric classes, and Figure 6.1, page , shows the classes defined in the
Prelude.) 

Notice the last bullet item. class Show is part of the Prelude. However,
class My_show is not part of the prelude. AS far as I can tell, that's
the only reason my_show 1 produces errors while show
1 is okay. ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] What does the Haskell type system do with show (1+2)?

2006-01-12 Thread Jeff . Harper

What does the Haskell type system do
with expressions such as these . . . ?
 show 1
 show (1+2)

The type of the subexpressions 1
and 1+2 are ambiguous since they have type (Num
a) = a. I'm under the assumption before 1+2
is evaluated, the 1 and 2 must be coerced into
a concrete type such as Int, Integer, Double, etc, and before
show 1 is evaluated, the 1 must be coerced into
a concrete type. Is my assumption correct? If so,
how does Haskell know into which type to coerce the subexpressions?

If I try to write a new function, my_show,
which converts an _expression_ into a string representation that includes
type information, I run into errors with expressions like show 1
and show (1+2) because of the type ambiguity.

class (Show a) = My_show a where
 my_show :: a - String

instance My_show Int where
 my_show a = show a ++ 
:: Int

instance My_show Integer where
 my_show a = show a ++ 
:: Integer

I can avoid the errors if I change it
to my_show (1::Int) or my_show ((1+2)::Int). I'm
wondering what the difference is between, my_show and Haskell's built-in
show that causes my_show to produce an error message when it is used with
ambiguous types, but Haskell's show works okay with ambiguous types.



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


[Haskell-cafe] Question about classes from a Haskell newbie.

2005-05-23 Thread Jeff . Harper

Hi,

I'm new to Haskell and even newer to
this list.  I have over 20 years of experience in C or C++.

For fun, I decided to write a Fourier
transform in Haskell. It would be convenient if I had a function
that converts any real or complex number into a complex number. My
attempt at doing this is below. Hugs produces errors when I try to
load this code.

Essentially, I'm trying to define a
class called ConvertibleToComplex. There is a function in this class
called toComplex. toComplex has the type:

class ConvertibleToComplex a where
 toComplex :: RealFloat
b = a - Complex b

I'd like some instances of toComplex
to return a Complex Double while other instances return a Complex Float.
Doing this sort of thing in C++ is fairly easy. However, I
get the feeling that I'm pushing the Haskell type system to do something
it isn't designed to do. Is there a way to define ConvertibleToComplex
so that toComplex's return type is generic and a particular instance of
ConvertibleToComplex decides what the return type is?

Here is my attempt at doing this. If
someone can give me some pointers on how to make this work, I'd appreciate
it.


module Main where

import Complex


-- toComplex should convert a real or
complex number to a complex number.
--
-- Here's my goal for the type of toComplex.
Given:
-- f :: Float
-- d :: Double
-- cf :: Complex Float
-- cd :: Complex Double
--
-- When toComplex is applied to these,
I'd like it to evaluate to the 
-- following types:
--
-- toComplex f :: Complex Float
-- toComplex d :: Complex Double
-- toComplex cf :: Complex Float
-- toComplex cd :: Complex Double


class ConvertibleToComplex a where
 toComplex :: RealFloat
b = a - Complex b
 
-- If I uncomment the following code,
Hugs produces errors:
-- ERROR c:\tmp\test2.hs:29
- Inferred type is not general enough
-- *** _expression_  : toComplex
-- *** Expected type : (ConvertibleToComplex
Float, RealFloat a) = Float - Complex a
-- *** Inferred type : (ConvertibleToComplex
Float, RealFloat Float) = Float - Complex Float   
  
  
  

{-
instance ConvertibleToComplex Float
where
toComplex
f = f :+ 0

instance ConvertibleToComplex Double
where
toComplex
d = d :+ 0

instance ConvertibleToComplex (Complex
a) where
toComplex
c = c
-}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe