 | libGenI-0.16.1: A natural language generator (specifically, an FB-LTAG surface realiser) | Contents | Index |
|
|
|
|
| Synopsis |
|
| ePutStrLn :: String -> IO () | | | ePutStr :: String -> IO () | | | eFlush :: IO () | | | trim :: String -> String | | | dropTillIncluding :: Char -> String -> String | | | toLowerHead :: String -> String | | | toUpperHead :: String -> String | | | | | toAlphaNum :: String -> [AlphaNum] | | | isNumber :: Char -> Bool | | | fst3 :: (a, b, c) -> a | | | snd3 :: (a, b, c) -> b | | | thd3 :: (a, b, c) -> c | | | equating :: Eq b => (a -> b) -> (a -> a -> Bool) | | | comparing :: Ord b => (a -> b) -> (a -> a -> Ordering) | | | tail_ :: [a] -> [a] | | | map' :: (a -> b) -> [a] -> [b] | | | wordsBy :: Eq a => a -> [a] -> [[a]] | | | boundsCheck :: Int -> [a] -> Bool | | | isEmptyIntersect :: Eq a => [a] -> [a] -> Bool | | | groupByFM :: Ord b => (a -> b) -> [a] -> (Map b [a]) | | | multiGroupByFM :: Ord b => (a -> [b]) -> [a] -> (Map b [a]) | | | insertToListMap :: Ord b => b -> a -> Map b [a] -> Map b [a] | | | groupAndCount :: (Eq a, Ord a) => [a] -> [(a, Int)] | | | combinations :: [[a]] -> [[a]] | | | mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b] | | | repList :: (a -> Bool) -> (a -> a) -> [a] -> [a] | | | mapTree' :: (a -> b) -> Tree a -> Tree b | | | filterTree :: (a -> Bool) -> Tree a -> [a] | | | treeLeaves :: Tree a -> [a] | | | preTerminals :: Tree a -> [(a, a)] | | | repNode :: (Tree a -> Tree a) -> (Tree a -> Bool) -> Tree a -> Maybe (Tree a) | | | repAllNode :: (Tree a -> Tree a) -> (Tree a -> Bool) -> Tree a -> Tree a | | | listRepNode :: (Tree a -> Tree a) -> (Tree a -> Bool) -> [Tree a] -> ([Tree a], Bool) | | | repNodeByNode :: a -> Bool -> a -> Tree a -> Tree a | | | geniBug :: String -> a | | | basename :: FilePath -> FilePath | | | (///) :: FilePath -> FilePath -> FilePath | | | type Interval = (Int, Int) | | | (!+!) :: Interval -> Interval -> Interval | | | ival :: Int -> Interval | | | showInterval :: Interval -> String | | | type BitVector = Integer | | | showBitVector :: Int -> BitVector -> String | | | showTable :: [String] -> [a] -> (a -> [String]) -> String | | | readFile' :: FilePath -> IO String | | | buf_size :: Int | | | lazySlurp :: ForeignPtr Word8 -> Int -> Int -> IO String | | | data TimeOut = TimeOut Unique | | | timeOutTc :: TyCon | | | withTimeout :: Integer -> IO a -> IO a -> IO a | | | exitTimeout :: IO () |
|
|
| Documentation |
|
| ePutStrLn :: String -> IO () |
|
| ePutStr :: String -> IO () |
|
| eFlush :: IO () |
|
| trim :: String -> String |
|
| dropTillIncluding :: Char -> String -> String |
| Drop all characters up to and including the one in question
|
|
| toLowerHead :: String -> String |
|
| toUpperHead :: String -> String |
|
| data AlphaNum |
| Constructors | | Instances | |
|
|
| toAlphaNum :: String -> [AlphaNum] |
|
| isNumber :: Char -> Bool |
|
| fst3 :: (a, b, c) -> a |
|
| snd3 :: (a, b, c) -> b |
|
| thd3 :: (a, b, c) -> c |
|
| equating :: Eq b => (a -> b) -> (a -> a -> Bool) |
|
| comparing :: Ord b => (a -> b) -> (a -> a -> Ordering) |
|
| tail_ :: [a] -> [a] |
| A forgiving version of tail : if you give it the empty list, it returns the empty list
|
|
| map' :: (a -> b) -> [a] -> [b] |
| A strict version of map
|
|
| wordsBy :: Eq a => a -> [a] -> [[a]] |
|
| boundsCheck :: Int -> [a] -> Bool |
| Makes sure that index s is in the bounds of list l.
Surely there must be some more intelligent way to deal with this.
|
|
| isEmptyIntersect :: Eq a => [a] -> [a] -> Bool |
|
| groupByFM :: Ord b => (a -> b) -> [a] -> (Map b [a]) |
| Serves the same function as groupBy. It groups together
items by some property they have in common. The difference is that the
property is used as a key to a Map that you can lookup.
|
|
| multiGroupByFM :: Ord b => (a -> [b]) -> [a] -> (Map b [a]) |
| Same as groupByFM, except that we let an item appear in
multiple groups. The fn extracts the property from the item,
and returns multiple results in the form of a list
|
|
| insertToListMap :: Ord b => b -> a -> Map b [a] -> Map b [a] |
|
| groupAndCount :: (Eq a, Ord a) => [a] -> [(a, Int)] |
|
| combinations :: [[a]] -> [[a]] |
|
| mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b] |
|
| repList :: (a -> Bool) -> (a -> a) -> [a] -> [a] |
| Return the list, modifying only the first matching item.
|
|
| mapTree' :: (a -> b) -> Tree a -> Tree b |
| Strict version of mapTree (for non-strict, just use fmap)
|
|
| filterTree :: (a -> Bool) -> Tree a -> [a] |
|
| treeLeaves :: Tree a -> [a] |
|
| preTerminals :: Tree a -> [(a, a)] |
| Return pairs of (parent, terminal)
|
|
| repNode :: (Tree a -> Tree a) -> (Tree a -> Bool) -> Tree a -> Maybe (Tree a) |
|
| repAllNode :: (Tree a -> Tree a) -> (Tree a -> Bool) -> Tree a -> Tree a |
| Like repNode except that it performs the operations on
all nodes that match and doesn't care if any nodes match
or not
|
|
| listRepNode :: (Tree a -> Tree a) -> (Tree a -> Bool) -> [Tree a] -> ([Tree a], Bool) |
|
| repNodeByNode |
| :: | | | => a -> Bool | which node?
| | -> a | | | -> Tree a | | | -> Tree a | | | Replace a node in the tree in-place with another node; keep the
children the same. If the node is not found in the tree, or if
there are multiple instances of the node, this is treated as an
error.
|
|
|
| geniBug :: String -> a |
| errors specifically in GenI, which is very likely NOT the user's fault.
|
|
| basename :: FilePath -> FilePath |
|
| (///) :: FilePath -> FilePath -> FilePath |
|
| type Interval = (Int, Int) |
|
| (!+!) :: Interval -> Interval -> Interval |
|
| ival :: Int -> Interval |
|
| showInterval :: Interval -> String |
|
| type BitVector = Integer |
|
| showBitVector :: Int -> BitVector -> String |
| displays a bit vector, using a minimum number of bits
|
|
| showTable :: [String] -> [a] -> (a -> [String]) -> String |
|
| readFile' :: FilePath -> IO String |
|
| buf_size :: Int |
|
| lazySlurp :: ForeignPtr Word8 -> Int -> Int -> IO String |
|
| data TimeOut |
| Constructors | | Instances | |
|
|
| timeOutTc :: TyCon |
|
| withTimeout |
| :: | | | => Integer | | | -> IO a | action to run upon timing out
| | -> IO a | main action to run
| | -> IO a | |
|
|
| exitTimeout :: IO () |
| Like exitFailure, except that we return with a code that we reserve for timing out
|
|
| Produced by Haddock version 2.1.0 |