thrist-0.3: Type-threaded list

Safe HaskellSafe-Inferred

Data.Thrist

Contents

Synopsis

Types:

data Thrist whereSource

A type-threaded list of binary polymorphic types.

Constructors

Nil :: Thrist arr a a 
Cons :: (a `arr` b) -> Thrist arr b c -> Thrist arr a c 

Instances

(Category (Thrist * arr), Arrow arr) => Arrow (Thrist * arr) 
Category (Thrist * arr) 
Monoid (Thrist k arr a a) 

newtype Flipped m a b Source

A newtype wrapper, defined for convenience, that swaps the two type variables of a binary type. Can be used to reverse a Thrist using foldlThrist. See examples.

Constructors

Flipped 

Fields

unflip :: m b a
 

Fold and map functions:

mapThrist :: (forall i j. (i `brr` j) -> i `arr` j) -> Thrist brr a b -> Thrist arr a bSource

Equivalent to map for thrists. Takes a function from one binary type to another and applies it to each thrist element. For example this could convert a thrist of (a,b) into a thrist of Either a b:

foldrThrist :: (forall i j. (i `arr` j) -> (j `brr` c) -> i `brr` c) -> (b `brr` c) -> Thrist arr a b -> a `brr` cSource

Equivalent to foldr for thrists. Takes a combining function, a value to replace Nil, and a thrist, returning some new binary type.

foldlThrist :: (forall j k. (a `brr` j) -> (j `arr` k) -> a `brr` k) -> (a `brr` b) -> Thrist arr b c -> a `brr` cSource

Equivalent to foldl for Thrists.

foldr1Thrist :: (forall i j k. (i `arr` j) -> (j `arr` k) -> i `arr` k) -> Thrist arr a b -> a `arr` bSource

Equivalent to foldr1 for Thrists.

foldl1Thrist :: (forall i j k. (i `arr` j) -> (j `arr` k) -> i `arr` k) -> Thrist arr a b -> a `arr` bSource

Equivalent to foldl1 for Thrists.

Monadic functions:

mapMThrist :: Monad m => (forall i j. (i `brr` j) -> m (i `arr` j)) -> Thrist brr a b -> m (Thrist arr a b)Source

Equivalent to mapM on Thrists.

foldMThrist :: Monad m => (forall j k. (a `brr` j) -> (j `arr` k) -> m (a `brr` k)) -> (a `brr` b) -> Thrist arr b c -> m (a `brr` c)Source

Equivalent to foldM on Thrists.

Other list-like functions:

appendThrist :: Thrist arr a b -> Thrist arr b c -> Thrist arr a cSource

Equivalent to (++) for thrists.

nullThrist :: Thrist arr a b -> BoolSource

Returns True when the Thrist is Nil.

lengthThrist :: Thrist arr a b -> IntSource

Returns the length of the Thrist.