Strafunski-StrategyLib-5.0.1.0: Library for strategic programming

MaintainerRalf Laemmel, Joost Visser
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Data.Generics.Strafunski.StrategyLib.ContainerTheme

Contents

Description

This module is part of StrategyLib, a library of functional strategy combinators, including combinators for generic traversal. This module provides combinators which allow one to use strategies to construct generic containers.

Synopsis

Pointwise function update

modify :: Eq x => (x -> y) -> x -> y -> x -> y Source #

Pointwise modification of monomorphic functions

modifyTP :: (MonadPlus m, Eq t, Term t) => TP m -> t -> m t -> TP m Source #

Pointwise modification of type-preserving strategies

modifyTU :: (MonadPlus m, Eq t, Term t) => TU a m -> t -> m a -> TU a m Source #

Pointwise modification of type-unifying strategies

Generic Set (not observable)

type GSet = TU () Maybe Source #

Type of generic sets

emptyGSet :: GSet Source #

Empty generic set.

fullGSet :: GSet Source #

Completely filled generic set

addGSet :: (Eq t, Term t) => t -> GSet -> GSet Source #

Add an element to a generic set

removeGSet :: (Eq t, Term t) => t -> GSet -> GSet Source #

Remove an element from a generic set

containsGSet :: (Eq t, Term t) => t -> GSet -> Bool Source #

Test whether a given element is contained in a generic set

Generic Map (not observable)

type GMap value = TU value Maybe Source #

Type of generic maps

emptyGMap :: GMap v Source #

Empty generic map

removeGMap :: (Eq t, Term t) => t -> GMap v -> GMap v Source #

Remove an element from a generic map (my key)

containsGMap :: (Eq t, Term t) => t -> GMap v -> Bool Source #

Test whether an element with given key is contained in a generic map

putGMap :: (Eq t, Term t) => t -> v -> GMap v -> GMap v Source #

Add an entry with given key and value to a generic map

getGMap :: (Eq t, Term t) => t -> GMap v -> Maybe v Source #

Obtain the value for a given key from a generic map

sizeGList :: (a, b) -> b Source #

indxGList :: (a, b) -> a Source #

addGList :: Term t => t -> GList -> GList Source #

putGList :: Term t => Integer -> t -> GList -> GList Source #

mapGListTU :: Term t => (t -> ()) -> TU a Maybe -> GList -> [Maybe a] Source #

elemsGList :: Term t => (t -> ()) -> GList -> [t] Source #

nth :: [a] -> Integer -> a Source #

getCode :: Term x => Coder -> x -> Maybe Int Source #

setCode :: (Term x, Eq x) => Coder -> x -> Int -> Coder Source #

enCode :: (Term x, Eq x) => Coder -> x -> Coder Source #