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

Data.Class2

Description

Haskell with only one typeclass

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

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

How to make ad hoc overloading less ad hoc while defining no type classes. Haskell1' -- the extension of Haskell1 with functional dependencies, and bounded-polymorphic higher-rank types

Synopsis

Documentation

data ERROR a Source

Some functional dependencies: implementing Monad Error As it turns out, some functional dependencies are expressible already in Haskell1. The example is MonadError, which in Haskell' has the form

Instances

strMsg :: forall a. C (ERROR a) (String -> a) => String -> aSource

data ThrowError m a Source

Instances

C (ThrowError (Either e) a) (e -> Either e a) 

throwError :: forall e m a b t1 t2. (C (ThrowError m a) (e -> m a), C (RET m a) t1, C (BIND m a b) t2) => e -> m aSource

data CatchError m a Source

Instances

C (CatchError (Either e) a) (Either e a -> (e -> Either e a) -> Either e a) 

catchError :: forall e m a. C (CatchError m a) (m a -> (e -> m a) -> m a) => m a -> (e -> m a) -> m aSource

data FC1 a b c Source

Instances

C (FC1 Bool Char Int) (Bool -> Char -> Int) 

fc1 :: forall a b c. C (FC1 a b c) (a -> b -> c) => a -> b -> cSource

data FC2 a b c Source

Instances

TypeCast c Int => C (FC2 Bool Char c) (Bool -> Char -> Int) 

fc2 :: forall a b c. C (FC2 a b c) (a -> b -> c) => a -> b -> cSource

data FC3 a b c Source

Instances

TypeCast (FC3 Bool b c) (FC3 Bool Char Int) => C (FC3 Bool b c) (Bool -> Char -> Int) 

fc3 :: forall a b c. C (FC3 a b c) (a -> b -> c) => a -> b -> cSource

data FromList e Source

Instances

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)) 

fromList :: forall e array. C (FromList e) (Int -> [e] -> array) => Int -> [e] -> arraySource

data Index e Source

Instances

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)) 

indexA :: forall e array. C (Index e) (array -> Int -> e) => array -> Int -> eSource

data NUM a Source

Constructors

NUM 

Fields

nm_add :: a -> a -> a
 
nm_mul :: a -> a -> a
 
nm_fromInteger :: Integer -> a
 
nm_show :: a -> String
 

Instances

(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) 

data CLS a Source

Instances

(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) 

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

(*$$) :: forall a. C (CLS (NUM a)) (NUM a) => a -> a -> aSource

nshw :: forall a. C (CLS (NUM a)) (NUM a) => a -> StringSource

nfromI :: forall a. C (CLS (NUM a)) (NUM a) => Integer -> aSource

data PACK Source

Constructors

forall a . C (CLS (NUM a)) (NUM a) => PACK a 

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