MetaObject-0.0.2: A meta-object system for Haskell based on Perl 6ContentsIndex
MO.Util
Documentation
on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
traceShow :: Show a => a -> b -> b
traceM :: Monad m => String -> m ()
(?==?) :: (Eq a, Typeable a, Typeable b) => a -> b -> Bool
(?<=>?) :: (Ord a, Typeable a, Typeable b) => a -> b -> Ordering
addressOf :: a -> Word
data Ord a => Collection a
Constructors
MkCollection
c_objects :: Set a
c_names :: AtomMap a
show/hide Instances
cmap :: (Ord a, Ord b) => (a -> b) -> Collection a -> Collection b
remove :: (Monad m, Ord a) => Atom -> a -> Collection a -> m (Collection a)
add :: (Monad m, Ord a) => Atom -> a -> Collection a -> m (Collection a)
insert :: Ord a => Atom -> a -> Collection a -> Collection a
emptyCollection :: Ord a => Collection a
newCollection :: Ord a => [(Atom, a)] -> Collection a
newCollection' :: Ord a => (a -> Atom) -> [a] -> Collection a
newCollectionMap :: Ord a => AtomMap a -> Collection a
items :: Ord a => Collection a -> [a]
items_named :: Ord a => Collection a -> [(Atom, a)]
includes :: Ord a => Collection a -> a -> Bool
includes_name :: Ord a => Collection a -> Atom -> Bool
includes_any :: Ord a => Collection a -> [a] -> Bool
includes_any_name :: Ord a => Collection a -> [Atom] -> Bool
includes_all :: Ord a => Collection a -> [a] -> Bool
shadow :: Ord a => [Collection a] -> [a]
shadow' :: Ord a => [Collection a] -> AtomMap a
shadow_collection :: Ord a => [Collection a] -> Collection a
merge :: Ord a => [Collection a] -> [a]
merge' :: Ord a => [Collection a] -> AtomMap a
merge_collection :: Ord a => [Collection a] -> Collection a
sym_shadowing :: (Show a, Ord a) => b -> (b -> [b]) -> (b -> Collection a) -> Collection a
sym_merged_parents :: (Show a, Ord a) => b -> (b -> [b]) -> (b -> Collection a) -> Collection a
sym_inheritance :: Ord a => b -> (b -> [b]) -> (b -> (Collection a)) -> Collection a
module MO.Capture
Produced by Haddock version 2.1.0