GenI-0.22.0.1: A natural language generator (specifically, an FB-LTAG surface realiser)

Safe HaskellSafe-Infered

NLP.GenI.General

Contents

Description

This module provides some very generic, non-GenI specific functions on strings, trees and other miscellaneous odds and ends. Whenever possible, one should try to replace these functions with versions that are available in the standard libraries, or the Haskell platform ones, or on hackage.

Synopsis

IO

ePutStr :: String -> IO ()Source

putStr on stderr

Strings

dropTillIncluding :: Char -> String -> StringSource

Drop all characters up to and including the one in question

toUpperHead :: String -> StringSource

Make the first character of a string upper case

toLowerHead :: String -> StringSource

Make the first character of a string lower case

toAlphaNum :: String -> [AlphaNum]Source

An alphanumeric sort is one where you treat the numbers in the string as actual numbers. An alphanumeric sort would put x2 before x100, because 2 < 10, wheraeas a naive sort would put it the other way around because the characters 1 < 2. To sort alphanumerically, just 'sortBy (comparing toAlphaNum)'

clumpBy :: (a -> Int) -> Int -> [a] -> [[a]]Source

break a list of items into sublists of length < the clump size, taking into consideration that each item in the clump will have a single gap of padding interspersed

any item whose length is greater than the clump size is put into a clump by itself

given a length function clumpBy (length.show) 8 [hello, this, is, a, list]

Triples

first3 :: (a -> a2) -> (a, b, c) -> (a2, b, c)Source

second3 :: (b -> b2) -> (a, b, c) -> (a, b2, c)Source

third3 :: (c -> c2) -> (a, b, c) -> (a, b, c2)Source

fst3 :: (a, b, c) -> aSource

snd3 :: (a, b, c) -> bSource

thd3 :: (a, b, c) -> cSource

Lists

map' :: (a -> b) -> [a] -> [b]Source

A strict version of map

buckets :: Ord b => (a -> b) -> [a] -> [(b, [a])]Source

isEmptyIntersect :: Eq a => [a] -> [a] -> BoolSource

True if the intersection of two lists is empty.

groupByFM :: Ord b => (a -> b) -> [a] -> Map b [a]Source

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.

insertToListMap :: Ord b => b -> a -> Map b [a] -> Map b [a]Source

histogram :: Ord a => [a] -> Map a IntSource

combinations :: [[a]] -> [[a]]Source

mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b]Source

repList :: (a -> Bool) -> (a -> a) -> [a] -> [a]Source

Return the list, modifying only the first matching item.

Trees

mapTree' :: (a -> b) -> Tree a -> Tree bSource

Strict version of mapTree (for non-strict, just use fmap)

filterTree :: (a -> Bool) -> Tree a -> [a]Source

Like filter, except on Trees. Filter might not be a good name, though, because we return a list of nodes, not a tree.

treeLeaves :: Tree a -> [a]Source

The leaf nodes of a Tree

preTerminals :: Tree a -> [(a, a)]Source

Return pairs of (parent, terminal)

repNodeSource

Arguments

:: (Tree a -> Tree a)

replacement function

-> (Tree a -> Bool)

filtering function

-> Tree a 
-> Maybe (Tree a) 

repNode fn filt t returns a version of t in which the first node which filt matches is transformed using fn.

repAllNode :: (Tree a -> Tree a) -> (Tree a -> Bool) -> Tree a -> Tree aSource

Like repNode except that it performs the operations on all nodes that match and doesn't care if any nodes match or not

listRepNodeSource

Arguments

:: (Tree a -> Tree a)

replacement function

-> (Tree a -> Bool)

filtering function

-> [Tree a]

nodes

-> ([Tree a], Bool) 

Like repNode but on a list of tree nodes

repNodeByNodeSource

Arguments

:: (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.

Intervals

(!+!) :: Interval -> Interval -> IntervalSource

Add two intervals

ival :: Int -> IntervalSource

ival x builds a trivial interval from x to x

Bit vectors

showBitVector :: Int -> BitVector -> StringSource

displays a bit vector, using a minimum number of bits

Errors, logging and exceptions

geniBug :: String -> aSource

errors specifically in GenI, which is very likely NOT the user's fault.

mkLogname :: Typeable a => a -> StringSource

The module name for an arbitrary data type