raw-feldspar-0.2.1: Resource-Aware Feldspar

Safe HaskellNone
LanguageHaskell2010

Data.TypedStruct

Contents

Description

Typed binary tree structures

Synopsis

Representation

data Struct pred con a where Source #

Typed binary tree structure

The predicate pred is assumed to rule out pairs. Functions like extractSingle and zipStruct rely on this assumption.

Constructors

Single :: pred a => con a -> Struct pred con a 
Two :: Struct pred con a -> Struct pred con b -> Struct pred con (a, b) 

toStruct :: Struct p c a -> a -> Struct p Identity a Source #

Create a Struct from a Struct of any container c and a structured value a

For example:

toStruct (Two (Single Proxy) (Single Proxy)) (False,a)
  ==
Two (Single (Identity False)) (Single (Identity a))

Operations

extractSingle :: pred a => Struct pred c a -> c a Source #

Extract the value of a Single

mapStruct :: forall pred c1 c2 b. (forall a. pred a => c1 a -> c2 a) -> Struct pred c1 b -> Struct pred c2 b Source #

Map over a Struct

mapStructA :: forall m pred c1 c2 b. Applicative m => (forall a. pred a => c1 a -> m (c2 a)) -> Struct pred c1 b -> m (Struct pred c2 b) Source #

Monadic map over a Struct

mapStructA_ :: forall m pred cont b. Applicative m => (forall a. pred a => cont a -> m ()) -> Struct pred cont b -> m () Source #

Map over a Struct

listStruct :: forall pred cont b c. (forall y. pred y => cont y -> c) -> Struct pred cont b -> [c] Source #

Fold a Struct to a list

zipStruct :: forall pred c1 c2 c3 b. (forall a. pred a => c1 a -> c2 a -> c3 a) -> Struct pred c1 b -> Struct pred c2 b -> Struct pred c3 b Source #

Zip two Structs

zipListStruct :: forall pred c1 c2 b r. (forall a. pred a => c1 a -> c2 a -> r) -> Struct pred c1 b -> Struct pred c2 b -> [r] Source #

Zip two Structs to a list

compareStruct :: forall pred c1 c2 c d. (forall a b. (pred a, pred b) => c1 a -> c2 b -> Bool) -> Struct pred c1 c -> Struct pred c2 d -> Bool Source #

Compare two Structs using a function that compares the Single elements. If the structures don't match, False is returned.

liftStruct :: (pred a, pred b) => (con a -> con b) -> Struct pred con a -> Struct pred con b Source #

Lift a function operating on containers con to a function operating on Structs.

liftStruct2 :: (pred a, pred b, pred c) => (con a -> con b -> con c) -> Struct pred con a -> Struct pred con b -> Struct pred con c Source #

Lift a function operating on containers con to a function operating on Structs.