swish-0.5.0.3: A semantic web toolkit.

PortabilityA lot of LANGUAGE extensions...
Stabilityexperimental
MaintainerDouglas Burke

Swish.Utils.LookupMap

Description

This module defines a lookup table format and associated functions used by the graph matching code.

Synopsis

Documentation

class (Eq k, Show k) => LookupEntryClass a k v | a -> k, a -> v whereSource

LookupEntryClass defines essential functions of any datatype that can be used to make a LookupMap.

Minimal definition: newEntry and keyVal

Methods

newEntry :: (k, v) -> aSource

keyVal :: a -> (k, v)Source

entryKey :: a -> kSource

entryVal :: a -> vSource

entryEq :: Eq v => a -> a -> BoolSource

entryShow :: Show v => a -> StringSource

kmap :: LookupEntryClass a2 k2 v => (k -> k2) -> a -> a2Source

vmap :: LookupEntryClass a2 k v2 => (v -> v2) -> a -> a2Source

Instances

LookupEntryClass ClassRestriction ScopedName ClassRestriction 
LookupEntryClass RevNamespace URI (Maybe Text) 
LookupEntryClass NamedGraph ScopedName [RDFGraph] 
LookupEntryClass Namespace (Maybe Text) URI 
LookupEntryClass (Rule ex) ScopedName (Rule ex) 
LookupEntryClass (Formula ex) ScopedName (Formula ex) 
LookupEntryClass (Ruleset ex) Namespace (Ruleset ex) 
LookupEntryClass (DatatypeRel vt) ScopedName (DatatypeRel vt) 
(Eq k, Show k) => LookupEntryClass (k, v) k v

Predefine a pair of appropriate values as a valid lookup table entry (i.e. an instance of LookupEntryClass).

(Label lb, Eq lb, Show lb, Eq lv, Show lv) => LookupEntryClass (GenLabelEntry lb lv) lb lv 
Label lb => LookupEntryClass (LookupFormula lb (NSGraph lb)) lb (NSGraph lb) 
LookupEntryClass (OpenVarBindingModify a b) ScopedName (OpenVarBindingModify a b)

Allow an OpenVarBindingModify value to be accessed using a LookupMap.

LookupEntryClass (VarBindingModify a b) ScopedName (VarBindingModify a b)

Allow a VarBindingModify value to be accessed using a LookupMap.

LookupEntryClass (DatatypeMod vt lb vn) ScopedName (DatatypeMod vt lb vn) 
LookupEntryClass (Datatype ex lb vn) ScopedName (Datatype ex lb vn) 

data LookupMap a Source

Define a lookup map based on a list of values.

Note: the class constraint that a is an instance of LookupEntryClass is not defined here, for good reasons (which I forget right now, but something to do with the method dictionary being superfluous on an algebraic data type).

Constructors

LookupMap [a] 

Instances

Functor LookupMap 
Foldable LookupMap 
Traversable LookupMap 
Eq a => Eq (LookupMap a)

Define equality of LookupMap values based on equality of entries.

(This is possibly a poor definition, as it is dependent on ordering of list members. But it passes all current test cases, and is used only for testing.)

Show a => Show (LookupMap a)

Define Show instance for LookupMap based on Showing the list of entries.

emptyLookupMap :: LookupEntryClass a k v => LookupMap aSource

Empty lookup map of arbitrary (i.e. polymorphic) type.

makeLookupMap :: LookupEntryClass a k v => [a] -> LookupMap aSource

Function to create a LookupMap from a list of entries.

Currently, this is trivial but future versions could be more substantial.

listLookupMap :: LookupEntryClass a k v => LookupMap a -> [a]Source

Return list of lookup map entries.

Currently, this is trivial but future versions could be more substantial.

reverseLookupMap :: (LookupEntryClass a1 b c, LookupEntryClass a2 c b) => LookupMap a1 -> LookupMap a2Source

Given a lookup map, return a new map that can be used in the opposite direction of lookup.

keyOrder :: (LookupEntryClass a k v, Ord k) => a -> a -> OrderingSource

Given a pair of lookup entry values, return the ordering of their key values.

mapFind :: LookupEntryClass a k v => v -> k -> LookupMap a -> vSource

Find key in lookup map and return corresponding value, otherwise return default supplied.

mapFindMaybe :: LookupEntryClass a k v => k -> LookupMap a -> Maybe vSource

Find key in lookup map and return Just the corresponding value, otherwise return Nothing.

