gf-3.9: Grammatical Framework

Safe HaskellSafe
LanguageHaskell2010

PGF.Haskell

Contents

Description

Auxiliary types and functions for use with grammars translated to Haskell with gf -output-format=haskell -haskell=concrete

Synopsis

Concrete syntax

class EnumAll a where Source #

For enumerating parameter values used in tables

Minimal complete definition

enumAll

Methods

enumAll :: [a] Source #

Instances

EnumAll t => EnumAll (R_s t) Source # 

Methods

enumAll :: [R_s t] Source #

table :: (EnumAll k, Ord k) => [a] -> k -> a Source #

Tables

type Str = [Tok] Source #

Token sequences, output form linearization functions

data Tok Source #

Tokens

Instances

Eq Tok Source # 

Methods

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

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

Ord Tok Source # 

Methods

compare :: Tok -> Tok -> Ordering #

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

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

(>) :: Tok -> Tok -> Bool #

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

max :: Tok -> Tok -> Tok #

min :: Tok -> Tok -> Tok #

Show Tok Source # 

Methods

showsPrec :: Int -> Tok -> ShowS #

show :: Tok -> String #

showList :: [Tok] -> ShowS #

type Prefix Source #

Arguments

 = String

To be matched with the prefix of a following token

fromStr :: Str -> String Source #

Render a token sequence as a String

Common record types

class Has_s r a | r -> a where Source #

Overloaded function to project the s field from any record type

Minimal complete definition

proj_s

Methods

proj_s :: r -> a Source #

Instances

Has_s (R_s t) t Source # 

Methods

proj_s :: R_s t -> t Source #

data R_s t Source #

Haskell representation of the GF record type {s:t}

Constructors

R_s t 

Instances

Eq t => Eq (R_s t) Source # 

Methods

(==) :: R_s t -> R_s t -> Bool #

(/=) :: R_s t -> R_s t -> Bool #

Ord t => Ord (R_s t) Source # 

Methods

compare :: R_s t -> R_s t -> Ordering #

(<) :: R_s t -> R_s t -> Bool #

(<=) :: R_s t -> R_s t -> Bool #

(>) :: R_s t -> R_s t -> Bool #

(>=) :: R_s t -> R_s t -> Bool #

max :: R_s t -> R_s t -> R_s t #

min :: R_s t -> R_s t -> R_s t #

Show t => Show (R_s t) Source # 

Methods

showsPrec :: Int -> R_s t -> ShowS #

show :: R_s t -> String #

showList :: [R_s t] -> ShowS #

EnumAll t => EnumAll (R_s t) Source # 

Methods

enumAll :: [R_s t] Source #

Has_s (R_s t) t Source # 

Methods

proj_s :: R_s t -> t Source #

to_R_s :: Has_s r t => r -> R_s t Source #

Coerce from any record type {...,s:t,...} to the supertype {s:t}

Variants

(+++) :: Applicative f => f [a] -> f [a] -> f [a] infixr 5 Source #

Concatenation with variants

(!) :: Monad m => (t -> m (m a)) -> t -> m a Source #

Selection from tables with variants

(!$) :: Monad m => (a1 -> m a) -> m a1 -> m a Source #

(!*) :: Monad m => m (a1 -> m a) -> m a1 -> m a Source #