gf-3.7.1: Grammatical Framework

Safe HaskellNone
LanguageHaskell2010

GF.Support

Contents

Synopsis

Supporting infrastructure and system utilities

Source locations

data L a Source

Attaching location information

Constructors

L Location a 

Instances

Functor L Source 
Show a => Show (L a) Source 
Pretty a => Pretty (L a) Source 

unLoc :: L a -> a Source

noLoc :: a -> L a Source

ppL :: (Pretty a1, Pretty a2) => L a2 -> a1 -> Doc Source

Command line options

Option types

newtype Dump Source

Constructors

Dump Pass 

Option parsing

parseOptions Source

Arguments

:: ErrorMonad err 
=> [String]

list of string arguments

-> err (Options, [FilePath]) 

parseModuleOptions Source

Arguments

:: ErrorMonad err 
=> [String]

list of string arguments

-> err Options 

Option pretty-printing

optionsGFO :: Options -> [(String, Literal)] Source

Pretty-print the options that are preserved in .gfo files.

optionsPGF :: Options -> [(String, Literal)] Source

Pretty-print the options that are preserved in .pgf files.

Option manipulation

Checking specific options

flag :: (Flags -> a) -> Options -> a Source

renameEncoding :: String -> String Source

This is for bacward compatibility. Since GHC 6.12 we started using the native Unicode support in GHC but it uses different names for the code pages.

Setting specific options

Convenience methods for checking options

The Error monad

data Err a Source

Like Maybe type with error msgs

Constructors

Ok a 
Bad String 

Instances

err :: (String -> b) -> (a -> b) -> Err a -> b Source

Analogue of maybe

maybeErr :: ErrorMonad m => String -> Maybe a -> m a Source

Add msg s to Maybe failures

testErr :: ErrorMonad m => Bool -> String -> m () Source

fromErr :: a -> Err a -> a Source

Analogue of fromMaybe

errIn :: ErrorMonad m => String -> m a -> m a Source

lookupErr :: (ErrorMonad m, Eq a, Show a) => a -> [(a, b)] -> m b Source

Error monad class

class (Functor m, Monad m) => ErrorMonad m where Source

Minimal complete definition

raise, handle

Methods

raise :: String -> m a Source

handle :: m a -> (String -> m a) -> m a Source

handle_ :: m a -> m a -> m a Source

Instances

checks :: ErrorMonad m => [m a] -> m a Source

liftErr :: ErrorMonad m => Err a -> m a Source

Checking

checkUnique :: (Show a, Eq a) => [a] -> [String] Source

unifyMaybeBy :: (Eq b, Monad m) => (a -> b) -> Maybe a -> Maybe a -> m (Maybe a) Source

unifyMaybe :: (Eq a, Monad m) => Maybe a -> Maybe a -> m (Maybe a) Source

this is what happens when matching two values in the same module

Monadic operations on lists and pairs

mapPairListM :: Monad m => ((a, b) -> m c) -> [(a, b)] -> m [(a, c)] Source

mapPairsM :: Monad m => (b -> m c) -> [(a, b)] -> m [(a, c)] Source

pairM :: Monad m => (b -> m c) -> (b, b) -> m (c, c) Source

Binary search trees; now with FiniteMap

type BinTree a b = Map a b Source

isInBinTree :: Ord a => a -> BinTree a b -> Bool Source

lookupTree :: (ErrorMonad m, Ord a) => (a -> String) -> a -> BinTree a b -> m b Source

lookupTreeManyAll :: Ord a => (a -> String) -> [BinTree a b] -> a -> [b] Source

updateTree :: Ord a => (a, b) -> BinTree a b -> BinTree a b Source

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

filterBinTree :: Ord a => (a -> b -> Bool) -> BinTree a b -> BinTree a b Source

mapTree :: ((a, b) -> c) -> BinTree a b -> BinTree a c Source

tree2list :: BinTree a b -> [(a, b)] Source

Printing

(+++) :: String -> String -> String infixr 5 Source

(++-) :: String -> String -> String infixr 5 Source

(++++) :: String -> String -> String infixr 5 Source

(+++++) :: String -> String -> String infixr 5 Source

wrapLines :: Int -> String -> String Source

Thomas Hallgren's wrap lines

Topological sorting

topoTest :: Ord a => [(a, [a])] -> Either [a] [[a]] Source

Topological sorting with test of cyclicity

topoTest2 :: Ord a => [(a, [a])] -> Either [[a]] [[a]] Source

Topological sorting with test of cyclicity, new version /TH 2012-06-26

Misc

ifNull :: b -> ([a] -> b) -> [a] -> b Source

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

combinations is the same as sequence!!! peb 30/5-04

done :: Monad m => m () Source

return ()

iterFix :: Eq a => ([a] -> [a]) -> [a] -> [a] Source

Fix point iterator (for computing e.g. transitive closures or reachability)

chunks :: Eq a => a -> [a] -> [[a]] Source

chop into separator-separated parts

Files and IO

putIfVerb :: Output f => Options -> String -> f () Source

GF files path and library path manipulation

type InitPath Source

Arguments

 = String

the directory portion of a pathname

extendPathEnv :: MonadIO io => Options -> io [FilePath] Source

extends the search path with the gfLibraryPath and gfGrammarPathVar environment variables. Returns only existing paths.

