gf-3.10: Grammatical Framework

MaintainerKrasimir Angelov
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

PGF2

Contents

Description

This module is an Application Programming Interface to load and interpret grammars compiled in the Portable Grammar Format (PGF). The PGF format is produced as the 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.

readPGF :: FilePath -> IO PGF Source #

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

$ gf -make <grammar file name>

Identifiers

type CId = String Source #

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

Abstract syntax

type AbsName Source #

Arguments

 = CId

Name of abstract syntax

abstractName :: PGF -> AbsName Source #

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

Categories

type Cat Source #

Arguments

 = CId

Name of syntactic category

categories :: PGF -> [Cat] Source #

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

Functions

type Fun Source #

Arguments

 = CId

Name of function

functions :: PGF -> [Fun] Source #

List of all functions defined in the abstract syntax

functionsByCat :: PGF -> Cat -> [Fun] Source #

List of all functions defined for a category

functionType :: PGF -> Fun -> Maybe Type Source #

The type of a function

functionIsConstructor :: PGF -> Fun -> Bool Source #

The type of a function

hasLinearization :: Concr -> Fun -> Bool Source #

Returns True if there is a linearization defined for that function in that language

Expressions

data Expr Source #

Instances

Eq Expr Source # 

Methods

(==) :: Expr -> Expr -> Bool #

(/=) :: Expr -> Expr -> Bool #

Show Expr Source # 

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

showExpr :: [CId] -> Expr -> String Source #

renders an expression as a 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 Expr Source #

parses a String as an expression

mkAbs :: BindType -> CId -> Expr -> Expr Source #

Constructs an expression by lambda abstraction

unAbs :: Expr -> Maybe (BindType, CId, Expr) Source #

Decomposes an expression into an abstraction and a body

mkApp :: Fun -> [Expr] -> Expr Source #

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

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

Decomposes an expression into an application of a function

mkStr :: String -> Expr Source #

Constructs an expression from a string literal

unStr :: Expr -> Maybe String Source #

Decomposes an expression into a string literal

mkInt :: Int -> Expr Source #

Constructs an expression from an integer literal

unInt :: Expr -> Maybe Int Source #

Decomposes an expression into an integer literal

mkFloat :: Double -> Expr Source #

Constructs an expression from a real number

unFloat :: Expr -> Maybe Double Source #

Decomposes an expression into a real number literal

mkMeta :: Int -> Expr Source #

Constructs a meta variable as an expression

unMeta :: Expr -> Maybe Int Source #

Decomposes an expression into a meta variable

mkCId :: t -> t Source #

this functions is only for backward compatibility with the old Haskell runtime

Types

data Type Source #

Instances

type Hypo = (BindType, CId, Type) Source #

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

data BindType Source #

Constructors

Explicit 
Implicit 

startCat :: PGF -> Type Source #

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.

readType :: String -> Maybe Type Source #

parses a String as a type

showType :: [CId] -> Type -> String Source #

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

showContext :: [CId] -> [Hypo] -> String Source #

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

mkType :: [Hypo] -> CId -> [Expr] -> Type Source #

creates a type from a list of hypothesises, a category and a 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

unType :: Type -> ([Hypo], CId, [Expr]) Source #

Decomposes a type into a list of hypothesises, a category and a list of arguments for the category.

Type checking

checkExpr :: PGF -> Expr -> Type -> Either String Expr Source #

Checks an expression against a specified type.

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

Tries to infer the type of an 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 an error.

checkType :: PGF -> Type -> Either String Type Source #

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

Computing

Concrete syntax

type ConcName Source #

Arguments

 = CId

Name of concrete syntax

languages :: PGF -> Map ConcName Concr Source #

List of all languages available in the grammar.

concreteName :: Concr -> ConcName Source #

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

Linearization

linearize :: Concr -> Expr -> String Source #

Linearizes an expression as a string in the language

linearizeAll :: Concr -> Expr -> [String] Source #

Generates all possible linearizations of an expression

tabularLinearize :: Concr -> Expr -> [(String, String)] Source #

Generates a table of linearizations for an expression

tabularLinearizeAll :: Concr -> Expr -> [[(String, String)]] Source #

Generates a table of linearizations for an expression

type FId = Int Source #

data BracketedString Source #

BracketedString represents a sentence that is linearized as usual but we also want to retain the 'brackets' that mark the beginning and the end of each constituent.

Constructors

Leaf String

this is the leaf i.e. a single token

BIND

the surrounding tokens must be bound together

Bracket CId !FId !LIndex CId [BracketedString]

this is a bracket. The CId is the category of the phrase. The FId is an unique identifier for every phrase in the sentence. For context-free grammars i.e. without discontinuous constituents this identifier is also unique for every bracket. When there are discontinuous phrases then the identifiers are unique for every phrase but not for every bracket since the bracket represents a constituent. The different constituents could still be distinguished by using the constituent index i.e. LIndex. If the grammar is reduplicating then the constituent indices will be the same for all brackets that represents the same constituent. The second CId is the name of the abstract function that generated this phrase.

showBracketedString :: BracketedString -> String Source #

Renders the bracketed string as a string where the brackets are shown as (S ...) where S is the category.

flattenBracketedString :: BracketedString -> [String] Source #

Extracts the sequence of tokens from the bracketed string

Parsing

data ParseOutput Source #

This data type encodes the different outcomes which you could get from the parser.

Constructors

ParseFailed Int String

The integer is the position in number of unicode characters where the parser failed. The string is the token where the parser have failed.

ParseOk [(Expr, Float)]

If the parsing and the type checking are successful we get a list of abstract syntax trees. The list should be non-empty.

ParseIncomplete

The sentence is not complete.

parseWithHeuristics Source #

Arguments

:: Concr

the language with which we parse

-> Type

the start category

-> String

the input sentence

-> Double

the heuristic factor. A negative value tells the parser to lookup up the default from the grammar flags

-> [(Cat, Int -> Int -> Maybe (Expr, Float, Int))]

a list of callbacks for literal categories. The arguments of the callback are: the index of the constituent for the literal category; the input sentence; the current offset in the sentence. If a literal has been recognized then the output should be Just (expr,probability,end_offset)

-> ParseOutput 

Sentence Lookup

lookupSentence Source #

Arguments

:: Concr

the language with which we parse

-> Type

the start category

-> String

the input sentence

-> [(Expr, Float)] 

Generation

generateAll :: PGF -> Type -> [(Expr, Float)] Source #

Generates an exhaustive possibly infinite list of all abstract syntax expressions of the given type. The expressions are ordered by their probability.

Morphological Analysis

Visualizations

graphvizAbstractTree :: PGF -> GraphvizOptions -> Expr -> String Source #

Renders an abstract syntax tree in a Graphviz format.

Exceptions

Grammar specific callbacks

literalCallbacks :: [(AbsName, [(Cat, LiteralCallback)])] Source #

Callbacks for the App grammar