Safe Haskell | None |
---|---|
Language | Haskell98 |
- 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 = MkCollection {}
- 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
- module StringTable.Atom
- trace :: String -> a -> a
Documentation
data Ord a => Collection a Source
Ord a => Eq (Collection a) | |
Ord a => Ord (Collection a) | |
(Ord a, Show a) => Show (Collection a) | |
Typeable (* -> *) Collection |
cmap :: (Ord a, Ord b) => (a -> b) -> Collection a -> Collection b Source
remove :: (Monad m, Ord a) => Atom -> a -> Collection a -> m (Collection a) Source
add :: (Monad m, Ord a) => Atom -> a -> Collection a -> m (Collection a) Source
insert :: Ord a => Atom -> a -> Collection a -> Collection a Source
emptyCollection :: Ord a => Collection a Source
newCollection :: Ord a => [(Atom, a)] -> Collection a Source
newCollection' :: Ord a => (a -> Atom) -> [a] -> Collection a Source
newCollectionMap :: Ord a => AtomMap a -> Collection a Source
items :: Ord a => Collection a -> [a] Source
items_named :: Ord a => Collection a -> [(Atom, a)] Source
includes :: Ord a => Collection a -> a -> Bool Source
includes_name :: Ord a => Collection a -> Atom -> Bool Source
includes_any :: Ord a => Collection a -> [a] -> Bool Source
includes_any_name :: Ord a => Collection a -> [Atom] -> Bool Source
includes_all :: Ord a => Collection a -> [a] -> Bool Source
shadow :: Ord a => [Collection a] -> [a] Source
shadow' :: Ord a => [Collection a] -> AtomMap a Source
shadow_collection :: Ord a => [Collection a] -> Collection a Source
merge :: Ord a => [Collection a] -> [a] Source
merge' :: Ord a => [Collection a] -> AtomMap a Source
merge_collection :: Ord a => [Collection a] -> Collection a Source
sym_shadowing :: (Show a, Ord a) => b -> (b -> [b]) -> (b -> Collection a) -> Collection a Source
sym_merged_parents :: (Show a, Ord a) => b -> (b -> [b]) -> (b -> Collection a) -> Collection a Source
sym_inheritance :: Ord a => b -> (b -> [b]) -> (b -> Collection a) -> Collection a Source
module MO.Capture
module StringTable.Atom
The trace
function outputs the trace message given as its first argument,
before returning the second argument as its result.
For example, this returns the value of f x
but first outputs the message.
trace ("calling f with x = " ++ show x) (f x)
The trace
function should only be used for debugging, or for monitoring
execution. The function is not referentially transparent: its type indicates
that it is a pure function but it has the side effect of outputting the
trace message.