brassica-0.0.3: Featureful sound change applier
Safe HaskellSafe-Inferred
LanguageHaskell2010

Brassica.SoundChange.Types

Synopsis

Words and graphemes

type Grapheme = [Char] Source #

The type of graphemes, or more accurately multigraphs: for instance, "a", "ch", "c̓" :: Grapheme.

type PWord = [Grapheme] Source #

A word (or a subsequence of one) can be viewed as a list of Graphemes: e.g. Portuguese "filha" becomes ["f", "i", "lh", "a"] :: PWord.

(The name PWord is from ‘phonological word’, these being what a SCA typically manipulates; this name was chosen to avoid a clash with Prelude.Word.)

Lexemes

data Lexeme (a :: LexemeType) where Source #

A Lexeme is the smallest part of a sound change. Both matches and replacements are made up of Lexemes: the phantom type variable specifies where each different variety of Lexeme may occur.

Constructors

Grapheme :: Grapheme -> Lexeme a

In Brassica sound-change syntax, one or more letters without intervening whitespace

Category :: [CategoryElement a] -> Lexeme a

In Brassica sound-change syntax, delimited by square brackets

Boundary :: Lexeme 'Env

In Brassica sound-change syntax, specified as #

Optional :: [Lexeme a] -> Lexeme a

In Brassica sound-change syntax, delimited by parentheses

Metathesis :: Lexeme 'Replacement

In Brassica sound-change syntax, specified as @@

Geminate :: Lexeme a

In Brassica sound-change syntax, specified as >

Wildcard :: OneOf a 'Target 'Env => Lexeme a -> Lexeme a

In Brassica sound-change syntax, specified as ^ before another Lexeme

Kleene :: OneOf a 'Target 'Env => Lexeme a -> Lexeme a

In Brassica sound-change syntax, specified as * after another Lexeme

Discard :: Lexeme 'Replacement

In Brassica sound-change syntax, specified as ~

Instances

Instances details
Show (Lexeme a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

showsPrec :: Int -> Lexeme a -> ShowS #

show :: Lexeme a -> String #

showList :: [Lexeme a] -> ShowS #

NFData (Lexeme a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Lexeme a -> () #

data CategoryElement (a :: LexemeType) where Source #

The elements allowed in a Category: currently, only Graphemes and word boundaries.

data LexemeType Source #

The part of a Rule in which a Lexeme may occur: either the target, the replacement or the environment.

Constructors

Target 
Replacement 
Env 

Rules

data Rule Source #

A single sound change rule: in Brassica sound-change syntax with all elements specified, -flags target / replacement / environment / exception. (And usually the plaintext of the rule will contain a String resembling that pattern.)

Instances

Instances details
Generic Rule Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep Rule :: Type -> Type #

Methods

from :: Rule -> Rep Rule x #

to :: Rep Rule x -> Rule #

Show Rule Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

showsPrec :: Int -> Rule -> ShowS #

show :: Rule -> String #

showList :: [Rule] -> ShowS #

NFData Rule Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Rule -> () #

type Rep Rule Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Environment = ([Lexeme 'Env], [Lexeme 'Env]) Source #

An Environment is a tuple of (before, after) components, corresponding to a ‘/ before _ after’ component of a sound change.

Note that an empty environment is just ([], []).

data Direction Source #

Specifies application direction of rule — either left-to-right or right-to-left.

Constructors

LTR 
RTL 

Instances

Instances details
Generic Direction Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep Direction :: Type -> Type #

Show Direction Source # 
Instance details

Defined in Brassica.SoundChange.Types

NFData Direction Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Direction -> () #

Eq Direction Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep Direction Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep Direction = D1 ('MetaData "Direction" "Brassica.SoundChange.Types" "brassica-0.0.3-KZvvTDsX9bO8hsF2GF232f" 'False) (C1 ('MetaCons "LTR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RTL" 'PrefixI 'False) (U1 :: Type -> Type))

data Flags Source #

Flags which can be enabled, disabled or altered on a Rule to change how it is applied.

Instances

Instances details
Generic Flags Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep Flags :: Type -> Type #

Methods

from :: Flags -> Rep Flags x #

to :: Rep Flags x -> Flags #

Show Flags Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

showsPrec :: Int -> Flags -> ShowS #

show :: Flags -> String #

showList :: [Flags] -> ShowS #

NFData Flags Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Flags -> () #

type Rep Flags Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep Flags = D1 ('MetaData "Flags" "Brassica.SoundChange.Types" "brassica-0.0.3-KZvvTDsX9bO8hsF2GF232f" 'False) (C1 ('MetaCons "Flags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "highlightChanges") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "applyDirection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Direction)) :*: (S1 ('MetaSel ('Just "applyOnceOnly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "sporadic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

defFlags :: Flags Source #

A default selection of flags which are appropriate for most rules:

defFlags = Flags
    { highlightChanges = True
    , applyDirection = LTR
    , applyOnceOnly = False
    , sporadic = False
    }

That is: highlight changes, apply from left to right, apply repeatedly, and don’t apply sporadically.

Categories and statements

newtype CategoriesDecl Source #

Corresponds to a category declaration in a set of sound changes. Category declarations are mostly desugared away by the parser, but for rule application we still need to be able to filter out all unknown Graphemes; thus, a CategoriesDecl lists the Graphemes which are available at a given point.

Constructors

CategoriesDecl 

Fields

Instances

Instances details
Generic CategoriesDecl Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep CategoriesDecl :: Type -> Type #

Show CategoriesDecl Source # 
Instance details

Defined in Brassica.SoundChange.Types

NFData CategoriesDecl Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: CategoriesDecl -> () #

type Rep CategoriesDecl Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep CategoriesDecl = D1 ('MetaData "CategoriesDecl" "Brassica.SoundChange.Types" "brassica-0.0.3-KZvvTDsX9bO8hsF2GF232f" 'True) (C1 ('MetaCons "CategoriesDecl" 'PrefixI 'True) (S1 ('MetaSel ('Just "graphemes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Grapheme])))

data Statement Source #

A Statement can be either a single sound change rule, or a category declaration.

Instances

Instances details
Generic Statement Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep Statement :: Type -> Type #

Show Statement Source # 
Instance details

Defined in Brassica.SoundChange.Types

NFData Statement Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Statement -> () #

type Rep Statement Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep Statement = D1 ('MetaData "Statement" "Brassica.SoundChange.Types" "brassica-0.0.3-KZvvTDsX9bO8hsF2GF232f" 'False) (C1 ('MetaCons "RuleS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rule)) :+: C1 ('MetaCons "CategoriesDeclS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CategoriesDecl)))

plaintext' :: Statement -> String Source #

A simple wrapper around plaintext for Statements. Returns "categories … end" for all CategoriesDecl inputs.

type SoundChanges = [Statement] Source #

A set of SoundChanges is simply a list of Statements.

Utility

type family OneOf a x y :: Constraint where ... Source #

The constraint OneOf a x y is satisfied if a ~ x or a ~ y.

(Note: the strange () ~ Bool constraint is just a simple unsatisfiable constraint, so as to not give ‘non-exhaustive pattern match’ errors everywhere.)

Equations

OneOf a a y = () 
OneOf a x a = () 
OneOf a b c = (() ~ Bool, TypeError ((((('Text "Couldn't match type " :<>: 'ShowType a) :<>: 'Text " with ") :<>: 'ShowType b) :<>: 'Text " or ") :<>: 'ShowType c))