pgf2: Bindings to the C version of the PGF runtime

[ language, lgpl, library ] [ Propose Tags ]

GF, Grammatical Framework, is a programming language for multilingual grammar applications. GF grammars are compiled into Portable Grammar Format (PGF) which can be used with the PGF runtime, written in C. This package provides Haskell bindings to that runtime.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 1.2.0, 1.2.1, 1.3.0
Change log CHANGELOG.md
Dependencies base (>=4.3 && <5), containers, pretty [details]
License LGPL-3.0-only
Author Krasimir Angelov
Maintainer kr.angelov@gmail.com
Category Language
Home page https://www.grammaticalframework.org
Uploaded by JohnCamilleri at 2020-09-18T08:38:44Z
Distributions
Downloads 408 total (7 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for pgf2-1.2.1

[back to package description]

PGF2

This is a Haskell binding to the PGF runtime written in C.

The exposed modules are:

  • PGF2: a user API similar to Python and Java APIs
  • PGF2.Internal: an internal module with FFI definitions for the relevant C functions

How to compile

Important: You must have the C runtime already installed and available on your system. See https://github.com/GrammaticalFramework/gf-core/blob/master/src/runtime/c/INSTALL

Once the runtine is installed, you can install the library to your global Cabal installation:

cabal install pgf2 --extra-lib-dirs=/usr/local/lib

or add it to your stack.yaml file:

extra-deps:
  - pgf2
extra-lib-dirs:
  - /usr/local/lib

How to use

Simply import PGF2 in your Haskell program. The Cabal infrastructure will make sure to tell the compiler where to find the relevant modules.

Example

module Main where

import PGF2
import qualified Data.Map as Map

main = do
  pgf <- readPGF "App12.pgf"
  let Just eng = Map.lookup "AppEng" (languages pgf)
  
  -- Parsing
  let res = parse eng (startCat pgf) "this is a small theatre"
  let ParseOk ((tree,prob):rest) = res
  print tree
  
  -- Linearisation
  let Just expr = readExpr "AdjCN (PositA red_A) (UseN theatre_N)"
  let s = linearize eng expr
  print s