parameterized-utils-2.0.1.0: Classes and data structures for working with data-kind indexed types

Copyright(c) Galois Inc 2014-2019
MaintainerJoe Hendrix <jhendrix@galois.com>
Safe HaskellSafe
LanguageHaskell98

Data.Parameterized.Utils.BinTree

Description

 
Synopsis

Documentation

data MaybeS v Source #

A strict version of Maybe

Constructors

JustS !v 
NothingS 
Instances
Functor MaybeS Source # 
Instance details

Defined in Data.Parameterized.Utils.BinTree

Methods

fmap :: (a -> b) -> MaybeS a -> MaybeS b #

(<$) :: a -> MaybeS b -> MaybeS a #

Applicative MaybeS Source # 
Instance details

Defined in Data.Parameterized.Utils.BinTree

Methods

pure :: a -> MaybeS a #

(<*>) :: MaybeS (a -> b) -> MaybeS a -> MaybeS b #

liftA2 :: (a -> b -> c) -> MaybeS a -> MaybeS b -> MaybeS c #

(*>) :: MaybeS a -> MaybeS b -> MaybeS b #

(<*) :: MaybeS a -> MaybeS b -> MaybeS a #

Alternative MaybeS Source # 
Instance details

Defined in Data.Parameterized.Utils.BinTree

Methods

empty :: MaybeS a #

(<|>) :: MaybeS a -> MaybeS a -> MaybeS a #

some :: MaybeS a -> MaybeS [a] #

many :: MaybeS a -> MaybeS [a] #

fromMaybeS :: a -> MaybeS a -> a Source #

data Updated a Source #

Updated a contains a value that has been flagged on whether it was modified by an operation.

Constructors

Updated !a 
Unchanged !a 

data TreeApp e t Source #

Constructors

BinTree !e !t !t 
TipTree 

class IsBinTree t e | t -> e where Source #

Methods

asBin :: t -> TreeApp e t Source #

tip :: t Source #

bin :: e -> t -> t -> t Source #

size :: t -> Int Source #

Instances
IsBinTree (MapF k2 a) (Pair k2 a) Source # 
Instance details

Defined in Data.Parameterized.Map

Methods

asBin :: MapF k2 a -> TreeApp (Pair k2 a) (MapF k2 a) Source #

tip :: MapF k2 a Source #

bin :: Pair k2 a -> MapF k2 a -> MapF k2 a -> MapF k2 a Source #

size :: MapF k2 a -> Int Source #

balanceL :: IsBinTree c e => e -> c -> c -> c Source #

balanceL p l r returns a balanced tree for the sequence l ++ [p] ++ r.

It assumes that l and r are close to being balanced, and that only l may contain too many elements.

balanceR :: IsBinTree c e => e -> c -> c -> c Source #

balanceR p l r returns a balanced tree for the sequence l ++ [p] ++ r.

It assumes that l and r are close to being balanced, and that only r may contain too many elements.

glue :: IsBinTree c e => c -> c -> c Source #

glue l r concatenates l and r.

It assumes that l and r are already balanced with respect to each other.

merge :: IsBinTree c e => c -> c -> c Source #

Concatenate two trees that are ordered with respect to each other.

filterGt :: IsBinTree c e => (e -> Ordering) -> c -> MaybeS c Source #

Returns only entries that are less than predicate with respect to the ordering and Nothing if no elements are discarded.

filterLt :: IsBinTree c e => (e -> Ordering) -> c -> MaybeS c Source #

filterLt k m returns submap of m that only contains entries that are smaller than k. If no entries are deleted then return Nothing.

insert :: IsBinTree c e => (e -> e -> Ordering) -> e -> c -> Updated c Source #

insert p m inserts the binding into m. It returns an Unchanged value if the map stays the same size and an updated value if a new entry was inserted.

delete Source #

Arguments

:: IsBinTree c e 
=> (e -> Ordering)

Predicate that returns whether the entry is less than, greater than, or equal to the key we are entry that we are looking for.

-> c 
-> MaybeS c 

union :: IsBinTree c e => (e -> e -> Ordering) -> c -> c -> c Source #

Union two sets

link :: IsBinTree c e => e -> c -> c -> c Source #

link is called to insert a key and value between two disjoint subtrees.

data PairS f s Source #

A Strict pair

Constructors

PairS !f !s