gf-3.7: Grammatical Framework

Safe HaskellNone
LanguageHaskell2010

GF

Contents

Description

GF, the Grammatical Framework, as a library

Synopsis

Command line interface

main :: IO () Source

Run the GF main program, taking arguments from the command line. (It calls setConsoleEncoding and getOptions, then mainOpts.) Run gf --help for usage info.

getOptions :: IO (Options, [FilePath]) Source

Get and parse GF command line arguments. Fix relative paths. Calls getArgs and parseOptions.

mainOpts :: Options -> [FilePath] -> IO () Source

Run the GF main program with the given options and files. Depending on the options it invokes mainGFC, mainGFI, mainRunGFI, mainServerGFI, or it just prints version/usage info.

mainGFI :: Options -> [FilePath] -> IO () Source

Run the interactive GF Shell

mainRunGFI :: Options -> [FilePath] -> IO () Source

Run the GF Shell in quiet mode (gf -run).

mainServerGFI :: Options -> Int -> [FilePath] -> IO Server Source

Run the GF Server (gf -server). The Int argument is the port number for the HTTP service.

mainGFC :: Options -> [FilePath] -> IO () Source

Compile the given GF grammar files. The result is a number of .gfo files and, depending on the options, a .pgf file. (gf -batch, gf -make)

linkGrammars :: Options -> (UTCTime, [(ModuleName, Grammar)]) -> IO () Source

Create a .pgf file (and possibly files in other formats, if specified in the Options) from the output of parallelBatchCompile. If a .pgf file by the same name already exists and it is newer than the source grammar files (as indicated by the UTCTime argument), it is not recreated. Calls writePGF and writeOutputs.

writePGF :: Options -> PGF -> IOE () Source

Write the result of compiling a grammar (e.g. with compileToPGF or link) to a .pgf file. A split PGF file is output if the -split-pgf option is used.

writeOutputs :: Options -> PGF -> IOE () Source

Export the PGF to the OutputFormats specified in the Options. Calls exportPGF.

Compiling GF grammars

compileToPGF :: Options -> [FilePath] -> IOE PGF Source

Compiles a number of source files and builds a PGF structure for them. This is a composition of link and batchCompile.

link :: Options -> (ModuleName, Grammar) -> IOE PGF Source

Link a grammar into a PGF that can be used to linearize and parse with the PGF run-time system.

batchCompile :: Options -> [FilePath] -> IOE (UTCTime, (ModuleName, Grammar)) Source

Compile the given grammar files and everything they depend on. Compiled modules are stored in .gfo files (unless the -tags option is used, in which case tags files are produced instead). Existing .gfo files are reused if they are up-to-date (unless the option -src aka -force-recomp is used).

srcAbsName :: Grammar -> ModuleName -> ModuleName Source

Returns the name of the abstract syntax corresponding to the named concrete syntax

parallelBatchCompile :: (Output m, ErrorMonad m, MonadIO m) => t -> Options -> [FilePath] -> m (UTCTime, [(ModuleName, Grammar)]) Source

Compile the given grammar files and everything they depend on, like batchCompile. This function compiles modules in parallel. It keeps modules compiled in present and alltenses mode apart, storing the .gfo files in separate subdirectories to avoid creating the broken PGF files that can result from mixing different modes in the same concrete syntax.

The first argument is supposed to be the number of jobs to run in parallel, but this has not been implemented yet. Instead you have to use the GHC run-time flag +RTS -N -RTS to enable parallelism.

exportPGF Source

Arguments

:: Options 
-> OutputFormat 
-> PGF 
-> [(FilePath, String)]

List of recommended file names and contents.

Export a PGF to the given OutputFormat. For many output formats, additional Options can be used to control the output.

Compiling a single module

compileOne :: (Output m, ErrorMonad m, MonadIO m) => Options -> Grammar -> FullPath -> m OneOutput Source

Compile a given source file (or just load a .gfo file), given a Grammar containing everything it depends on. Calls reuseGFO or useTheSource.

reuseGFO :: (Output m, ErrorMonad m, MonadIO m) => Options -> Grammar -> FullPath -> m OneOutput Source

Read a compiled GF module. Also undo common subexp optimization, to enable normal computations.

useTheSource :: (Output m, ErrorMonad m, MonadIO m) => Options -> Grammar -> FullPath -> m OneOutput Source

Compile GF module from source. It both returns the result and stores it in a .gfo file (or a tags file, if running with the -tags option)

Abstract syntax, parsing, pretty printing and serialisation

getSourceModule :: (Output m, ErrorMonad m, MonadIO m) => Options -> FilePath -> m (ModuleName, ModuleInfo) Source

Read a source file and parse it (after applying preprocessors specified in the options)

Grammar modules

data Grammar Source

A grammar is a self-contained collection of grammar modules

allDepsModule :: Grammar -> ModuleInfo -> [OpenSpec] Source

all dependencies

partOfGrammar :: Grammar -> Module -> Grammar Source

select just those modules that a given one depends on, including itself

