String
this delicious cheese is very Italian (English)
Language-neutral tree
Strings
questo formaggio delizioso è molto italiano (Italian, notice word order)
see maitsev juust on väga itaaliapärane (Estonian)
...
Benefit: n
translation descriptions, not n*n
Abstract syntax
abstract Hello = {
flags startcat = Greeting ;
cat Greeting ; Recipient ;
fun
Hello : Recipient -> Greeting ;
World, Mum, Friends : Recipient ;
}
Concrete syntax
concrete HelloEng of Hello = {
lincat Greeting, Recipient = {s : Str} ;
lin
Hello recip = {s = "hello" ++ recip.s} ;
World = {s = "world"} ;
Mum = {s = "mum"} ;
Friends = {s = "friends"} ;
}
Finnish
-- This is a comment
concrete HelloFin of Hello = {
lincat Greeting, Recipient = {s : Str} ;
lin
Hello recip = {s = "terve" ++ recip.s} ;
World
= {s = "maailma"} ;
Mum = {s = "äiti"} ;
Friends
= {s = "ystävät"} ;
}
Italian
{-
This is a multiline comment
-}
concrete HelloIta of Hello = {
lincat Greeting, Recipient = {s : Str} ;
lin
Hello recip = {s = "ciao" ++ recip.s} ;
World = {s = "mondo"} ;
Mum = {s = "mamma"} ;
Friends = {s = "amici"} ;
}
Greeting
, where we greet a Recipient
, which can be World
or Mum
or Friends
Hello
Greeting
is the default start category for parsing and generationHelloEng
of the abstract syntax Hello
Greeting
and Recipient
are records holding a single string in the field s
++
{ s : Str }
, { s
= "world" }
recip.s
Compile info PGF and load it
$ gf --make Hello???.gf
$ gf Hello.pgf
GF commandline examples
> parse "hello world"
Hello World
> parse "hello dad"
Unknown words: dad
> parse "world hello"
no tree found
> linearize Hello World
hello world
> parse -lang=HelloEng "hello friends" | linearize
terve ystävät
ciao amici
hello friends
Look at the internal grammar representation
> print_grammar
Token sequence
Tree
(f1 (f2 f3))
(f1 (f2 ?1))
Parse
Linearize
"do not"
and "don't"
Examples from MOLTO Phrasebook
Example from ACE-in-GF
p -lang=Dut "John ziet precies 2 personen , die slechts reizigers inspecteren ."
| l -lang=Ace,Fin
John sees exactly 2 persons who inspect nothing but travelers .
John näkee tasan 2 henkilöÃ
¤ , joka tarkastaa vain matkustajia .
John sees exactly 2 persons who nothing but travelers inspect .
John näkee tasan 2 henkilöÃ
¤ , jonka vain matkustajat tarkastavat .
abstract Unitconv = {
flags startcat = Unitconv ;
cat Unit ; Unitconv ;
fun
f1 : Unit -> Unit -> Unitconv ;
f2, f3: Unit ;
}
concrete UnitconvDut of Unitconv = {
lincat Unit, Unitconv = {s : Str} ;
lin
f1 x y = {s = "hoeveel is" ++ x.s ++ "in" ++ y.s ++ "?"} ;
f2 = {s = "mijl"} ;
f3 = {s = "nautische mijl" | "mijl"} ;
}
concrete UnitconvWolfram of Unitconv = {
lincat Unit, Unitconv = {s : Str} ;
lin
f1 x y = {s = "convert" ++ x.s ++ "to" ++ y.s} ;
f2 = {s = "mile"} ;
f3 = {s = "nmi"} ;
}
Parsing i.e. converting a string hoeveel is nautische mijl ... to tree(s)
Unitconv> parse -lang=Dut "hoeveel is nautische mijl in mijl ?"
f1 f3 f2
f1 f3 f3
Linearization i.e. converting a tree f1 f3 f2 to string(s)
Unitconv> linearize -treebank -list (f1 f3 f2)
UnitconvDut: hoeveel is nautische mijl in mijl ?, , hoeveel is mijl in mijl ?
UnitconvWolfram: convert nmi to mile
Translation i.e. parse + linearize
Unitconv> parse -lang=Dut "hoeveel is nautische mijl in mijl ?" | l -lang=Wolfram
convert nmi to mile
convert nmi to nmi
abstract Food = {
flags startcat = Phrase ;
cat
Phrase ; Item ; Kind ; Quality ;
fun
Is : Item -> Quality -> Phrase ;
This, That : Kind -> Item ;
QKind : Quality -> Kind -> Kind ;
Wine, Cheese, Fish : Kind ;
Very : Quality -> Quality ;
Fresh, Warm, Italian, Expensive, Delicious, Boring : Quality ;
}
concrete FoodEng of Food = {
lincat
Phrase, Item, Kind, Quality = {s : Str} ;
lin
Is item quality = {s = item.s ++ "is" ++ quality.s} ;
This kind = {s = "this" ++ kind.s} ;
That kind = {s = "that" ++ kind.s} ;
QKind quality kind = {s = quality.s ++ kind.s} ;
Wine = {s = "wine"} ;
Cheese = {s = "cheese"} ;
Fish = {s = "fish"} ;
Very quality = {s = "very" ++ quality.s} ;
Fresh = {s = "fresh"} ;
Warm = {s = "warm"} ;
Italian = {s = "Italian"} ;
Expensive = {s = "expensive"} ;
Delicious = {s = "delicious" | "exquisit" | "tasty"} ; -- NB: variants
Boring = {s = "boring"} ;
}
concrete FoodIta of Food = {
lincat
Phrase, Item, Kind, Quality = {s : Str} ;
lin
Is item quality = {s = item.s ++ "
è" ++ quality.s} ;
This kind = {s = "questo" ++ kind.s} ;
That kind = {s = "quel" ++ kind.s} ;
QKind quality kind = {s = kind.s ++ quality.s} ; -- NB: word order
Wine = {s = "vino"} ;
Cheese = {s = "formaggio"} ;
Fish = {s = "pesce"} ;
Very quality = {s = "molto" ++ quality.s} ;
Fresh = {s
= "fresco"} ;
Warm = {s = "caldo"} ;
Italian = {s = "italiano"} ;
Expensive = {s = "caro"} ;
Delicious = {s = "delizioso"} ;
Boring = {s = "noioso"} ;
}
++
{s = .. }
Example
Instead:
This kind = {s = "questo" ++ kind.s} ;
That kind = {s = "quel" ++ kind.s} ;
we want to write:
This = prefix "questo" ;
That = prefix "quel" ;
resource StringOper = {
oper
SS : Type = {s : Str} ;
ss : Str -> SS = \x -> {s
= x} ;
cc : SS -> SS -> SS = \x,y -> ss (x.s ++ y.s) ;
prefix : Str -> SS -> SS = \p,x -> ss (p ++ x.s) ;
}
Explanation
SS
becomes a shorthand for {s : Str}
(record with a single string)ss
constructs a SS
from a given string Str
cc
concatenates 2 SS
args and returns SS
prefix
is the same as cc
, but the 1st arg is a simple stringconcrete FoodEng of Food = open StringOper in {
lincat S, Item, Kind, Quality = SS ;
lin
Is item quality = cc item (prefix "is" quality) ;
This = prefix "this" ; -- same as: This k = prefix "this" k ;
That = prefix "that" ;
QKind k q = cc k q ;
Wine = ss "wine" ;
Cheese = ss "cheese" ;
Fish = ss "fish" ;
Very = prefix "very" ;
Fresh = ss "fresh" ;
Warm = ss "warm" ;
Italian = ss "Italian" ;
Expensive = ss "expensive" ;
Delicious = ss "delicious" ;
Boring = ss "boring" ;
}
Notice:
Wine
takes no arguments and has lincat SS
, ss "wine"
produces SS
This
takes 1 argument (SS
) and has lincat SS
, prefix "this"
also takes one argument (SS
) and produces SS
Idea: for readability reasons reuse the same name for different functions.
This cannot be done directly but can be done via the overload
statement.
oper mkN : overload {
mkN : (dog : Str) -> Noun ; -- regular nouns
mkN : (mouse,mice : Str) -> Noun ; -- irregular nouns
}
The definition can be also given at the same time:
oper mkN = overload {
mkN : (dog : Str) -> Noun = regNoun ;
mkN : (mouse,mice : Str) -> Noun = mkNoun ;
}
where regNoun
is an operator that takes a string and produces Noun
,
and mkNoun
is one that takes two strings as arguments.
abstract Morefood = Food, Fruit, Mushroom ** {
cat
Question ;
fun
QIs : Item -> Quality -> Question ;
Pizza : Kind ;
}
concrete MorefoodIta of Morefood = FoodIta, FruitIta ** open StringOper in {
lincat
Question = SS ;
lin
QIs item quality = ss (item.s ++ "
è" ++ quality.s) ;
Pizza = ss "pizza" ;
}
Fruit [Peach,Apple]
: include only Peach
and Apple
from Fruit
Fruit - [Peach,Apple]
: include everything but exclude Peach
and Apple
Parameter type Number
enumerating its constructors.
param Number = Sg | Pl ;
Table that depends on Number
used in a linearization type.
lincat Kind = {s : Number => Str} ;
The linearization of Cheese
is now a record that holds a table
whose leaves are strings. This models the fact that the form of Cheese
depends on Number
(parametric feature).
lin Cheese = {
s = table {
Sg => "cheese" ;
Pl => "cheeses"
}
} ;
To be able to extract the string (which we need for the surface form)
we use the selection operator !
, e.g.
table {Sg => "cheese" ; Pl => "cheeses"} ! Pl
which returns "cheeses".
Constructors can take arguments from other parameter types.
param Number = Sg | Pl ;
param VerbForm = VPresent Number | VPast | VPastPart | VPresPart ;
A table VerbForm => Str
:
table {
VPresent Sg => "drinks" ;
VPresent Pl => "drink" ;
VPast => "drank" ;
VPastPart => "drunk" ;
VPresPart => "drinking"
}
A word is really a more complex structure than a string.
oper regNoun : Str -> {s : Number => Str} = \dog -> {
s = table {
Sg => dog ;
Pl => dog + "s"
}
} ;
oper regVerb : Str -> {s : VerbForm => Str} = \talk -> {
s = table {
VPresent Sg => talk + "s" ;
VPresent Pl => talk ;
VPresPart => talk + "ing" ;
_ => talk + "ed" -- i.e. VPast (I asked), VPastPart (asked by)
}
} ;
Notice
+
for concatenating strings into a single token (can be applied only to strings known at compile time)_
applies to everything which the pattern matcher did not yet matchAbstract definition of Is
does not specify agreement restrictions:
-- this/these pizza/pizzas is/are warm
fun Is : Item -> Quality -> Phrase ;
Copula (koppelwerkwoord) depends on the number (in English):
-- copula Sg ==> "is"
oper copula : Number -> Str = \n ->
case n of {
Sg => "is" ;
Pl => "are"
} ;
Item
(e.g. "this wine") should contain information about its number to
be able to pass it along.
lincat Item = {s : Str ; n : Number} ;
lin This kind = {
s = "this" ++ kind.s ! Sg ;
n = Sg
} ;
We can now form a correct sentence
lin Is item qual = {s = item.s ++ copula item.n ++ qual.s} ;
Case expressions are syntactic sugar for tables:
case e of {...} === table {...} ! e
i.e. these definitions are equivalent:
oper copula : Number -> Str = \n ->
case n of {
Sg => "is" ;
Pl => "are"
} ;
oper copula : Number -> Str = \n ->
table {
Sg => "is" ;
Pl => "are"
} ! n ;
Kinds have number as a parametric feature: both singular and plural can be formed,
lincat Kind = {s : Number => Str} ;
Items have number as an inherent feature: they are inherently either singular or plural,
lincat Item
= {s : Str ; n : Number} ;
Italian Kind will have parametric number and inherent gender:
lincat Kind = {s : Number => Str ; g : Gender} ;
Questions to ask when designing parameters:
English has also cases:
param Case = Nom | Gen ;
and noun forms depend on both number and case:
oper Noun : Type = {s : Number => Case => Str} ;
We can define the worst-case function that builds the internal English
noun structure like this (where x
= singular form, y
= plural form):
oper mkNoun : Str -> Str -> Noun
= \x,y -> {
s = table {
Sg => table {
Nom => x ;
Gen => x + "'s"
} ;
Pl => table {
Nom => y ;
Gen => y + case last y of {
"s" => "'" ;
_ => "'s"
}
}
} ;
For convenience reasons and thanks to the fact that English plural nouns usually end with "s", we can define a 1-argument version:
oper regNoun : Str -> Noun = \x -> mkNoun x (x + "s")
Note that it hides the internal noun structure,
i.e. only mkNoun
operates with that.
We can make the operator even smarter (more accurate):
oper regNoun : Str -> Noun = \w ->
let
ws : Str = case w of {
_ + ("a" | "e" | "i" | "o") + "o" => w + "s" ; -- bamboo
_ + ("s" | "x" | "sh" | "o") => w + "es" ; -- bus, hero
_ + "z" => w + "zes" ;-- quiz
_ + ("a" | "e" | "o" | "u") + "y" => w + "s" ; -- boy
x + "y" => x + "ies" ;-- fly
_ => w + "s" -- car
}
in
mkNoun w ws
GF supports regular expression patterns:
_ + ("a" | "e" | "i" | "o") + "o" => w + "s" ; -- bamboo
_ + ("s" | "x" | "sh" | "o") => w + "es" ; -- bus, hero
x + "y" => x + "ies" ;-- fly
_ => w + "s" -- car
Note:
P | Q
P + Q
x
) matches anything and gets bound to itIdea: operator calculates the word full paradigm from as little input information as possible. As a result the application lexicon will look simple and easy to modify.
English
Dog = mkN "dog"
Mouse = mkN "mouse" "mice"
...
German
Country = mkN "Land" neutr
...
Concise notation for tables
\\x1,...,xn => t === table { x1 => ... table { xn => t } ... }
Example
param Number = Sg | Pl ;
Gender = Masc | Fem ;
lincat
Quality = {s : Gender => Number => Str} ;
Kind = {s : Number => Str ; g : Gender} ;
lin
QKind quality kind = {
s = table {
Sg => kind.s ! Sg ++ quality.s ! kind.g ! Sg ;
Pl => kind.s ! Pl ++ quality.s ! kind.g ! Pl ;
};
g = kind.g
} ;
-- NB: shorter
QKind quality kind = {
s = \\n => kind.s ! n ++ quality.s ! kind.g ! n ;
g = kind.g
} ;
param
Number = Sg | Pl ;
Gender = Masc | Fem ;
lincat
Quality = {s : Gender => Number
=> Str} ;
Kind = {s : Number => Str ; g : Gender} ;
lin
Very qual = {s = table {
Masc => table {
Sg => "molto" + qual.s ! Masc ! Sg ;
Pl => "molto" + qual.s ! Masc ! Pl
} ;
Fem => table {
Sg => "molto" + qual.s ! Fem ! Sg ;
Pl => "molto" + qual.s ! Fem ! Pl
}
}
}
-- NB: shorter
Very qual = {s = \\g,n => "molto" ++ qual.s ! g ! n} ;
Example: German transitive verbs (i.e. verbs that syntactically require an object) determine the case of their object (i.e. this is an inherent feature).
Clean solution: extend the regular verb type and definitions:
lincat TV = Verb ** {c : Case} ;
lin Follow = regVerb "folgen" ** {c = Dative} ;
Benefits
TV
can be used in contexts where Verb
is required-- Optional string with preference on the string vs. empty.
optStr : Str -> Str = \s -> variants {s ; []} ;
strOpt : Str -> Str = \s -> variants {[] ; s} ;
-- Infix
infixSS : Str -> SS -> SS -> SS = \f,x,y -> ss (x.s ++ f ++ y.s) ;
prefixSS : Str -> SS -> SS = \f,x -> ss (f ++ x.s) ;
...
-- Bind together two tokens in some lexers, either obligatorily or optionally
glue : Str -> Str -> Str = \x,y -> x ++ BIND ++ y ;
glueOpt : Str -> Str -> Str = \x,y -> variants {glue x y ; x ++ y} ;
noglueOpt : Str -> Str -> Str = \x,y -> variants {x ++ y ; glue x y} ;
-- Force capitalization of next word in some unlexers
capitalize : Str -> Str = \s -> CAPIT ++ s ;
-- These should be hidden, and never changed since they are hardcoded
-- in (un)lexers
BIND : Str = "&+" ;
PARA : Str = "&-" ;
CAPIT : Str = "&|" ;
-- Parentheses
paren : Str -> Str = \s -> "(" ++ s ++ ")" ;
parenss : SS -> SS = \s -> ss (paren s.s) ;
-- Missing form.
nonExist : Str = variants {} ;
-- Identity function
id : (A : Type) -> A -> A = \_,a -> a ;
-- Zero, one, two, or more (elements in a list etc)
param ENumber = E0 | E1 | E2 | Emore ;
eNext : ENumber -> ENumber = \e -> case e of {
E0 => E1 ; E1 => E2 ; _ => Emore
} ;
-- Use the glue operator with arbitrary number of arguments
-- (where arbitrary =< 5 ;))
BIND : Str = "&+" ;
glue = overload {
glue : (x1,x2 : Str) -> Str = \x1,x2 -> x1 ++ BIND ++ x2 ;
glue : (x1,x2,x3 : Str) -> Str = \x1,x2,x3 -> x1 ++ BIND ++ x2 ++ BIND ++ x3;
glue : (x1,x2,x3,x4 : Str) -> Str = \x1,x2,x3,x4 -> x1 ++ BIND ++ x2 ++ ...
glue : (x1,x2,x3,x4,x5 : Str) -> Str = \x1,x2,x3,x4,x5 -> x1 ++ BIND ++ ...
};
param Bool = True | False ;
oper
if_then_else : (A : Type) -> Bool -> A -> A -> A = \_,c,d,e ->
case c of {
True => d ;
False => e
} ;
andB : (_,_ : Bool) -> Bool = \a,b -> if_then_else Bool a b False ;
orB : (_,_ : Bool) -> Bool = \a,b -> if_then_else Bool a True b ;
notB : Bool -> Bool = \a -> if_then_else Bool a False True ;
if_then_Str : Bool -> Str -> Str -> Str = if_then_else Str ;
onlyIf : Bool -> Str -> Str = \b,s -> case b of {
True => s ;
_ => nonExist
} ;
A resource grammar has two kinds of categories and two kinds of rules:
GF makes no formal distinction between these two kinds. But it is a good discipline to follow.
Two kinds of lexical categories:
Example:
Conj ; -- conjunction e.g. "and"
Det ; -- determiner e.g. "this"
Example:
N ; -- noun e.g. "pizza"
A ; -- adjective e.g. "good"
V ; -- verb e.g. "sleep"
this_Det, that_Det, these_Det, those_Det : Det ;
very_AdA : AdA ;
Cl ; -- clause e.g. "this pizza is good"
NP ; -- noun phrase e.g. "this pizza"
CN ; -- common noun e.g. "warm pizza"
AP ; -- adjectival phrase e.g. "very warm"
...
We need the following combinations:
mkCl : NP -> AP -> Cl ; -- e.g. "this pizza is very warm"
mkNP : Det -> CN -> NP ; -- e.g. "this pizza"
mkCN : AP -> CN -> CN ; -- e.g. "warm pizza"
mkAP : AdA -> AP -> AP ; -- e.g. "very warm"
We also need lexical insertion, to form phrases from single words:
mkCN : N -> NP ;
mkAP : A -> AP ;
Naming convention: to construct a C
, use a function mkC
.
Heavy overloading: e.g. ~20 operations named mkNP
!
Language-specific and language-independent parts:
Syntax???
has the same types and functions for all languagesParadigms???
has partly different types and functions for different languagesDutch
> i -path=alltenses -retain alltenses/ParadigmsDut.gfo
> cc -table mkN "auto"
s . ResDut.NF ParamX.Sg ResDut.Nom => auto
s . ResDut.NF ParamX.Sg ResDut.Gen => autos
s . ResDut.NF ParamX.Pl ResDut.Nom => auto's
s . ResDut.NF ParamX.Pl ResDut.Gen => auto's
g . ResDut.Utr
Finnish
> i -path=alltenses -retain alltenses/ParadigmsFin.gfo
> cc -table mkN "talo"
s . ResFin.NCase ParamX.Sg ResFin.Nom => talo
s . ResFin.NCase ParamX.Sg ResFin.Gen => talon
s . ResFin.NCase ParamX.Sg ResFin.Part => taloa
s . ResFin.NCase ParamX.Sg ResFin.Transl => taloksi
...
...
...
lincat
Phrase = Cl ;
Item = NP ;
Kind = CN ;
Quality = AP ;
lin
Is item quality = mkCl item quality ;
This kind = mkNP this_Det kind ;
That kind = mkNP that_Det kind ;
These kind = mkNP these_Det kind ;
Those kind = mkNP those_Det kind ;
QKind quality kind = mkCN quality kind ;
Very quality = mkAP very_AdA quality ;
Lexical rules (English-specific):
Wine = mkCN (mkN "wine") ;
Pizza = mkCN (mkN "pizza") ;
Cheese = mkCN (mkN "cheese") ;
-- NB: 'fish' is irregular word, 1-arg smart paradigm would fail
Fish = mkCN (mkN "fish" "fish") ;
Fresh = mkAP (mkA "fresh") ;
Warm = mkAP (mkA "warm") ;
Italian
= mkAP (mkA "Italian") ;
Expensive = mkAP (mkA "expensive") ;
open
s one or more interfaces
resource
, but it only contains the types of oper
s, not (necessarily) their definitionsAdd the keyword incomplete
. We will use the header
incomplete concrete FoodsI of Foods = open Syntax, LexFoods in
where
interface Syntax -- the resource grammar interface
interface LexFoods -- the domain lexicon interface
When we moreover have
instance SyntaxEng of Syntax -- the English resource grammar
instance LexFoodsEng of LexFoods -- the English domain lexicon
we can write a functor instantiation
concrete FoodsGer of Foods = FoodsI with
(Syntax = SyntaxGer),
(LexFoods = LexFoodsGer) ;
incomplete concrete FoodsI of Foods = open Syntax, LexFoods in {
lincat
Phrase = Cl ;
Item = NP ;
Kind
= CN ;
Quality = AP ;
lin
Is item quality = mkCl item quality ;
This kind = mkNP this_Det kind ;
That kind = mkNP that_Det kind ;
These kind = mkNP these_Det kind ;
Those kind = mkNP those_Det kind ;
QKind quality kind = mkCN quality kind ;
Very quality = mkAP very_AdA quality ;
Wine = mkCN wine_N ;
Pizza = mkCN pizza_N ;
Cheese = mkCN cheese_N ;
Fish
= mkCN fish_N ;
Fresh = mkAP fresh_A ;
Warm = mkAP warm_A ;
Italian = mkAP italian_A ;
...
}
interface LexFoods = open Syntax in {
oper
wine_N : N ;
pizza_N : N ;
cheese_N : N ;
fish_N : N ;
fresh_A : A ;
warm_A : A ;
italian_A : A ;
expensive_A : A ;
delicious_A : A ;
boring_A : A ;
}
Definitions for the oper
s in the instance.
instance LexFoodsGer of LexFoods = open SyntaxGer, ParadigmsGer in {
oper
wine_N = mkN "Wein" ;
pizza_N = mkN "Pizza" "Pizzen" feminine ;
cheese_N = mkN "Käse" "Käsen" masculine ;
fish_N = mkN "Fisch" ;
fresh_A = mkA "frisch" ;
warm_A = mkA "warm" "wärmer" "wärmste" ;
italian_A = mkA "italienisch" ;
expensive_A = mkA "teuer" ;
delicious_A = mkA "kÃ
¶stlich" ;
boring_A = mkA "langweilig" ;
}
Super simple! Just parametrizes the functor (FoodsI
) with the
German grammar and the domain lexicon.
concrete FoodsGer of Foods = FoodsI with
(Syntax = SyntaxGer),
(LexFoods = LexFoodsGer) ;
Just two modules are needed:
The functor instantiation is completely mechanical to write.
The domain lexicon instance requires some knowledge of the words of the language:
Module types:
AdjectiveDut.gf
AdverbDut.gf
AllDutAbs.gf
AllDut.gf
CatDut.gf
ConjunctionDut.gf
ExtDut.gf
ExtraDutAbs.gf
ExtraDut.gf
GrammarDut.gf
IdiomDut.gf
IrregDutAbs.gf
IrregDut.gf
LangDut.gf
LexiconDut.gf
MakeStructuralDut.gf: resource
MorphoDut.gf: resource
NounDut.gf
NumeralDut.gf
ParadigmsDut.gf: resource
PhraseDut.gf
QuestionDut.gf
RelativeDut.gf
ResDut.gf
SentenceDut.gf
StructuralDut.gf
SymbolDut.gf
VerbDut.gf
Adjective.gf
Adverb.gf
Backward.gf
Cat.gf
Common.gf
Compatibility.gf
Conjunction.gf
Extra.gf
Grammar.gf
Idiom.gf
Lang.gf
Lexicon.gf
Noun.gf
Numeral.gf
NumeralTransfer.gf
Phrase.gf
Question.gf
Relative.gf
Sentence.gf
Structural.gf
Symbol.gf
Tense.gf
Text.gf
Transfer.gf
Verb.gf
Combinators.gf: incomplete resource
CombinatorsDut.gf: resource
...
Constructors.gf: incomplete resource
ConstructorsDut.gf: resource
...
Syntax.gf: interface
SyntaxDut.gf: instance
...
Symbolic.gf: incomplete resource
SymbolicDut.gf: resource
...
TryDut.gf
...
cat
) and functions (fun
)startcat
(can be also given at runtime)abstract Test = {
flags startcat = Greeting ;
cat Greeting ;
cat Name ;
fun hi : Greeting ;
fun personal_hi : Name -> Greeting ;
fun two_person_hi : Name -> Name -> Greeting ;
-- Note: you cannot use the same function name
-- with a different type
-- fun hi : Name -> Greeting ;
-- this is OK because -> is right assoc.
fun two_person_hi : Name -> (Name -> Greeting) ;
fun weird_hi : (Name -> Name) -> Greeting ;
}
lincat
)lin
){s : Str }
) instead of strings (Str
), because records can be often extended without breaking code (e.g {s : Str, g : Gender}
)oper
definitionsresource
oper
s, not (necessarily) their definitionsconcrete
is complete with respect to an abstract
resource
is complete if all oper
s and param
s have a definition partincomplete concrete
can be parametrized in a concrete*
2 men runs*
1 man run*
convert 3 kg to EUR*
dim the fanModeling:
Command
and Kind
are GF categoriesDevice
and Action
are dependent types (they depend on Kind
)Command
does not have a Kind
Abstract
cat
Command ;
Kind ;
Device Kind ; -- argument type Kind
Action Kind ;
fun
-- the Kinds of Action and Device must be the same,
-- to be able to form a Command
CAction : (k : Kind) -> Action k -> Device k -> Command ;
DKindOne : (k : Kind) -> Device k ;
light, fan : Kind ;
dim : Action light ;
Concrete
The concrete syntax does not know anything about dependent types but must suppress the extra argument.
lincat Action = {s : Str} ;
-- the Kind argument is suppressed in linearization
lin CAction _ act dev = {s = act.s ++ dev.s} ;
Syntax and semantics are OK:
> parse "dim the light"
CAction light dim (DKindOne light)
Syntax OK, semantics not:
> parse "dim the fan"
The parsing is successful but the type checking failed with error(s):
Couldn't match expected type Device light
against inferred type Device fan
In the expression: DKindOne fan
Token look-ahead (unfortunately) ignores dependent types:
> parse "dim the
fan light
Sometimes an action can be performed on all kinds of devices.
This is represented as a function that takes a Kind
as an argument and
produces an Action
for that Kind
:
fun switchOn, switchOff : (k : Kind) -> Action k ;
Functions of this kind are called polymorphic.
Compare:
light : Kind ;
dim : Action light ;
Parsing examples:
Test> parse "switch on the fan "
CAction fan (switchOn fan) (DKindOne fan)
Test> parse "switch on the light "
CAction light (switchOn light) (DKindOne light)
Abstract
flags startcat = Command ;
cat Command ; Kind ; Device Kind ; Action Kind ;
fun
CAction : (k : Kind) -> Action k -> Device k -> Command ;
light, fan : Kind ;
dim : Action light ;
DKindOne : (k : Kind) -> Device k ;
switchOn, switchOff : (k : Kind) -> Action k ;
Concrete
lincat Command, Kind, Device, Action = { s : Str };
lin CAction _ act dev = {s = act.s ++ dev.s} ;
-- Kinds
light = { s = "light" } ;
fan = { s = "fan" } ;
DKindOne k = { s = "the" ++ k.s } ;
-- Actions
dim = { s = "dim" } ;
switchOn _ = { s = "switch on" } ;
switchOff _ = { s = "switch off" } ;
&+
glues tokensExample (token list that as a string should look like "12 is a number."):
1 &+ 2 is a number &+ .
PGF server usage example
$ GF_RESTRICTED=yes gf --server=1234 --document-root /path/docroot/
$ (create /path/docroot/grammars/Test.pgf)
$ curl "http://localhost:1234/grammars/Test.pgf?
command=parse&cat=Utt&from=TestEng&input=hello"
$ (process the JSON output)
Example
audio -> natural language string -> tree -> formal expression -> evaluation result
/one plus two/ -> "one plus two" -> (plus n1 n2) -> eval(1+2) -> 3
Links
An ACE grammar in GF/RGL adds multiple natural languages as front-ends to ACE.
p -lang=Ace "if a person admires no golfer then the person buys
at least 2 aquariums that nothing but travelers inspect ." | l
si una persona no admira cap golfista llavors la persona compra
almenys 2 aquarins que nomÈs viatgers inspeccionen .
als een persoon geen golfer bewondert , dan koopt de persoon
ten minste 2 aquaria die slechts reizigers inspecteren .
jos henkilö ei ihaile mitään golfaajaa niin henkilö ostaa
vähintä
än 2 akvaariota jonka vain matkustajat tarkastavat .
si une personne n' admire aucun golfeur alors la personne achète
au moins 2 aquariums que seulement des voyageurs inspectent .
wenn eine Person keinen Golfer bewundert , dann kauft die Person
wenigstens 2 Aquariume die nur Reisenden inspizieren .
si una persona non ammira nessuno giocatore di golf allora la persona compra
almeno 2 acquari che soltanto viaggiatori ispezionano .
si una persona no admira hacia golfista entonces la persona compra
al menos 2 acuarios que solamente viajeros inspeccionan .
om en person beundrar inget golfspelare så personen k
öper
minst 2 akvariumar som bara resenärar avsynar .
Table of Contents | t |
---|---|
Exposé | ESC |
Full screen slides | e |
Presenter View | p |
Source Files | s |
Slide Numbers | n |
Toggle screen blanking | b |
Show/hide slide context | c |
Notes | 2 |
Help | h |