gf-3.1.6.2: Grammatical Framework

Portabilityportable
Stabilitystable
MaintainerAarne Ranta

PGF

Contents

Description

This module is an Application Programming Interface to load and interpret grammars compiled in Portable Grammar Format (PGF). The PGF format is produced as a final output from the GF compiler. The API is meant to be used for embedding GF grammars in Haskell programs

Synopsis

PGF

data PGF Source

An abstract data type representing multilingual grammar in Portable Grammar Format.

Instances

Binary PGF 

readPGF :: FilePath -> IO PGFSource

Reads file in Portable Grammar Format and produces PGF structure. The file is usually produced with:

 $ gf -make <grammar file name>

Identifiers

data CId Source

An abstract data type that represents identifiers for functions and categories in PGF.

Instances

Eq CId 
Ord CId 
Read CId 
Show CId 
Binary CId 

mkCId :: String -> CIdSource

Creates a new identifier from String

showCId :: CId -> StringSource

Renders the identifier as String

readCId :: String -> Maybe CIdSource

Reads an identifier from String. The function returns Nothing if the string is not valid identifier.

Languages

type Language = CIdSource

This is just a CId with the language name. A language name is the identifier that you write in the top concrete or abstract module in GF after the concrete/abstract keyword. Example:

 abstract Lang = ...
 concrete LangEng of Lang = ...

languages :: PGF -> [Language]Source

List of all languages available in the given grammar.

abstractName :: PGF -> LanguageSource

The abstract language name is the name of the top-level abstract module

languageCode :: PGF -> Language -> Maybe StringSource

Gets the RFC 4646 language tag of the language which the given concrete syntax implements, if this is listed in the source grammar. Example language tags include "en" for English, and "en-UK" for British English.

Types

data Type Source

To read a type from a String, use readType.

Instances

Eq Type 
Ord Type 
Show Type 
Binary Type 

type Hypo = (BindType, CId, Type)Source

Hypo represents a hypothesis in a type i.e. in the type A -> B, A is the hypothesis

showType :: [CId] -> Type -> StringSource

renders type as String. The list of identifiers is the list of all free variables in the expression in order reverse to the order of binding.

readType :: String -> Maybe TypeSource

Reads a Type from a String.

mkType :: [Hypo] -> CId -> [Expr] -> TypeSource

creates a type from list of hypothesises, category and list of arguments for the category. The operation mkType [h_1,...,h_n] C [e_1,...,e_m] will create h_1 -> ... -> h_n -> C e_1 ... e_m

mkHypo :: Type -> HypoSource

creates hypothesis for non-dependent type i.e. A

mkDepHypo :: CId -> Type -> HypoSource

creates hypothesis for dependent type i.e. (x : A)

mkImplHypo :: CId -> Type -> HypoSource

creates hypothesis for dependent type with implicit argument i.e. ({x} : A)

categories :: PGF -> [CId]Source

List of all categories defined in the given grammar. The categories are defined in the abstract syntax with the 'cat' keyword.

startCat :: PGF -> TypeSource

The start category is defined in the grammar with the 'startcat' flag. This is usually the sentence category but it is not necessary. Despite that there is a start category defined you can parse with any category. The start category definition is just for convenience.

Functions

functions :: PGF -> [CId]Source

List of all functions defined in the abstract syntax

functionType :: PGF -> CId -> Maybe TypeSource

The type of a given function

Expressions & Trees

Tree

type Tree = ExprSource

Tree is the abstract syntax representation of a given sentence in some concrete syntax. Technically Tree is a type synonym of Expr.

Expr

data Expr Source

An expression in the abstract syntax of the grammar. It could be both parameter of a dependent type or an abstract syntax tree for for some sentence.

Instances

showExpr :: [CId] -> Expr -> StringSource

renders expression as String. The list of identifiers is the list of all free variables in the expression in order reverse to the order of binding.

readExpr :: String -> Maybe ExprSource

parses String as an expression

mkApp :: CId -> [Expr] -> ExprSource

Constructs an expression by applying a function to a list of expressions

unApp :: Expr -> Maybe (CId, [Expr])Source

Decomposes an expression into application of function

mkStr :: String -> ExprSource

Constructs an expression from string literal

unStr :: Expr -> Maybe StringSource

Decomposes an expression into string literal

mkInt :: Int -> ExprSource

Constructs an expression from integer literal

unInt :: Expr -> Maybe IntSource

Decomposes an expression into integer literal

mkDouble :: Double -> ExprSource

Constructs an expression from real number literal

unDouble :: Expr -> Maybe DoubleSource

Decomposes an expression into real number literal

mkMeta :: ExprSource

Constructs an expression which is meta variable

isMeta :: Expr -> BoolSource

Checks whether an expression is a meta variable

Operations

Linearization

linearize :: PGF -> Language -> Tree -> StringSource

Linearizes given expression as string in the language

linearizeAllLang :: PGF -> Tree -> [(Language, String)]Source

Linearizes given expression as string in all languages available in the grammar.

