heterolist-0.2.0.0: A heterogeneous list type

Safe HaskellNone
LanguageHaskell2010

Data.HeteroList

Description

This module provides heterogenuous lists. There are a few functions on these lists which are an attempt to be parallels of the Functor, Applicative and Monad classes, although these are not part of type classes, and certainly not the above classes because the types don't match.

I believe this sort of package has potential in testing generic libraries.

For example, lets say you have (n) sets of test data.

And (m) different functions that work on that data.

And (m) different "check functions" (perhaps just the functions above but one release back as a control).

Making a complete test case for all this is tricky, because you may be testing different types and the functions you're testing on them may have different results.

You can sometimes get situations where you just have to write (n * m) test cases.

This approach hopefully makes the work (n + m) instead.

It probably needs some work but I have included a functional example in the documentation for hap.

Synopsis

Documentation

data HeteroList l where Source #

Heterogeneous list type. Construct like so:

x = (5 :: Int) :- 'a' :- True :- Nil

Constructors

(:-) :: a -> HeteroList as -> HeteroList (a ': as) infixr 5 
Nil :: HeteroList '[] 

Instances

HeteroListConstraint Eq a => Eq (HeteroList a) Source # 

Methods

(==) :: HeteroList a -> HeteroList a -> Bool #

(/=) :: HeteroList a -> HeteroList a -> Bool #

(HeteroListConstraint Eq a, HeteroListConstraint Ord a) => Ord (HeteroList a) Source # 
(Show a, Show (ShowRest (HeteroList as))) => Show (HeteroList ((:) * a as)) Source # 

Methods

showsPrec :: Int -> HeteroList ((* ': a) as) -> ShowS #

show :: HeteroList ((* ': a) as) -> String #

showList :: [HeteroList ((* ': a) as)] -> ShowS #

Show (HeteroList ([] *)) Source # 

(++) :: HeteroList a -> HeteroList b -> HeteroList (a :++ b) Source #

Append two heterogeneous lists. Of course, as HeteroLists know their type, this produces a new type.

happend :: HeteroList a -> HeteroList b -> HeteroList (a :++ b) Source #

Synonym for '(++)'.

class HeteroListConstraintT c a => HeteroListConstraint c a Source #

Applies a constraint c to a type of HeteroList a. So you want to write this:

(HeteroListConstraintT c t) => HeteroList t

not

HeteroListConstraintT c (HeteroList t)  => HeteroList t

Instances

HeteroListConstraintT c a => HeteroListConstraint c a Source # 

class IsHeteroListT a => IsHeteroList a Source #

Constraint which requires the argument to be a HeteroList

Instances

IsHeteroListT a => IsHeteroList a Source # 

type family GetHead a where ... Source #

Get the type of the first element of a HeteroList

Equations

GetHead (HeteroList (a ': _)) = a 

type family GetTail a where ... Source #

Get the type of the tail of a HeteroList.

Equations

GetTail (HeteroList (_ ': as)) = as 

type family GetHeteroListParam a where ... Source #

Gets the types of the HeteroList. Naturally this is a list of types of type [*].

Equations

GetHeteroListParam (HeteroList a) = a 

hmap :: HeteroMapConstraint c a b => Poly c -> HeteroList a -> HeteroList b Source #

The analogue of map. Not you'll need to pass a Poly as the function. A more complex example is included in the function hap.

hconcatMap :: forall c a b. (HeteroMapConstraint c a b, HeteroListConstraint IsHeteroList b) => Poly c -> HeteroList a -> HeteroList (ConcatT b) Source #

The analogue of concatMap, or >>= ("bind") from Monad. It's just hmap followed by hconcat.

class HeteroMapConstraintT c a b => HeteroMapConstraint c a b Source #

This constraints c, which is intended to be the argument of a Poly, to be a constraint which allows one to map between the two HeteroLists of type a and b

Instances

HeteroMapConstraintT c a b => HeteroMapConstraint c a b Source # 

hmapfl :: forall f a b c. (HeteroMapConstraint c f b, c ~ WhatsC a, HeteroListConstraint IsHeteroList b) => HeteroList f -> HeteroList a -> HeteroList b Source #

Applies every function in the HeteroList of Polys in the first argument to the HeteroList which is the second argument. This is much like hap except the result list is not "flattened" by hconcat

hap :: forall f a b c. (HeteroMapConstraint c f b, c ~ WhatsC a, HeteroListConstraint IsHeteroList b) => HeteroList f -> HeteroList a -> HeteroList (ConcatT b) Source #

This is the analogue of ap, or 'Control.Applicative.<*>. Arguments are the same as hmapfl, but the result is flattened.

Here's an example usage:

>>> triple = Poly @((IsHomoFunc 1) &&& ((Arg 0) `IxConstrainBy` Num)) (*3)
>>> compareZero = Poly @((IsFunc 1) &&& ((Arg 0) `IxConstrainBy` (Num &&& Ord)) &&& ((Result 1) `IxIs` Ordering)) (`compare` 0)
>>> greaterThanZero = Poly @((IsFunc 1) &&& ((Arg 0) `IxConstrainBy` (Num &&& Ord)) &&& ((Result 1) `IxIs` Bool)) (> 0)
>>> f = triple :- compareZero :- greaterThanZero :- Nil
>>> x = (42 :: Int) :- (-100 :: Float) :- (22 % 7 :: Rational) :- Nil
>>> f `hap` x
[126, -300.0, 66 % 7, GT, LT, GT, True, False, True]

Note that

type family ConcatT a where ... Source #

The type of a concatenated list. Note, like HeteroListConstraintT you need to apply this type function to the parameter to HeteroList.

Equations

ConcatT (HeteroList a ': as) = a :++ ConcatT as 
ConcatT '[] = '[] 

toList :: forall a t. IsHomogeneousList a t => HeteroList t -> [a] Source #

Naturally, if (and only if) a HeteroList is actually homogeneous, we can turn it into an ordinary list.

class HeteroListConstraint (Equal a) t => IsHomogeneousList a t Source #

IsHomogeneousList a t

constraints a 'HeteroList t' to have elements only of type a.

i.e.

IsHomogeneousList Int t => HeteroList t

means the HeteroList only has elements of type Int.

length :: forall t. HeteroList t -> Int Source #

Length of a HeteroList. I'm not sure if this can be done in constant time as the type defines the length, but currently it just does the usual traverse the list and count.

type family ListLength t :: Nat where ... Source #

Type level length the paramter of a HeteroList

Equations

ListLength '[] = 0 
ListLength (_ ': as) = 1 + ListLength as