|
Graphics.UI.ObjectIO.CommonDef | Portability | portable | Stability | provisional | Maintainer | ka2_mail@yahoo.com |
|
|
|
|
Contents |
- Common definitions
- Type declarations
- Function declarations
- Bound type
- Operations
- Calculation rules on Point2s, Sizes, Rectangles and Vector2s:
- Function declarations
- Class declarations
- List operations
- Error generation
- A visible module
|
|
Description |
CommonDef defines common types for the Object I/O library and access-rules.
|
|
Synopsis |
|
type St s a = s -> (a, s) | | type Cond x = x -> Bool | | type UCond x = x -> (Bool, x) | | toSt :: (x -> y) -> St x y | | setBetween :: Int -> Int -> Int -> Int | | isBetween :: Int -> Int -> Int -> Bool | | minmax :: Int -> Int -> (Int, Int) | | fst3snd3 :: (a, b, c) -> (a, b) | | fst3thd3 :: (a, b, c) -> (a, c) | | snd3thd3 :: (a, b, c) -> (b, c) | | eqfst2id :: (Eq a) => a -> (a, b) -> Bool | | eqfst3id :: (Eq a) => a -> (a, b, c) -> Bool | | | | zeroBound :: Bound -> Bool | | decBound :: Bound -> Bound | | incBound :: Bound -> Bound | | data Rect = Rect {} | | addPointSize :: Size -> Point2 -> Point2 | | rectangleToRect :: Rectangle -> Rect | | rectToRectangle :: Rect -> Rectangle | | isEmptyRect :: Rect -> Bool | | isEmptyRectangle :: Rectangle -> Bool | | pointInRect :: Point2 -> Rect -> Bool | | pointInRectangle :: Point2 -> Rectangle -> Bool | | posSizeToRect :: Point2 -> Size -> Rect | | posSizeToRectangle :: Point2 -> Size -> Rectangle | | sizeToRect :: Size -> Rect | | sizeToRectangle :: Size -> Rectangle | | rectSize :: Rect -> Size | | disjointRects :: Rect -> Rect -> Bool | | intersectRects :: Rect -> Rect -> Rect | | subtractRects :: Rect -> Rect -> [Rect] | | class AddVector a where | | | class SubVector a where | | | class ToTuple a where | | | class FromTuple a where | | | class ToTuple4 a where | | | class FromTuple4 a where | | | isSingleton :: [x] -> Bool | | initLast :: [x] -> ([x], x) | | split :: Int -> [x] -> ([x], [x]) | | condMap :: Cond x -> IdFun x -> [x] -> (Bool, [x]) | | uspan :: UCond a -> [a] -> ([a], [a]) | | filterMap :: (x -> (Bool, y)) -> [x] -> [y] | | stateMap :: (x -> s -> (y, s)) -> [x] -> s -> ([y], s) | | ucontains :: UCond x -> [x] -> (Bool, [x]) | | cselect :: Cond x -> x -> [x] -> (Bool, x) | | access :: St x (Bool, y) -> y -> [x] -> (Bool, y, [x]) | | accessList :: St x y -> [x] -> ([y], [x]) | | remove :: Cond x -> x -> [x] -> (Bool, x, [x]) | | uremove :: UCond x -> x -> [x] -> (Bool, x, [x]) | | creplace :: Cond x -> x -> [x] -> (Bool, [x]) | | ucreplace :: UCond x -> x -> [x] -> (Bool, [x]) | | replaceOrAppend :: Cond x -> x -> [x] -> [x] | | ureplaceOrAppend :: UCond x -> x -> [x] -> [x] | | removeCheck :: (Eq x) => x -> [x] -> (Bool, [x]) | | removeSpecialChars :: [Char] -> String -> String | | disjointLists :: (Eq x) => [x] -> [x] -> Bool | | noDuplicates :: (Eq x) => [x] -> Bool | | unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) | | stateMapM :: (Monad m) => (x -> s -> m (y, s)) -> [x] -> s -> m ([y], s) | | foldrM :: (Monad m) => (x -> s -> m s) -> s -> [x] -> m s | | sequenceMap :: (Monad m) => (x -> m a) -> [x] -> m [a] | | ssequence :: (Monad m) => [s -> m (a, s)] -> s -> m ([a], s) | | gather :: (Eq b) => [(a, b)] -> [([a], b)] | | dumpFatalError :: String -> String -> String -> x | | dummy :: String -> x | | module Graphics.UI.ObjectIO.StdIOCommon |
|
|
|
Common definitions |
|
Type declarations |
|
type St s a = s -> (a, s) |
State transformer |
|
type Cond x = x -> Bool |
Simple predicate |
|
type UCond x = x -> (Bool, x) |
Predicate which returns its updated argument |
|
Function declarations |
|
toSt :: (x -> y) -> St x y |
This function is convenient for lifting a function to a St transformer. |
|
setBetween :: Int -> Int -> Int -> Int |
|
isBetween :: Int -> Int -> Int -> Bool |
|
minmax :: Int -> Int -> (Int, Int) |
|
fst3snd3 :: (a, b, c) -> (a, b) |
|
fst3thd3 :: (a, b, c) -> (a, c) |
|
snd3thd3 :: (a, b, c) -> (b, c) |
|
eqfst2id :: (Eq a) => a -> (a, b) -> Bool |
|
eqfst3id :: (Eq a) => a -> (a, b, c) -> Bool |
|
Bound type |
|
data Bound |
|
|
Operations |
|
zeroBound :: Bound -> Bool |
|
decBound :: Bound -> Bound |
|
incBound :: Bound -> Bound |
|
Calculation rules on Point2s, Sizes, Rectangles and Vector2s: |
|
data Rect |
|
|
Function declarations |
|
addPointSize :: Size -> Point2 -> Point2 |
|
rectangleToRect :: Rectangle -> Rect |
|
rectToRectangle :: Rect -> Rectangle |
|
isEmptyRect :: Rect -> Bool |
|
isEmptyRectangle :: Rectangle -> Bool |
|
pointInRect :: Point2 -> Rect -> Bool |
|
pointInRectangle :: Point2 -> Rectangle -> Bool |
|
posSizeToRect :: Point2 -> Size -> Rect |
|
posSizeToRectangle :: Point2 -> Size -> Rectangle |
|
sizeToRect :: Size -> Rect |
|
sizeToRectangle :: Size -> Rectangle |
|
rectSize :: Rect -> Size |
|
disjointRects :: Rect -> Rect -> Bool |
|
intersectRects :: Rect -> Rect -> Rect |
|
subtractRects :: Rect -> Rect -> [Rect] |
|
Class declarations |
|
class AddVector a where |
|
|
class SubVector a where |
|
|
class ToTuple a where |
|
|
class FromTuple a where |
|
|
class ToTuple4 a where |
|
|
class FromTuple4 a where |
|
|
List operations |
|
isSingleton :: [x] -> Bool |
|
initLast :: [x] -> ([x], x) |
|
split :: Int -> [x] -> ([x], [x]) |
|
condMap :: Cond x -> IdFun x -> [x] -> (Bool, [x]) |
|
uspan :: UCond a -> [a] -> ([a], [a]) |
|
filterMap :: (x -> (Bool, y)) -> [x] -> [y] |
|
stateMap :: (x -> s -> (y, s)) -> [x] -> s -> ([y], s) |
|
ucontains :: UCond x -> [x] -> (Bool, [x]) |
|
cselect :: Cond x -> x -> [x] -> (Bool, x) |
|
access :: St x (Bool, y) -> y -> [x] -> (Bool, y, [x]) |
|
accessList :: St x y -> [x] -> ([y], [x]) |
|
remove :: Cond x -> x -> [x] -> (Bool, x, [x]) |
|
uremove :: UCond x -> x -> [x] -> (Bool, x, [x]) |
|
creplace :: Cond x -> x -> [x] -> (Bool, [x]) |
|
ucreplace :: UCond x -> x -> [x] -> (Bool, [x]) |
|
replaceOrAppend :: Cond x -> x -> [x] -> [x] |
|
ureplaceOrAppend :: UCond x -> x -> [x] -> [x] |
|
removeCheck :: (Eq x) => x -> [x] -> (Bool, [x]) |
|
removeSpecialChars :: [Char] -> String -> String |
|
disjointLists :: (Eq x) => [x] -> [x] -> Bool |
|
noDuplicates :: (Eq x) => [x] -> Bool |
|
unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d]) |
|
stateMapM :: (Monad m) => (x -> s -> m (y, s)) -> [x] -> s -> m ([y], s) |
|
foldrM :: (Monad m) => (x -> s -> m s) -> s -> [x] -> m s |
|
sequenceMap :: (Monad m) => (x -> m a) -> [x] -> m [a] |
|
ssequence :: (Monad m) => [s -> m (a, s)] -> s -> m ([a], s) |
|
gather :: (Eq b) => [(a, b)] -> [([a], b)] |
|
Error generation |
|
dumpFatalError :: String -> String -> String -> x |
Error generation rule.
Evaluation causes termination with the message:
Fatal error in rule <rule> [module] <message> . |
|
dummy :: String -> x |
Universal dummy value.
Evaluation causes termination with the message:
Fatal error: dummy evaluated! <message> . |
|
A visible module |
|
module Graphics.UI.ObjectIO.StdIOCommon |
|
Produced by Haddock version 0.3 |