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

Control.Poly2

Description

Type-class overloaded functions: second-order typeclass programming with backtracking

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

Synopsis

Documentation

type Fractionals = Float :*: (Double :*: HNil)Source

The classes of types used in the examples below

data OpenEqs Source

The Fractionals, Nums and Ords above are closed. But Eqs is open (i.e., extensible), due to the following:

Instances

data RusselC Source

Why we call Nums etc. a type class rather than a type set? The following does not work: type synonyms can't be recursive.

 type Russel = AllOfBut () Russel :*: HNil

But the more elaborate version does, with the expected result:

Instances

data AllOf x Source

Instances

(Apply (Member h) x bf, MemApp bf t x r) => Apply (Member (:*: (AllOf h) t)) x r 

data AllOfBut x y Source

Instances

(Apply (Member exc) x bf, Apply (MemCase2 h t x) bf r) => Apply (Member (:*: (AllOfBut h exc) t)) x r 

data TypeCl x Source

Instances

TypeCls l x r => Apply (Member (TypeCl l)) x r 

class TypeCls l x r | l x -> rSource

Classifies if the type x belongs to the open class labeled l The result r is either HTrue or HFalse

Instances

TypeCast r HFalse => TypeCls l x r

the default instance: x does not belong

Apply (Member Russel) x r => TypeCls RusselC x r 
TypeCls OpenEqs () HTrue 

data Member tl Source

Deciding the membership in a closed class, specified by enumeration, union and difference

Instances

GFN Z IsAnEq a (Member Eqs)

Each case of a 2-poly function is defined by two instances, of GFN and or Apply classes.

GFN Z ApproxEq' (x, x) (PairOf (Member Nums)) 
GFN Z ApproxEq (x, x) (PairOf (Member Fractionals)) 
(TypeEq h x bf, MemApp bf t x r) => Apply (Member (:*: h t)) x r 
(Apply (Member exc) x bf, Apply (MemCase2 h t x) bf r) => Apply (Member (:*: (AllOfBut h exc) t)) x r 
(Apply (Member h) x bf, MemApp bf t x r) => Apply (Member (:*: (AllOf h) t)) x r 
Apply (Member HNil) x HFalse 
TypeCls l x r => Apply (Member (TypeCl l)) x r 
GFN (S (S (S Z))) ApproxEq ((x, x), (x, x)) (PairOf (PairOf (Member Nums))) 
GFN (S (S Z)) ApproxEq (x, x) (PairOf (Member Eqs)) 
GFN (S Z) ApproxEq' (x, x) (PairOf (Member Fractionals)) 
GFN (S Z) ApproxEq (x, x) (PairOf (Member Nums)) 

class MemApp bf t x r | bf t x -> rSource

Instances

Apply (Member t) x r => MemApp HFalse t x r 
MemApp HTrue t x HTrue 

data MemCase2 h t x Source

we avoid defining a new class like MemApp above. I guess, after Apply, we don't need a single class ever?

Instances

Apply (Member (:*: (AllOf h) t)) x r => Apply (MemCase2 h t x) HFalse r 
Apply (Member t) x r => Apply (MemCase2 h t x) HTrue r 

class GFN n f a pred | n f a -> predSource

A type class for instance guards and back-tracking Here, pred and f are labels and n is of a kind numeral.

Instances

TypeCast pred Otherwise => GFN n ApproxEq' a pred 
TypeCast pred Otherwise => GFN n ApproxEq a pred 
TypeCast pred Otherwise => GFN n IsAnEq a pred

the default instance

GFN Z IsAnEq a (Member Eqs)

Each case of a 2-poly function is defined by two instances, of GFN and or Apply classes.

GFN Z ApproxEq' (x, x) (PairOf (Member Nums)) 
GFN Z ApproxEq (x, x) (PairOf (Member Fractionals)) 
GFN (S Z) IsAnEq (x, y) Otherwise

Augment the above function, to test for pairs of Eqs We could have added an instance to TypeCls OpenEqs above. But we wish to show off the recursive invocation of a second-order polymorphic function

GFN (S (S (S Z))) ApproxEq ((x, x), (x, x)) (PairOf (PairOf (Member Nums))) 
GFN (S (S Z)) ApproxEq (x, x) (PairOf (Member Eqs)) 
GFN (S Z) ApproxEq' (x, x) (PairOf (Member Fractionals)) 
GFN (S Z) ApproxEq (x, x) (PairOf (Member Nums)) 