depPathModule :: ModuleInfo -> [OpenSpec] Source

initial dependency list

allExtends :: Grammar -> ModuleName -> [Module] Source

all modules that a module extends, directly or indirectly, with restricts

allExtendsPlus :: Grammar -> ModuleName -> [ModuleName] Source

the same as allExtends plus that an instance extends its interface

isCompilableModule :: ModuleInfo -> Bool Source

don't generate code for interfaces and for incomplete modules

isCompleteModule :: ModuleInfo -> Bool Source

interface and "incomplete M" are not complete

allAbstracts :: Grammar -> [ModuleName] Source

all abstract modules sorted from least to most dependent

greatestAbstract :: Grammar -> Maybe ModuleName Source

the last abstract in dependency order (head of list)

allResources :: Grammar -> [ModuleName] Source

all resource modules

greatestResource :: Grammar -> Maybe ModuleName Source

the greatest resource in dependency order

allConcretes :: Grammar -> ModuleName -> [ModuleName] Source

all concretes for a given abstract

allConcreteModules :: Grammar -> [ModuleName] Source

all concrete modules for any abstract

abstractOfConcrete :: ErrorMonad m => Grammar -> ModuleName -> m ModuleName Source

we store the module type with the identifier

Judgements

data Info Source

the constructors are judgements in

  • abstract syntax (ABS)
  • resource (RES)
  • concrete syntax (CNC)

and indirection to module (INDIR)

Constructors

AbsCat (Maybe (L Context))

(ABS) context of a category

AbsFun (Maybe (L Type)) (Maybe Int) (Maybe [L Equation]) (Maybe Bool)

(ABS) type, arrity and definition of a function

ResParam (Maybe (L [Param])) (Maybe [Term])

(RES) the second parameter is list of all possible values

ResValue (L Type)

(RES) to mark parameter constructors for lookup

ResOper (Maybe (L Type)) (Maybe (L Term))

(RES)

ResOverload [ModuleName] [(L Type, L Term)]

(RES) idents: modules inherited

CncCat (Maybe (L Type)) (Maybe (L Term)) (Maybe (L Term)) (Maybe (L Term)) (Maybe PMCFG)

(CNC) lindef ini'zed,

CncFun (Maybe (Ident, Context, Type)) (Maybe (L Term)) (Maybe (L Term)) (Maybe PMCFG)

(CNC) type info added at TC

AnyInd Bool ModuleName

(INDIR) the Bool says if canonical

Instances

Terms

data Term Source

Constructors

Vr Ident

variable

Cn Ident

constant

Con Ident

constructor

Sort Ident

basic type

EInt Int

integer literal

EFloat Double

floating point literal

K String

string literal or token: "foo"

Empty

the empty string []

App Term Term

application: f a

Abs BindType Ident Term

abstraction: x -> b

Meta !MetaId

metavariable: ?i (only parsable: ? = ?0)

ImplArg Term

placeholder for implicit argument {t}

Prod BindType Ident Term Term

function type: (x : A) -> B, A -> B, ({x} : A) -> B

Typed Term Term

type-annotated term

below this, the constructors are only for concrete syntax

Example Term String

example-based term: @in M.C "foo"

RecType [Labelling]

record type: { p : A ; ...}

R [Assign]

record: { p = a ; ...}

P Term Label

projection: r.p

ExtR Term Term

extension: R ** {x : A} (both types and terms)

Table Term Term

table type: P => A

T TInfo [Case]

table: table {p => c ; ...}

V Type [Term]

table given as course of values: table T [c1 ; ... ; cn]

S Term Term

selection: t ! p

Let LocalDef Term

local definition: let {t : T = a} in b

Q QIdent

qualified constant from a package

QC QIdent

qualified constructor from a package

C Term Term

concatenation: s ++ t

Glue Term Term

agglutination: s + t

EPatt Patt

pattern (in macro definition): # p

EPattType Term

pattern type: pattern T

ELincat Ident Term

boxed linearization type of Ident

ELin Ident Term

boxed linearization of type Ident

AdHocOverload [Term]

ad hoc overloading generated in Rename

FV [Term]

alternatives in free variation: variants { s ; ... }

Alts Term [(Term, Term)]

alternatives by prefix: pre {t ; s/c ; ...}

Strs [Term]

conditioning prefix strings: strs {s ; ...}

Error String

error values returned by Predef.error

data Patt Source

Patterns

Constructors

PC Ident [Patt]

constructor pattern: C p1 ... pn C

PP QIdent [Patt]

package constructor pattern: P.C p1 ... pn P.C

PV Ident

variable pattern: x

PW

wild card pattern: _

PR [(Label, Patt)]

record pattern: {r = p ; ...} -- only concrete

PString String

string literal pattern: "foo" -- only abstract

PInt Int

integer literal pattern: 12 -- only abstract

PFloat Double

float literal pattern: 1.2 -- only abstract

PT Type Patt

type-annotated pattern

PAs Ident Patt

as-pattern: x@p