mapContains :: LookupEntryClass a k v => LookupMap a -> k -> BoolSource

Test to see if key is present in the supplied map

mapReplace :: LookupEntryClass a k v => LookupMap a -> a -> LookupMap aSource

Replace an existing occurrence of a key a with a new key-value pair.

The resulting lookup map has the same form as the original in all other respects. Assumes exactly one occurrence of the supplied key.

mapReplaceOrAdd :: LookupEntryClass a k v => a -> LookupMap a -> LookupMap aSource

Replace an existing occurrence of a key a with a new key-value pair, or add a new key-value pair if the supplied key is not already present.

mapReplaceAll :: LookupEntryClass a k v => LookupMap a -> a -> LookupMap aSource

Replace any occurrence of a key a with a new key-value pair.

The resulting lookup map has the same form as the original in all other respects.

mapReplaceMap :: LookupEntryClass a k v => LookupMap a -> LookupMap a -> LookupMap aSource

Replace any occurrence of a key in the first argument with a corresponding key-value pair from the second argument, if present.

This could be implemented by multiple applications of mapReplaceAll, but is arranged differently so that only one new LookupMap value is created.

Note: keys in the new map that are not present in the old map are not included in the result map

mapAdd :: LookupMap a -> a -> LookupMap aSource

Add supplied key-value pair to the lookup map.

This is effectively an optimized case of mapReplaceOrAdd or mapAddIfNew, where the caller guarantees to avoid duplicate key values.

mapAddIfNew :: LookupEntryClass a k v => LookupMap a -> a -> LookupMap aSource

Add supplied key-value pair to the lookup map, only if the key value is not already present.

mapDelete :: LookupEntryClass a k v => LookupMap a -> k -> LookupMap aSource

Delete supplied key value from the lookup map.

This function assumes exactly one occurrence.

mapDeleteAll :: LookupEntryClass a k v => LookupMap a -> k -> LookupMap aSource

Delete any occurrence of a supplied key value from the lookup map.

mapApplyToAll :: LookupEntryClass a k v => LookupMap a -> (k -> w) -> [w]Source

Return a list of values obtained by applying a function to each key in the map. Creates an alternative set of values that can be retrieved using mapTranslate.

mapTranslate :: LookupEntryClass a k v => LookupMap a -> [w] -> k -> w -> wSource

Find a node in a lookup map list, and returns the corresponding value from a supplied list. The appropriate ordering of the list is not specified here, but an appropriately ordered list may be obtained by mapApplyToAll.

mapEq :: (LookupEntryClass a k v, Eq v) => LookupMap a -> LookupMap a -> BoolSource

Compare two lookup maps for equality.

Two maps are equal if they have the same set of keys, and if each key maps to an equivalent value.

mapKeys :: LookupEntryClass a k v => LookupMap a -> [k]Source

Return the list of keys in a supplied LookupMap

mapVals :: (Eq v, LookupEntryClass a k v) => LookupMap a -> [v]Source

Return list of distinct values in a supplied LookupMap

mapSelect :: LookupEntryClass a k v => LookupMap a -> [k] -> LookupMap aSource

Select portion of a lookup map that corresponds to a supplied list of keys

mapMerge :: (LookupEntryClass a k v, Eq a, Show a, Ord k) => LookupMap a -> LookupMap a -> LookupMap aSource

Merge two lookup maps, ensuring that if the same key appears in both maps it is associated with the same value.

mapTranslateKeys :: (LookupEntryClass a1 k1 v, LookupEntryClass a2 k2 v) => (k1 -> k2) -> LookupMap a1 -> LookupMap a2Source

An fmap-like function that returns a new lookup map that is a copy of the supplied map with entry keys replaced according to a supplied function.

mapTranslateVals :: (LookupEntryClass a1 k v1, LookupEntryClass a2 k v2) => (v1 -> v2) -> LookupMap a1 -> LookupMap a2Source

An fmap-like function that returns a new lookup map that is a copy of the supplied map with entry values replaced according to a supplied function.

mapTranslateEntries :: (a1 -> a2) -> LookupMap a1 -> LookupMap a2Source

A function that returns a new lookup map that is a copy of the supplied map with complete entries replaced according to a supplied function.

mapTranslateEntriesM :: Monad m => (a1 -> m a2) -> LookupMap a1 -> m (LookupMap a2)Source

A monadic form of mapTranslateEntries which is the same as Data.Traversable.mapM.

Since LookupMap now has a Data.Traversable.Traversable instance this is just mapM.