| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
PGF2.Internal
Contents
Synopsis
- type FId = Int
- isPredefFId :: FId -> Bool
- type FunId = Int
- type Token = String
- data Production
- data PArg = PArg [FId] !FId
- data Symbol
- data Literal
- globalFlags :: PGF -> [(String, Literal)]
- abstrFlags :: PGF -> [(String, Literal)]
- concrFlags :: Concr -> [(String, Literal)]
- concrTotalCats :: Concr -> FId
- concrCategories :: Concr -> [(Cat, FId, FId, [String])]
- concrProductions :: Concr -> FId -> [Production]
- concrTotalFuns :: Concr -> FunId
- concrFunction :: Concr -> FunId -> (Fun, [SeqId])
- concrTotalSeqs :: Concr -> SeqId
- concrSequence :: Concr -> SeqId -> [Symbol]
- build :: (forall s. (?builder :: Builder s) => B s a) -> a
- eAbs :: (?builder :: Builder s) => BindType -> String -> B s Expr -> B s Expr
- eApp :: (?builder :: Builder s) => B s Expr -> B s Expr -> B s Expr
- eMeta :: (?builder :: Builder s) => Int -> B s Expr
- eFun :: (?builder :: Builder s) => Fun -> B s Expr
- eVar :: (?builder :: Builder s) => Int -> B s Expr
- eTyped :: (?builder :: Builder s) => B s Expr -> B s Type -> B s Expr
- eImplArg :: (?builder :: Builder s) => B s Expr -> B s Expr
- dTyp :: (?builder :: Builder s) => [B s Hypo] -> Cat -> [B s Expr] -> B s Type
- hypo :: BindType -> CId -> B s Type -> B s Hypo
- data AbstrInfo
- newAbstr :: (?builder :: Builder s) => [(String, Literal)] -> [(Cat, [B s Hypo], Float)] -> [(Fun, B s Type, Int, Float)] -> AbstrInfo
- data ConcrInfo
- newConcr :: (?builder :: Builder s) => AbstrInfo -> [(String, Literal)] -> [(String, String)] -> [(FId, [FunId])] -> [(FId, [FunId])] -> [(FId, [Production])] -> [(Fun, [SeqId])] -> [[Symbol]] -> [(Cat, FId, FId, [String])] -> FId -> ConcrInfo
- newPGF :: (?builder :: Builder s) => [(String, Literal)] -> AbsName -> AbstrInfo -> [(ConcName, ConcrInfo)] -> B s PGF
- data PGF = PGF {}
- data Concr = Concr {
- concr :: Ptr PgfConcr
- touchConcr :: Touch
- writePGF :: FilePath -> PGF -> IO ()
Access the internal structures
isPredefFId :: FId -> Bool Source #
data Production Source #
Instances
| Eq Production Source # | |
Defined in PGF2.Internal | |
| Ord Production Source # | |
Defined in PGF2.Internal Methods compare :: Production -> Production -> Ordering # (<) :: Production -> Production -> Bool # (<=) :: Production -> Production -> Bool # (>) :: Production -> Production -> Bool # (>=) :: Production -> Production -> Bool # max :: Production -> Production -> Production # min :: Production -> Production -> Production # | |
| Show Production Source # | |
Defined in PGF2.Internal Methods showsPrec :: Int -> Production -> ShowS # show :: Production -> String # showList :: [Production] -> ShowS # | |
Constructors
| SymCat !Int !LIndex | |
| SymLit !Int !LIndex | |
| SymVar !Int !Int | |
| SymKS Token | |
| SymKP [Symbol] [([Symbol], [String])] | |
| SymBIND | |
| SymNE | |
| SymSOFT_BIND | |
| SymSOFT_SPACE | |
| SymCAPIT | |
| SymALL_CAPIT |
Constructors
| LStr String | a string constant |
| LInt Int | an integer constant |
| LFlt Double | a floating point constant |
concrTotalCats :: Concr -> FId Source #
concrProductions :: Concr -> FId -> [Production] Source #
concrTotalFuns :: Concr -> FunId Source #
concrTotalSeqs :: Concr -> SeqId Source #
concrSequence :: Concr -> SeqId -> [Symbol] Source #
Building new PGFs in memory
newAbstr :: (?builder :: Builder s) => [(String, Literal)] -> [(Cat, [B s Hypo], Float)] -> [(Fun, B s Type, Int, Float)] -> AbstrInfo 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
An abstract data type representing multilingual grammar in Portable Grammar Format.