pgf2: Bindings to the PGF runtime in C

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

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]

Properties

Versions 1.1.0, 1.2.0, 1.2.1, 1.3.0
Change log CHANGELOG.md
Dependencies base (>=4.3 && <5), containers, lifted-base, mtl, pgf2, pretty [details]
License LGPL-3.0-only
Author Krasimir Angelov
Maintainer Krasimir Angelov, John J. Camilleri
Category Language
Home page https://www.grammaticalframework.org
Uploaded by JohnCamilleri at 2020-07-11T19:02:27Z

Modules

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for pgf2-1.1.0

[back to package description]

PGF2

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

The exposed modules are:

How to compile

cabal install

Note: you must have the PGF C runtime already installed and available. See https://github.com/GrammaticalFramework/gf-core/blob/master/src/runtime/c/INSTALL

How to use

Import PGF to the Haskell program that you're writing. 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