ForestStructures-0.0.1.0: Tree- and forest structures

Safe HaskellNone
LanguageHaskell2010

Data.Forest.StructuredPaired

Description

A semi-specialized forest structure with the following atomic elements: (i) unstructured regions of type a, (ii) binary paired regions of type (b,b) with a recursing tree (or insertion between the two b's), (iii) juxtaposition of two elements, and (iv) an empty structure.

Synopsis

Documentation

data SPForest r t Source #

A structured forest.

Constructors

SPR r

An (unstructured) region with the structured forest. In case r forms a monoid SPJ (SPR a) (SPR b) equiv SPR (a<>b) should hold.

SPT t (SPForest r t) t

A tree within the forest brackets the forest on the left and right side with elements of type t.

SPJ [SPForest r t]

Juxtaposition of two forests. This allows for simple concatenation of forests. In particular, there is no particular position, while lists prefer x:xs vs xs++[x].

SPE

An empty forest. SPJ SPE SPE equiv SPE should hold.

Instances
Bitraversable SPForest Source # 
Instance details

Defined in Data.Forest.StructuredPaired

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> SPForest a b -> f (SPForest c d) #

Bifoldable SPForest Source # 
Instance details

Defined in Data.Forest.StructuredPaired

Methods

bifold :: Monoid m => SPForest m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> SPForest a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> SPForest a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> SPForest a b -> c #

Bifunctor SPForest Source # 
Instance details

Defined in Data.Forest.StructuredPaired

Methods

bimap :: (a -> b) -> (c -> d) -> SPForest a c -> SPForest b d #

first :: (a -> b) -> SPForest a c -> SPForest b c #

second :: (b -> c) -> SPForest a b -> SPForest a c #

(Eq r, Eq t) => Eq (SPForest r t) Source # 
Instance details

Defined in Data.Forest.StructuredPaired

Methods

(==) :: SPForest r t -> SPForest r t -> Bool #

(/=) :: SPForest r t -> SPForest r t -> Bool #

(Ord r, Ord t) => Ord (SPForest r t) Source # 
Instance details

Defined in Data.Forest.StructuredPaired

Methods

compare :: SPForest r t -> SPForest r t -> Ordering #

(<) :: SPForest r t -> SPForest r t -> Bool #

(<=) :: SPForest r t -> SPForest r t -> Bool #

(>) :: SPForest r t -> SPForest r t -> Bool #

(>=) :: SPForest r t -> SPForest r t -> Bool #

max :: SPForest r t -> SPForest r t -> SPForest r t #

min :: SPForest r t -> SPForest r t -> SPForest r t #

(Read r, Read t) => Read (SPForest r t) Source # 
Instance details

Defined in Data.Forest.StructuredPaired

(Show r, Show t) => Show (SPForest r t) Source # 
Instance details

Defined in Data.Forest.StructuredPaired

Methods

showsPrec :: Int -> SPForest r t -> ShowS #

show :: SPForest r t -> String #

showList :: [SPForest r t] -> ShowS #

Generic (SPForest r t) Source # 
Instance details

Defined in Data.Forest.StructuredPaired

Associated Types

type Rep (SPForest r t) :: Type -> Type #

Methods

from :: SPForest r t -> Rep (SPForest r t) x #

to :: Rep (SPForest r t) x -> SPForest r t #

type Rep (SPForest r t) Source # 
Instance details

Defined in Data.Forest.StructuredPaired

_SPE :: forall r t. Prism' (SPForest r t) () Source #

_SPJ :: forall r t. Prism' (SPForest r t) [SPForest r t] Source #

_SPT :: forall r t. Prism' (SPForest r t) (t, SPForest r t, t) Source #

_SPR :: forall r t. Prism' (SPForest r t) r Source #

toStaticForest :: SPForest r t -> Forest p v a Source #

Structured Forests can be transformed into static forests.

TODO types involved!