liboleg-2010.1.9.0: An evolving collection of Oleg Kiselyov's Haskell modules

Data.Class1

Description

Haskell with only one typeclass

http://okmij.org/ftp/Haskell/Haskell1/Class1.hs

http://okmij.org/ftp/Haskell/types.html#Haskell1

How to make ad hoc overloading less ad hoc while defining no type classes. For clarity, we call as Haskell1 the language Haskell98 with no typeclass declarations but with a single, pre-defined typeclass C (which has two parameters related by a functional dependency). The programmers may not declare any typeclasses; but they may add instances to C and use them. We show on a series of examples that despite the lack of typeclass declarations, Haskell1 can express all the typeclass code of Haskell98 plus multi-parameter type classes and even some (most useful?) functional dependencies.

Haskell1 is not a new language and requires no new compilers; rather, it is a subset of the current Haskell. The removal of typeclass declarations is merely the matter of discipline.

Synopsis

Documentation

class C l t | l -> t whereSource

The one and only type class present in Haskell1

Methods

ac :: l -> tSource

Instances

C (MinBound Bool) Bool 
C (MinBound Int) Int 
(C (Add a) (a -> a -> a), C (Mul a) (a -> a -> a), C (FromInteger a) (Integer -> a), C (SHOW a) (a -> String)) => C (CLS (NUM a)) (NUM a) 
C (SHOW Float) (Float -> String) 
C (SHOW Int) (Int -> String) 
C (SHOW a) (a -> String) => C (SHOW (Maybe a)) (Maybe a -> String)

An example of using monads and other overloaded functions

C (SHOW a) (a -> String) => C (SHOW (Dual a)) (Dual a -> String) 
C (FromInteger Float) (Integer -> Float) 
C (FromInteger Int) (Integer -> Int)

fromInteger conversion This numeric operation is different from the previous in that the overloading is resolved on the result type only. The function read is another example of such a producer

C (FromInteger a) (Integer -> a) => C (FromInteger (Dual a)) (Integer -> Dual a) 
C (Mul Float) (Float -> Float -> Float) 
C (Mul Int) (Int -> Int -> Int)

The following test uses the previously defined +$ operation, which now accounts for duals automatically. As in Haskell98, our overloaded functions are extensible.

Likewise define the overloaded multiplication

(C (Add a) (a -> a -> a), C (Mul a) (a -> a -> a)) => C (Mul (Dual a)) (Dual a -> Dual a -> Dual a) 
C (Add Float) (Float -> Float -> Float)

Let's define the addition for floats

C (Add Int) (Int -> Int -> Int) 
C (Add a) (a -> a -> a) => C (Add (Dual a)) (Dual a -> Dual a -> Dual a)

We define the addition of Duals inductively, with the addition over base types as the base case. We could have eliminated the mentioning (a->a->a) and replaced with some type t. But then we would need the undecidable instance extension...

C (Index Bool) ((Int, Integer) -> Int -> Bool) 
C (Index Char) (String -> Int -> Char) 
(C (Index a) (ara -> Int -> a), C (Index b) (arb -> Int -> b)) => C (Index (a, b)) ((ara, arb) -> Int -> (a, b)) 
C (FromList Bool) (Int -> [Bool] -> (Int, Integer)) 
C (FromList Char) (Int -> [Char] -> String) 
(C (FromList a) (Int -> [a] -> ara), C (FromList b) (Int -> [b] -> arb)) => C (FromList (a, b)) (Int -> [(a, b)] -> (ara, arb)) 
C (ERROR String) (String -> String) 
C (RET (Either e) a) (a -> Either e a) 
C (RET Maybe a) (a -> Maybe a) 
C (CatchError (Either e) a) (Either e a -> (e -> Either e a) -> Either e a) 
C (ThrowError (Either e) a) (e -> Either e a) 
C (BIND (Either e) a b) (Either e a -> (a -> Either e b) -> Either e b) 
C (BIND Maybe a b) (Maybe a -> (a -> Maybe b) -> Maybe b) 
TypeCast (FC3 Bool b c) (FC3 Bool Char Int) => C (FC3 Bool b c) (Bool -> Char -> Int) 
TypeCast c Int => C (FC2 Bool Char c) (Bool -> Char -> Int) 
C (FC1 Bool Char Int) (Bool -> Char -> Int) 

data Add a Source

