pgf2-1.2.1: Bindings to the C version of the PGF runtime

Safe HaskellNone
LanguageHaskell2010

PGF2.Internal

Contents

Synopsis

Access the internal structures

type FId = Int Source #

type FunId = Int Source #

data PArg Source #

Constructors

PArg [FId] !FId 
Instances
Eq PArg Source # 
Instance details

Defined in PGF2.FFI

Methods

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

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

Ord PArg Source # 
Instance details

Defined in PGF2.FFI

Methods

compare :: PArg -> PArg -> Ordering #

(<) :: PArg -> PArg -> Bool #

(<=) :: PArg -> PArg -> Bool #

(>) :: PArg -> PArg -> Bool #

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

max :: PArg -> PArg -> PArg #

min :: PArg -> PArg -> PArg #

Show PArg Source # 
Instance details

Defined in PGF2.FFI

Methods

showsPrec :: Int -> PArg -> ShowS #

show :: PArg -> String #

showList :: [PArg] -> ShowS #

data Symbol Source #

Instances
Eq Symbol Source # 
Instance details

Defined in PGF2.Internal

Methods

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

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

Ord Symbol Source # 
Instance details

Defined in PGF2.Internal

Show Symbol Source # 
Instance details

Defined in PGF2.Internal

data Literal Source #

Constructors

LStr String

a string constant

LInt Int

an integer constant

LFlt Double

a floating point constant

Instances
Eq Literal Source # 
Instance details

Defined in PGF2.Internal

Methods

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

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

Ord Literal Source # 
Instance details

Defined in PGF2.Internal

Show Literal Source # 
Instance details

Defined in PGF2.Internal

concrFunction :: Concr -> FunId -> (Fun, [SeqId]) Source #

concrSequence :: Concr -> SeqId -> [Symbol] Source #

Building new PGFs in memory

build :: (forall s. (?builder :: Builder s) => B s a) -> a Source #

eAbs :: (?builder :: Builder s) => BindType -> String -> B s Expr -> B s Expr Source #

eApp :: (?builder :: Builder s) => B s Expr -> B s Expr -> B s Expr Source #

eMeta :: (?builder :: Builder s) => Int -> B s Expr Source #

eFun :: (?builder :: Builder s) => Fun -> B s Expr Source #

eVar :: (?builder :: Builder s) => Int -> B s Expr Source #

eTyped :: (?builder :: Builder s) => B s Expr -> B s Type -> B s Expr Source #

eImplArg :: (?builder :: Builder s) => B s Expr -> B s Expr Source #

dTyp :: (?builder :: Builder s) => [B s Hypo] -> Cat -> [B s Expr] -> B s Type Source #

hypo :: BindType -> CId -> B s Type -> B s Hypo Source #

newAbstr :: (?builder :: Builder s) => [(String, Literal)] -> [(Cat, [B s Hypo], Float)] -> [(Fun, B s Type, Int, Float)] -> AbstrInfo Source #

newConcr Source #

Arguments

:: (?builder :: Builder s) 
=> AbstrInfo 
-> [(String, Literal)]

Concrete syntax flags

-> [(String, String)]

Printnames

-> [(FId, [FunId])]

Lindefs

-> [(FId, [FunId])]

Linrefs

-> [(FId, [Production])]

Productions

-> [(Fun, [SeqId])]

Concrete functions (must be sorted by Fun)

-> [[Symbol]]

Sequences (must be sorted)

-> [(Cat, FId, FId, [String])]

Concrete categories

-> FId

The total count of the categories

-> ConcrInfo 

newPGF :: (?builder :: Builder s) => [(String, Literal)] -> AbsName -> AbstrInfo -> [(ConcName, ConcrInfo)] -> B s PGF Source #

Expose PGF and Concr for FFI with C

data PGF Source #

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

Constructors

PGF 

Fields

data Concr Source #

Constructors

Concr 

Fields

Write an in-memory PGF to a file