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
-- dependences in a new class definition,
so that my first attempt
-- at a definition of class Divide
works.