Example 1: Building overloaded numeric functions, the analogue of Num. The following defines overloaded numeric functions `a la carte'. We shall see how to bundle such methods into what Haskell98 calls classes

Instances

C (Add Float) (Float -> Float -> Float)

Let's define the addition for floats

C (Add Int) (Int -> Int -> Int) 
C (Add a) (a -> a -> a) => C (Add (Dual a)) (Dual a -> Dual a -> Dual a)

We define the addition of Duals inductively, with the addition over base types as the base case. We could have eliminated the mentioning (a->a->a) and replaced with some type t. But then we would need the undecidable instance extension...

data Mul a Source

Instances

C (Mul Float) (Float -> Float -> Float) 
C (Mul Int) (Int -> Int -> Int)

The following test uses the previously defined +$ operation, which now accounts for duals automatically. As in Haskell98, our overloaded functions are extensible.

Likewise define the overloaded multiplication

(C (Add a) (a -> a -> a), C (Mul a) (a -> a -> a)) => C (Mul (Dual a)) (Dual a -> Dual a -> Dual a) 

data FromInteger a Source

Instances

C (FromInteger Float) (Integer -> Float) 
C (FromInteger Int) (Integer -> Int)

fromInteger conversion This numeric operation is different from the previous in that the overloading is resolved on the result type only. The function read is another example of such a producer

C (FromInteger a) (Integer -> a) => C (FromInteger (Dual a)) (Integer -> Dual a) 

(+$) :: forall a. C (Add a) (a -> a -> a) => a -> a -> aSource

We can now define the generic addition. We use the operation +$ to avoid the confusion with Prelude.(+)

In H98, the overloaded addition was a method. In Haskell1, it is an ordinary (bounded polymorphic) function The signature looks a bit ugly; we'll see how to simplify it a bit

data Dual a Source

We now illustrate overloading over datatypes other than basic ones. We define dual numbers (see Wikipedia)

Constructors

Dual a a 

Instances

Show a => Show (Dual a) 
C (SHOW a) (a -> String) => C (SHOW (Dual a)) (Dual a -> String) 
C (FromInteger a) (Integer -> a) => C (FromInteger (Dual a)) (Integer -> Dual a) 
(C (Add a) (a -> a -> a), C (Mul a) (a -> a -> a)) => C (Mul (Dual a)) (Dual a -> Dual a -> Dual a) 
C (Add a) (a -> a -> a) => C (Add (Dual a)) (Dual a -> Dual a -> Dual a)

We define the addition of Duals inductively, with the addition over base types as the base case. We could have eliminated the mentioning (a->a->a) and replaced with some type t. But then we would need the undecidable instance extension...

mul_sig :: a -> a -> aSource

Here is a different, perhaps simpler, way of defining signatures of overloaded functions. The constraint C is inferred and no longer has to be mentioned explicitly

mul_as :: a -> Mul aSource

frmInteger :: forall a. C (FromInteger a) (Integer -> a) => Integer -> aSource

and the corresponding overloaded function (which in Haskell98 was a method) Again, we chose a slightly different name to avoid the confusion with the Prelude

data SHOW a Source

We can define generic function at will, using already defined overloaded functions. For example,

Instances

C (SHOW Float) (Float -> String) 
C (SHOW Int) (Int -> String) 
C (SHOW a) (a -> String) => C (SHOW (Maybe a)) (Maybe a -> String)

An example of using monads and other overloaded functions

C (SHOW a) (a -> String) => C (SHOW (Dual a)) (Dual a -> String) 

shw :: forall a. C (SHOW a) (a -> String) => a -> StringSource

data MinBound a Source

Finally, we demonstrate overloading of non-functional values, such as minBound and maxBound. These are not methods in the classical sense.

Instances

mnBound :: forall a. C (MinBound a) a => aSource

data RET m a Source

We are defining a super-set of monads, so called `restricted monads'. Restricted monads include all ordinary monads; in addition, we can define a SET monad. See http://okmij.org/ftp/Haskell/types.html#restricted-datatypes

Instances

C (RET (Either e) a) (a -> Either e a) 
C (RET Maybe a) (a -> Maybe a) 

data BIND m a b Source

Instances

C (BIND (Either e) a b) (Either e a -> (a -> Either e b) -> Either e b) 
C (BIND Maybe a b) (Maybe a -> (a -> Maybe b) -> Maybe b) 

ret :: forall m a. C (RET m a) (a -> m a) => a -> m aSource

bind :: forall m a b. C (BIND m a b) (m a -> (a -> m b) -> m b) => m a -> (a -> m b) -> m bSource