PImplArg Patt

placeholder for pattern for implicit argument {p}

PTilde Term

inaccessible pattern

PNeg Patt

negated pattern: -p

PAlt Patt Patt

disjunctive pattern: p1 | p2

PSeq Patt Patt

sequence of token parts: p + q

PMSeq MPatt MPatt

sequence of token parts: p + q

PRep Patt

repetition of token part: p*

PChar

string of length one: ?

PChars [Char]

character list: ["aeiou"]

PMacro Ident 
PM QIdent 

data TInfo Source

to guide computation and type checking of tables

Constructors

TRaw

received from parser; can be anything

TTyped Type

type annontated, but can be anything

TComp Type

expanded

TWild Type

just one wild card pattern, no need to expand

data Label Source

record label

Constructors

LIdent RawIdent 
LVar Int 

type Equation = ([Patt], Term) Source

type Case = (Patt, Term) Source

type Altern = (Term, [(Term, Term)]) Source

Source locations

data L a Source

Attaching location information

Constructors

L Location a 

Instances

Functor L 
Show a => Show (L a) 
Binary a => Binary (L a) 

unLoc :: L a -> a Source

noLoc :: a -> L a Source

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

PMCFG

type FId = Int Source

type Sequence = Array DotPos Symbol Source

Functions for constructing and analysing source code terms.

termForm :: Monad m => Term -> m ([(BindType, Ident)], Term, [Term]) Source

Assignment

unzipR :: [Assign] -> ([Label], [Term]) Source

mapAssignM :: Monad m => (Term -> m c) -> [Assign] -> m [(Label, (Maybe c, c))] Source

Records

mkRecordN :: Int -> (Int -> Label) -> [Term] -> Term Source

mkRecord :: (Int -> Label) -> [Term] -> Term Source

mkRecTypeN :: Int -> (Int -> Label) -> [Type] -> Type Source

mkRecType :: (Int -> Label) -> [Type] -> Type Source

Types

Terms

defLinType :: Type Source

default linearization type

mkFreshVar :: [Ident] -> Ident Source

refreshing variables

mkFreshVarX :: [Ident] -> Ident -> Ident Source

trying to preserve a given symbol

freshAsTerm :: String -> Term Source

quick hack for refining with var in editor

string2term :: String -> Term Source

create a terminal for concrete syntax

ident2terminal :: Ident -> Term Source

create a terminal from identifier

Term and pattern conversion

Almost compositional

composSafeOp :: (Term -> Term) -> Term -> Term Source

to define compositional term functions

composOp :: Monad m => (Term -> m Term) -> Term -> m Term Source

to define compositional term functions

composPattOp :: Monad m => (Patt -> m Patt) -> Patt -> m Patt Source

collectOp :: Monoid m => (Term -> m) -> Term -> m Source

mconcatMap :: Monoid c => (a -> c) -> [a] -> c Source

collectPattOp :: (Patt -> [a]) -> Patt -> [a] Source

Misc

allCaseValues :: Term -> [([Patt], Term)] Source

to gather ultimate cases in a table; preserves pattern list

strsFromTerm :: Term -> Err [Str] Source

to get a string from a term that represents a sequence of terminals

stringFromTerm :: Term -> String Source

to print an Str-denoting term as a string; if the term is of wrong type, the error msg

wordsInTerm :: Term -> [String] Source

to find the word items in a term

sortRec :: [(Label, a)] -> [(Label, a)] Source

Dependencies

allDependencies :: (ModuleName -> Bool) -> BinTree Ident Info -> [(Ident, [Ident])] Source

dependency check, detecting circularities and returning topo-sorted list

Pretty printing

ppParams :: Pretty a => TermPrintQual -> [(a, [(t, Ident, Term)])] -> Doc Source

ppTerm :: (Ord a, Num a) => TermPrintQual -> a -> Term -> Doc Source

ppPatt :: (Ord a, Num a) => TermPrintQual -> a -> Patt -> Doc Source

ppConstrs :: Constraints -> [Doc] Source

ppMeta :: MetaId -> Doc Source

Identifiers

data Ident Source

the constructors labelled INTERNAL are internal representation never returned by the parser

ident2utf8 :: Ident -> ByteString Source

This function should be used with care, since the returned ByteString is UTF-8-encoded.

Normal identifiers (returned by the parser)

Special identifiers for internal use

argIdent :: Int -> Ident -> Int -> Ident Source

to mark argument variables

varStr :: Ident Source

used in lin defaults

varX :: Int -> Ident Source

refreshing variables

Raw identifiers

data RawIdent Source

Identifiers are stored as UTF-8-encoded bytestrings. (It is also possible to use regular Haskell Strings, with somewhat reduced performance and increased memory use.)

Binary serialisation

data VersionTagged a Source

Constructors

Tagged 

Fields

unV :: a
 
WrongVersion 

decodeModuleHeader :: MonadIO io => FilePath -> io (VersionTagged Module) Source

Read just the module header, the returned Module will have an empty body