Error handling in the IO monad

type IOE a = IO a Source

Was: newtype IOE a = IOE { appIOE :: IO (Err a) }

tryIOE :: IOE a -> IO (Err a) Source

Catch exceptions caused by calls to raise or fail in the IO monad. To catch all IO exceptions, use try instead.

useIOE :: a -> IOE a -> IO a Source

Print the error message and return a default value if the IO operation fails

maybeIO :: MonadIO f => IO a -> f (Maybe a) Source

Diagnostic output

class Monad m => Output m where Source

Instances

putPointE :: (MonadIO m, Output m) => Verbosity -> Options -> String -> m b -> m b Source

ioErrorText :: IOError -> String Source

Because GHC adds the confusing text "user error" for failures caused by calls to fail.

Timing

timeIt :: MonadIO m => m t -> m (Integer, t) Source

File IO

Reused

class Monad m => MonadIO m where

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Methods

liftIO :: IO a -> m a

Lift a computation from the IO monad.

Instances

MonadIO IO 
MonadIO m => MonadIO (CGIT m) 
MonadIO m => MonadIO (MaybeT m) 
MonadIO m => MonadIO (InputT m) 
MonadIO m => MonadIO (ListT m) 
MonadIO m => MonadIO (IdentityT m) 
MonadIO m => MonadIO (ReaderT r m) 
MonadIO m => MonadIO (ContT r m) 
MonadIO m => MonadIO (StateT s m) 
MonadIO m => MonadIO (StateT s m) 
MonadIO m => MonadIO (ExceptT e m) 
(Error e, MonadIO m) => MonadIO (ErrorT e m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

liftErr :: ErrorMonad m => Err a -> m a Source

Backwards compatible try and catch

catch :: IO a -> (IOError -> IO a) -> IO a Source

Console IO

Changing which character encoding to use for console IO

setConsoleEncoding :: IO () Source

Set the console encoding (for Windows, has no effect on Unix-like systems)

Console colors

data TermColors Source

Constructors

TermColors 

Fields

redFg, blueFg, restore :: String
 

Binary serialisation

class Binary t Source

The Binary class provides put and get, methods to encode and decode a Haskell value to a lazy ByteString. It mirrors the Read and Show classes for textual representation of Haskell types, and is suitable for serialising Haskell values to disk, over the network.

For parsing and generating simple external binary formats (e.g. C structures), Binary may be used, but in general is not suitable for complex protocols. Instead use the Put and Get primitives directly.

Instances of Binary should satisfy the following property:

decode . encode == id

That is, the get and put methods should be the inverse of each other. A range of instances are provided for basic Haskell types.

Minimal complete definition

put, get

Instances

Binary Bool Source 
Binary Char Source 
Binary Double Source 
Binary Float Source 
Binary Int Source 
Binary Int8 Source 
Binary Int16 Source 
Binary Int32 Source 
Binary Int64 Source 
Binary Integer Source 
Binary Ordering Source 
Binary Word Source 
Binary Word8 Source 
Binary Word16 Source 
Binary Word32 Source 
Binary Word64 Source 
Binary () Source 
Binary ByteString Source 
Binary ByteString Source 
Binary IntSet Source 
Binary RawIdent Source 
Binary a => Binary [a] Source 
(Binary a, Integral a) => Binary (Ratio a) Source 
Binary a => Binary (Maybe a) Source 
Binary e => Binary (IntMap e) Source 
(Ord a, Binary a) => Binary (Set a) Source 
Binary e => Binary (Tree e) Source 
Binary e => Binary (Seq e) Source 
Binary a => Binary (VersionTagged a) Source 
(Binary a, Binary b) => Binary (Either a b) Source 
(Binary a, Binary b) => Binary (a, b) Source 
(Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) Source 
(Binary i, Ix i, Binary e) => Binary (Array i e) Source 
(Ord k, Binary k, Binary e) => Binary (Map k e) Source 
(Binary a, Binary b, Binary c) => Binary (a, b, c) Source 
(Binary a, Binary b, Binary c, Binary d) => Binary (a, b, c, d) Source 
(Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a, b, c, d, e) Source 
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f) => Binary (a, b, c, d, e, f) Source 
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g) => Binary (a, b, c, d, e, f, g) Source 
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h) => Binary (a, b, c, d, e, f, g, h) Source 
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h, Binary i) => Binary (a, b, c, d, e, f, g, h, i) Source 
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h, Binary i, Binary j) => Binary (a, b, c, d, e, f, g, h, i, j) Source 

encode :: Binary a => a -> ByteString Source

Encode a value using binary serialisation to a lazy ByteString.

decode :: Binary a => ByteString -> a Source

Decode a value from a lazy ByteString, reconstructing the original structure.

encodeFile :: Binary a => FilePath -> a -> IO () Source

Lazily serialise a value to a file

This is just a convenience function, it's defined simply as:

encodeFile f = B.writeFile f . encode

So for example if you wanted to compress as well, you could use:

B.writeFile f . compress . encode

decodeFile :: Binary a => FilePath -> IO a Source

Lazily reconstruct a value previously written to a file.

This is just a convenience function, it's defined simply as:

decodeFile f = return . decode =<< B.readFile f

So for example if you wanted to decompress as well, you could use:

return . decode . decompress =<< B.readFile f