data Otherwise Source

The guard that always succeeds (cf. otherwise in Haskell)

Instances

Apply Otherwise a HTrue 
GFN (S Z) IsAnEq (x, y) Otherwise

Augment the above function, to test for pairs of Eqs We could have added an instance to TypeCls OpenEqs above. But we wish to show off the recursive invocation of a second-order polymorphic function

newtype GFn f Source

Constructors

GFn f 

Instances

(GFN Z f a pred, Apply pred a flag, Apply (GFnTest Z f flag) a b) => Apply (GFn f) a b 

newtype GFnA n f Source

Constructors

GFnA f 

Instances

Apply (GFnA n ApproxEq') a Bool 
Apply (GFnA n ApproxEq) a Bool 
Apply (GFnA n IsAnEq) a Bool 
Apply (GFnA Z IsAnEq) a Bool 
(Apply (GFn ApproxEq) (x, x) Bool, Eq x) => Apply (GFnA (S (S (S Z))) ApproxEq) ((x, x), (x, x)) Bool 
Eq x => Apply (GFnA (S (S Z)) ApproxEq) (x, x) Bool 
(Fractional x, Ord x) => Apply (GFnA (S Z) ApproxEq') (x, x) Bool 
(Num x, Ord x) => Apply (GFnA (S Z) ApproxEq) (x, x) Bool 
(Apply (GFn IsAnEq) x Bool, Apply (GFn IsAnEq) y Bool) => Apply (GFnA (S Z) IsAnEq) (x, y) Bool 
(Num x, Ord x) => Apply (GFnA Z ApproxEq') (x, x) Bool 
(Fractional x, Ord x) => Apply (GFnA Z ApproxEq) (x, x) Bool 

newtype GFnTest n f flag Source

Constructors

GFnTest f 

Instances

(GFN (S n) f a pred, Apply pred a flag, Apply (GFnTest (S n) f flag) a b) => Apply (GFnTest n f HFalse) a b 
Apply (GFnA n f) a b => Apply (GFnTest n f HTrue) a b 

data IsAnEq Source

A generic function that tests if its argument is a member of Eqs

Constructors

IsAnEq 

Instances

TypeCast pred Otherwise => GFN n IsAnEq a pred

the default instance

GFN Z IsAnEq a (Member Eqs)

Each case of a 2-poly function is defined by two instances, of GFN and or Apply classes.

GFN (S Z) IsAnEq (x, y) Otherwise

Augment the above function, to test for pairs of Eqs We could have added an instance to TypeCls OpenEqs above. But we wish to show off the recursive invocation of a second-order polymorphic function

Apply (GFnA n IsAnEq) a Bool 
Apply (GFnA Z IsAnEq) a Bool 
(Apply (GFn IsAnEq) x Bool, Apply (GFn IsAnEq) y Bool) => Apply (GFnA (S Z) IsAnEq) (x, y) Bool 

data PairOf t Source

The main test: approximate equality. See the article for the description.

Instances

GFN Z ApproxEq' (x, x) (PairOf (Member Nums)) 
GFN Z ApproxEq (x, x) (PairOf (Member Fractionals)) 
TypeCast r HFalse => Apply (PairOf t) x r 
GFN (S (S (S Z))) ApproxEq ((x, x), (x, x)) (PairOf (PairOf (Member Nums))) 
GFN (S (S Z)) ApproxEq (x, x) (PairOf (Member Eqs)) 
GFN (S Z) ApproxEq' (x, x) (PairOf (Member Fractionals)) 
GFN (S Z) ApproxEq (x, x) (PairOf (Member Nums)) 
Apply t x r => Apply (PairOf t) (x, x) r 

data ApproxEq Source

Constructors

ApproxEq 

Instances

TypeCast pred Otherwise => GFN n ApproxEq a pred 
GFN Z ApproxEq (x, x) (PairOf (Member Fractionals)) 
GFN (S (S (S Z))) ApproxEq ((x, x), (x, x)) (PairOf (PairOf (Member Nums))) 
GFN (S (S Z)) ApproxEq (x, x) (PairOf (Member Eqs)) 
GFN (S Z) ApproxEq (x, x) (PairOf (Member Nums)) 
Apply (GFnA n ApproxEq) a Bool 
(Apply (GFn ApproxEq) (x, x) Bool, Eq x) => Apply (GFnA (S (S (S Z))) ApproxEq) ((x, x), (x, x)) Bool 
Eq x => Apply (GFnA (S (S Z)) ApproxEq) (x, x) Bool 
(Num x, Ord x) => Apply (GFnA (S Z) ApproxEq) (x, x) Bool 
(Fractional x, Ord x) => Apply (GFnA Z ApproxEq) (x, x) Bool 

data ApproxEq' Source

Constructors

ApproxEq' 

Instances

TypeCast pred Otherwise => GFN n ApproxEq' a pred 
GFN Z ApproxEq' (x, x) (PairOf (Member Nums)) 
GFN (S Z) ApproxEq' (x, x) (PairOf (Member Fractionals)) 
Apply (GFnA n ApproxEq') a Bool 
(Fractional x, Ord x) => Apply (GFnA (S Z) ApproxEq') (x, x) Bool 
(Num x, Ord x) => Apply (GFnA Z ApproxEq') (x, x) Bool 

data HNil Source

Constructors

HNil 

Instances

data a :*: b Source

Constructors

a :*: b 

Instances

(TypeEq h x bf, MemApp bf t x r) => Apply (Member (:*: h t)) x r 
(Apply (Member exc) x bf, Apply (MemCase2 h t x) bf r) => Apply (Member (:*: (AllOfBut h exc) t)) x r 
(Apply (Member h) x bf, MemApp bf t x r) => Apply (Member (:*: (AllOf h) t)) x r 

data HTrue Source

Instances

Apply Otherwise a HTrue 
TypeEq x x HTrue 
TypeCls OpenEqs () HTrue 
MemApp HTrue t x HTrue 
Apply (GFnA n f) a b => Apply (GFnTest n f HTrue) a b 
Apply (Member t) x r => Apply (MemCase2 h t x) HTrue r 

data HFalse Source

Instances

Apply (Member t) x r => MemApp HFalse t x r 
Apply (Member HNil) x HFalse 
(GFN (S n) f a pred, Apply pred a flag, Apply (GFnTest (S n) f flag) a b) => Apply (GFnTest n f HFalse) a b 
Apply (Member (:*: (AllOf h) t)) x r => Apply (MemCase2 h t x) HFalse r 

data Z Source

Constructors

Z 

Instances

GFN Z IsAnEq a (Member Eqs)

Each case of a 2-poly function is defined by two instances, of GFN and or Apply classes.

GFN Z ApproxEq' (x, x) (PairOf (Member Nums)) 
GFN Z ApproxEq (x, x) (PairOf (Member Fractionals)) 
GFN (S Z) IsAnEq (x, y) Otherwise

Augment the above function, to test for pairs of Eqs We could have added an instance to TypeCls OpenEqs above. But we wish to show off the recursive invocation of a second-order polymorphic function

GFN (S (S (S Z))) ApproxEq ((x, x), (x, x)) (PairOf (PairOf (Member Nums))) 
GFN (S (S Z)) ApproxEq (x, x) (PairOf (Member Eqs)) 
GFN (S Z) ApproxEq' (x, x) (PairOf (Member Fractionals)) 
GFN (S Z) ApproxEq (x, x) (PairOf (Member Nums)) 
Apply (GFnA Z IsAnEq) a Bool 
(Apply (GFn ApproxEq) (x, x) Bool, Eq x) => Apply (GFnA (S (S (S Z))) ApproxEq) ((x, x), (x, x)) Bool 
Eq x => Apply (GFnA (S (S Z)) ApproxEq) (x, x) Bool 
(Fractional x, Ord x) => Apply (GFnA (S Z) ApproxEq') (x, x) Bool 
(Num x, Ord x) => Apply (GFnA (S Z) ApproxEq) (x, x) Bool 
(Apply (GFn IsAnEq) x Bool, Apply (GFn IsAnEq) y Bool) => Apply (GFnA (S Z) IsAnEq) (x, y) Bool 
(Num x, Ord x) => Apply (GFnA Z ApproxEq') (x, x) Bool 
(Fractional x, Ord x) => Apply (GFnA Z ApproxEq) (x, x) Bool 

newtype S n Source

Constructors

S n 

Instances

GFN (S Z) IsAnEq (x, y) Otherwise

Augment the above function, to test for pairs of Eqs We could have added an instance to TypeCls OpenEqs above. But we wish to show off the recursive invocation of a second-order polymorphic function

GFN (S (S (S Z))) ApproxEq ((x, x), (x, x)) (PairOf (PairOf (Member Nums))) 
GFN (S (S Z)) ApproxEq (x, x) (PairOf (Member Eqs)) 
GFN (S Z) ApproxEq' (x, x) (PairOf (Member Fractionals)) 
GFN (S Z) ApproxEq (x, x) (PairOf (Member Nums)) 
(Apply (GFn ApproxEq) (x, x) Bool, Eq x) => Apply (GFnA (S (S (S Z))) ApproxEq) ((x, x), (x, x)) Bool 
Eq x => Apply (GFnA (S (S Z)) ApproxEq) (x, x) Bool 
(Fractional x, Ord x) => Apply (GFnA (S Z) ApproxEq') (x, x) Bool 
(Num x, Ord x) => Apply (GFnA (S Z) ApproxEq) (x, x) Bool 
(Apply (GFn IsAnEq) x Bool, Apply (GFn IsAnEq) y Bool) => Apply (GFnA (S Z) IsAnEq) (x, y) Bool 

class TypeCast a b | a -> b, b -> a whereSource

Methods

typeCast :: a -> bSource

Instances

TypeCast' () a b => TypeCast a b 

class TypeCast' t a b | t a -> b, t b -> a whereSource

Methods

typeCast' :: t -> a -> bSource

Instances

TypeCast'' t a b => TypeCast' t a b 

class TypeCast'' t a b | t a -> b, t b -> a whereSource

Methods

typeCast'' :: t -> a -> bSource

Instances

TypeCast'' () a a 

class TypeEq x y b | x y -> bSource

Instances

TypeCast HFalse b => TypeEq x y b 
TypeEq x x HTrue 

class Apply f a r | f a -> r whereSource

Methods

apply :: f -> a -> rSource

Instances

Apply Otherwise a HTrue 
TypeCast r HFalse => Apply (PairOf t) x r 
(GFN Z f a pred, Apply pred a flag, Apply (GFnTest Z f flag) a b) => Apply (GFn f) a b 
(TypeEq h x bf, MemApp bf t x r) => Apply (Member (:*: h t)) x r 
(Apply (Member exc) x bf, Apply (MemCase2 h t x) bf r) => Apply (Member (:*: (AllOfBut h exc) t)) x r 
(Apply (Member h) x bf, MemApp bf t x r) => Apply (Member (:*: (AllOf h) t)) x r 
Apply (Member HNil) x HFalse 
TypeCls l x r => Apply (Member (TypeCl l)) x r 
Apply t x r => Apply (PairOf t) (x, x) r 
Apply (x -> y) x y 
Apply (GFnA n ApproxEq') a Bool 
Apply (GFnA n ApproxEq) a Bool 
Apply (GFnA n IsAnEq) a Bool 
Apply (GFnA Z IsAnEq) a Bool 
(Apply (GFn ApproxEq) (x, x) Bool, Eq x) => Apply (GFnA (S (S (S Z))) ApproxEq) ((x, x), (x, x)) Bool 
Eq x => Apply (GFnA (S (S Z)) ApproxEq) (x, x) Bool 
(Fractional x, Ord x) => Apply (GFnA (S Z) ApproxEq') (x, x) Bool 
(Num x, Ord x) => Apply (GFnA (S Z) ApproxEq) (x, x) Bool 
(Apply (GFn IsAnEq) x Bool, Apply (GFn IsAnEq) y Bool) => Apply (GFnA (S Z) IsAnEq) (x, y) Bool 
(Num x, Ord x) => Apply (GFnA Z ApproxEq') (x, x) Bool 
(Fractional x, Ord x) => Apply (GFnA Z ApproxEq) (x, x) Bool 
(GFN (S n) f a pred, Apply pred a flag, Apply (GFnTest (S n) f flag) a b) => Apply (GFnTest n f HFalse) a b 
Apply (GFnA n f) a b => Apply (GFnTest n f HTrue) a b 
Apply (Member (:*: (AllOf h) t)) x r => Apply (MemCase2 h t x) HFalse r 
Apply (Member t) x r => Apply (MemCase2 h t x) HTrue r