linearizeAll :: PGF -> Tree -> [String]Source

The same as linearizeAllLang but does not return the language.

showPrintName :: PGF -> Language -> CId -> StringSource

Show the printname of function or category

Parsing

parse :: PGF -> Language -> Type -> String -> [Tree]Source

Tries to parse the given string in the specified language and to produce abstract syntax expression. An empty list is returned if the parsing is not successful. The list may also contain more than one element if the grammar is ambiguous. Throws an exception if the given language cannot be used for parsing, see canParse.

parseAllLang :: PGF -> Type -> String -> [(Language, [Tree])]Source

Tries to parse the given string with all available languages. Languages which cannot be used for parsing (see canParse) are ignored. The returned list contains pairs of language and list of abstract syntax expressions (this is a list, since grammars can be ambiguous). Only those languages for which at least one parsing is possible are listed.

parseAll :: PGF -> Type -> String -> [[Tree]]Source

The same as parseAllLang but does not return the language.

Evaluation

compute :: PGF -> Expr -> ExprSource

Converts an expression to normal form

Type Checking

The type checker in PGF does both type checking and renaming i.e. it verifies that all identifiers are declared and it distinguishes between global function or type indentifiers and variable names. The type checker should always be applied on expressions entered by the user i.e. those produced via functions like readType and readExpr because otherwise unexpected results could appear. All typechecking functions returns updated versions of the input types or expressions because the typechecking could also lead to metavariables instantiations.

checkType :: PGF -> Type -> Either TcError TypeSource

Check whether a given type is consistent with the abstract syntax of the grammar.

checkExpr :: PGF -> Expr -> Type -> Either TcError ExprSource

Checks an expression against a specified type.

inferExpr :: PGF -> Expr -> Either TcError (Expr, Type)Source

Tries to infer the type of a given expression. Note that even if the expression is type correct it is not always possible to infer its type in the GF type system. In this case the function returns the CannotInferType error.

data TcError Source

If an error occurs in the typechecking phase the type checker returns not a plain text error message but a TcError structure which describes the error.

Constructors

UnknownCat CId

Unknown category name was found.

UnknownFun CId

Unknown function name was found.

WrongCatArgs [CId] Type CId Int Int

A category was applied to wrong number of arguments. The first integer is the number of expected arguments and the second the number of given arguments. The [CId] argument is the list of free variables in the type. It should be used for the showType function.

TypeMismatch [CId] Expr Type Type

The expression is not of the expected type. The first type is the expected type, while the second is the inferred. The [CId] argument is the list of free variables in both the expression and the type. It should be used for the showType and showExpr functions.

NotFunType [CId] Expr Type

Something that is not of function type was applied to an argument.

CannotInferType [CId] Expr

It is not possible to infer the type of an expression.

UnresolvedMetaVars [CId] Expr [MetaId]

Some metavariables have to be instantiated in order to complete the typechecking.

UnexpectedImplArg [CId] Expr

Implicit argument was passed where the type doesn't allow it

ppTcError :: TcError -> DocSource

Renders the type checking error to a document. See Text.PrettyPrint.

Word Completion (Incremental Parsing)

completeSource

Arguments

:: PGF 
-> Language 
-> Type 
-> String 
-> [String]

Possible completions, including the given input.

Complete the last word in the given string. If the input is empty or ends in whitespace, the last word is considred to be the empty string. This means that the completions will be all possible next words.

data ParseState Source

An abstract data type whose values represent the current state in an incremental parser.

initState :: PGF -> Language -> Type -> ParseStateSource

Creates an initial parsing state for a given language and startup category.

nextState :: ParseState -> String -> Either ErrorState ParseStateSource

From the current state and the next token nextState computes a new state, where the token is consumed and the current position is shifted by one. If the new token cannot be accepted then an error state is returned.

getCompletions :: ParseState -> String -> Map String ParseStateSource

If the next token is not known but only its prefix (possible empty prefix) then the getCompletions function can be used to calculate the possible next words and the consequent states. This is used for word completions in the GF interpreter.

extractTrees :: ParseState -> Type -> [Tree]Source

This function extracts the list of all completed parse trees that spans the whole input consumed so far. The trees are also limited by the category specified, which is usually the same as the startup category.

Generation

generateRandom :: PGF -> Type -> IO [Expr]Source

Generates an infinite list of random abstract syntax expressions. This is usefull for tree bank generation which after that can be used for grammar testing.

generateAll :: PGF -> Type -> [Expr]Source

The same as generateAllDepth but does not limit the depth in the generation, and doesn't give an initial expression.

generateAllDepth :: Maybe Expr -> PGF -> Type -> Maybe Int -> [Expr]Source

Generates an exhaustive possibly infinite list of abstract syntax expressions. A depth can be specified to limit the search space.

generateRandomFrom :: Maybe Expr -> Maybe Probabilities -> StdGen -> PGF -> Type -> [Expr]Source

Morphological Analysis

Visualizations

Browsing