brassica-1.0.0: Featureful sound change applier
CopyrightSee LICENSE file
LicenseBSD3
MaintainerBrad Neimann
Safe HaskellSafe-Inferred
LanguageHaskell2010

Brassica.SoundChange.Types

Description

This module contains the types used to represent sound changes and words in Brassica. In brief:

  • A set of SoundChanges is composed of a list of elements
  • Their most important elements are sound change Rules
  • Sound changes are composed of Lexemes denoting parts of the input and output words
  • Each word is a sequence of Graphemes

For more details on the syntax and semantics of sound changes, refer to the reference guide.

Synopsis

Words and graphemes

type Grapheme = [Char] Source #

The type of graphemes within a word. "#" is taken to denote a word boundary (whch is universally treated as a normal grapheme in sound changes.)

type PWord = [Grapheme] Source #

Brassica views a word, or a subsequence of one, as a list of Graphemes. For instance, Portuguese "filha" becomes ["f", "i", "lh", "a"] when tokenised correctly.

(The name PWord is from ‘phonological word’, these being what sound changes typically manipulate. The name was chosen to avoid a clash with Word from base.)

addBoundaries :: PWord -> PWord Source #

Add word boundaries ("#") at the beginning and end of a PWord.

removeBoundaries :: PWord -> PWord Source #

Remove word boundaries ("#") from the beginning and end of a PWord.

Lexemes

data Lexeme category (a :: LexemeType) where Source #

Each part of a sound change is made up of a sequence of Lexemes. Each Lexeme denotes part of an input or output word.

The first type variable category is the type used to represent categories within the sound change. This will usually be CategorySpec after parsing, or Expanded after expansion.

The second type variable is phantom and represents the part of the rule in which the lexeme is placed. Various lexemes are restricted to Matched or Replacement positions respectively.

For details on the syntax and semantics of each kind of lexeme, refer to the reference guide.

Constructors

Grapheme :: Grapheme -> Lexeme category a 
Category :: category a -> Lexeme category a 
GreedyCategory :: category 'Matched -> Lexeme category 'Matched

Written %category, matching-only

Optional :: [Lexeme category a] -> Lexeme category a

Written (lexemes)

GreedyOptional :: [Lexeme category 'Matched] -> Lexeme category 'Matched

Written %(lexemes), matching-only

Metathesis :: Lexeme category 'Replacement

Written \, replacement-only

Geminate :: Lexeme category a

Written >

Wildcard :: Lexeme category a -> Lexeme category a

Written ^lexeme

Kleene :: Lexeme category a -> Lexeme category a

Written lexeme*

Discard :: Lexeme category 'Replacement

Written ~, replacement-only

Backreference :: Either String Int -> category a -> Lexeme category a

Written @n category or @#id category

Multiple :: category 'Replacement -> Lexeme category 'Replacement

Written @? category

Feature

Written lexeme$Name or variations (see reference guide)

Fields

Autosegment

Not directly available in Brassica syntax, inserted in expansion

Fields

Instances

Instances details
(forall (x :: LexemeType). Show (c x)) => Show (Lexeme c a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

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

show :: Lexeme c a -> String #

showList :: [Lexeme c a] -> ShowS #

(forall (x :: LexemeType). NFData (c x)) => NFData (Lexeme c a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Lexeme c a -> () #

(forall (x :: LexemeType). Eq (c x)) => Eq (Lexeme c a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

(==) :: Lexeme c a -> Lexeme c a -> Bool #

(/=) :: Lexeme c a -> Lexeme c a -> Bool #

(forall (x :: LexemeType). Ord (c x)) => Ord (Lexeme c a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

compare :: Lexeme c a -> Lexeme c a -> Ordering #

(<) :: Lexeme c a -> Lexeme c a -> Bool #

(<=) :: Lexeme c a -> Lexeme c a -> Bool #

(>) :: Lexeme c a -> Lexeme c a -> Bool #

(>=) :: Lexeme c a -> Lexeme c a -> Bool #

max :: Lexeme c a -> Lexeme c a -> Lexeme c a #

min :: Lexeme c a -> Lexeme c a -> Lexeme c a #

data LexemeType Source #

The part of a Rule in which a Lexeme may occur.

Constructors

Matched

In the target, environment or exception (‘matching’ position)

Replacement

In the replacement only

AnyPart

Not restricted to any one part

generalise :: (c 'AnyPart -> c a) -> Lexeme c 'AnyPart -> Lexeme c a Source #

Generalise a Lexeme c 'AnyPart so it can be used in any specific part of a sound change, given a way to similarly generalise any categories it contains.

Categories

mapCategory :: (forall x. c x -> c' x) -> Lexeme c a -> Lexeme c' a Source #

Map a function over any categories in the given Lexeme.

mapCategoryA :: Applicative t => (forall x. c x -> t (c' x)) -> Lexeme c a -> t (Lexeme c' a) Source #

Like mapCategory, with an Applicative effect.

type CategoryElement category a = [Lexeme category a] Source #

A single element of a category: a sequence of Lexemes. (Single Graphemes receive some special treatment, e.g. they can be written without surrounding braces in Brassica syntax.)

data CategorySpec a Source #

The specification of a category in Brassica sound-change syntax. Usually this will be as a CategorySpec: a list of CategoryElements, each of which modifies the previous definition using the given CategoryModification method.

In some positions (e.g. after a Backreference) a category must be provided, but that category can be predefined, to be inlined during expansion. In such positions, the given category name is stored as a MustInline category. (In other positions predefined categories are indistinguishable from normal Graphemes, and represented as such.)

Constructors

CategorySpec [(CategoryModification, CategoryElement CategorySpec a)] 
MustInline String

A single grapheme assumed to have been specified earlier as a category

Instances

Instances details
Generic (CategorySpec a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep (CategorySpec a) :: Type -> Type #

Methods

from :: CategorySpec a -> Rep (CategorySpec a) x #

to :: Rep (CategorySpec a) x -> CategorySpec a #

Show (CategorySpec a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

NFData (CategorySpec a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: CategorySpec a -> () #

Eq (CategorySpec a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Ord (CategorySpec a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep (CategorySpec a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep (CategorySpec a) = D1 ('MetaData "CategorySpec" "Brassica.SoundChange.Types" "brassica-1.0.0-23v7eBGV3gz5i0Q0Z9IDsG" 'False) (C1 ('MetaCons "CategorySpec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(CategoryModification, CategoryElement CategorySpec a)])) :+: C1 ('MetaCons "MustInline" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data CategoryModification Source #

The individual operations used to construct a category in Brassica sound-change syntax.

Constructors

Union

Written [Category1 &Category2] or [Category1 Category2]

Intersect

Written [Category1 +Category2]

Subtract

Written [Category1 -Category2]

Instances

Instances details
Generic CategoryModification Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep CategoryModification :: Type -> Type #

Show CategoryModification Source # 
Instance details

Defined in Brassica.SoundChange.Types

NFData CategoryModification Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: CategoryModification -> () #

Eq CategoryModification Source # 
Instance details

Defined in Brassica.SoundChange.Types

Ord CategoryModification Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep CategoryModification Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep CategoryModification = D1 ('MetaData "CategoryModification" "Brassica.SoundChange.Types" "brassica-1.0.0-23v7eBGV3gz5i0Q0Z9IDsG" 'False) (C1 ('MetaCons "Union" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Intersect" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Subtract" 'PrefixI 'False) (U1 :: Type -> Type)))

newtype Expanded a Source #

The type of a category after expansion: a simple list of CategoryElements.

Constructors

FromElements 

Instances

Instances details
Monoid (Expanded a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

mempty :: Expanded a #

mappend :: Expanded a -> Expanded a -> Expanded a #

mconcat :: [Expanded a] -> Expanded a #

Semigroup (Expanded a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

(<>) :: Expanded a -> Expanded a -> Expanded a #

sconcat :: NonEmpty (Expanded a) -> Expanded a #

stimes :: Integral b => b -> Expanded a -> Expanded a #

Generic (Expanded a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep (Expanded a) :: Type -> Type #

Methods

from :: Expanded a -> Rep (Expanded a) x #

to :: Rep (Expanded a) x -> Expanded a #

Show (Expanded a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

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

show :: Expanded a -> String #

showList :: [Expanded a] -> ShowS #

NFData (Expanded a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Expanded a -> () #

Eq (Expanded a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

(==) :: Expanded a -> Expanded a -> Bool #

(/=) :: Expanded a -> Expanded a -> Bool #

Ord (Expanded a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

compare :: Expanded a -> Expanded a -> Ordering #

(<) :: Expanded a -> Expanded a -> Bool #

(<=) :: Expanded a -> Expanded a -> Bool #

(>) :: Expanded a -> Expanded a -> Bool #

(>=) :: Expanded a -> Expanded a -> Bool #

max :: Expanded a -> Expanded a -> Expanded a #

min :: Expanded a -> Expanded a -> Expanded a #

type Rep (Expanded a) Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep (Expanded a) = D1 ('MetaData "Expanded" "Brassica.SoundChange.Types" "brassica-1.0.0-23v7eBGV3gz5i0Q0Z9IDsG" 'True) (C1 ('MetaCons "FromElements" 'PrefixI 'True) (S1 ('MetaSel ('Just "elements") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CategoryElement Expanded a])))

generaliseExpanded :: Expanded 'AnyPart -> Expanded a Source #

Generalise an Expanded category to be used in any part of a sound change, similarly to generalise.

Rules

data Rule c Source #

A single sound change rule.

In Brassica sound-change syntax with all elements specified, this would be -flags target / replacement / environment1 / environment2 / … / exception.

Constructors

Rule 

Fields

Instances

Instances details
Generic (Rule c) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep (Rule c) :: Type -> Type #

Methods

from :: Rule c -> Rep (Rule c) x #

to :: Rep (Rule c) x -> Rule c #

(forall (a :: LexemeType). Show (c a)) => Show (Rule c) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

showsPrec :: Int -> Rule c -> ShowS #

show :: Rule c -> String #

showList :: [Rule c] -> ShowS #

(forall (a :: LexemeType). NFData (c a)) => NFData (Rule c) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Rule c -> () #

type Rep (Rule c) Source # 
Instance details

Defined in Brassica.SoundChange.Types

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

An Environment is a tuple of (before, after) components, corresponding to an environment or exception in a sound change: before _ after.

(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-1.0.0-23v7eBGV3gz5i0Q0Z9IDsG" 'False) (C1 ('MetaCons "LTR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RTL" 'PrefixI 'False) (U1 :: Type -> Type))

data Sporadicity Source #

Specifies how regularly a rule should be applied. A sporadic rule will produce two or more results, preserving the input as one of the outputs.

Constructors

ApplyAlways

Always apply the rule

PerWord

Apply sporadically, either to the whole word or to none of the word

PerApplication

Apply sporadically, at each application site

Instances

Instances details
Generic Sporadicity Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep Sporadicity :: Type -> Type #

Show Sporadicity Source # 
Instance details

Defined in Brassica.SoundChange.Types

NFData Sporadicity Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Sporadicity -> () #

Eq Sporadicity Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep Sporadicity Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep Sporadicity = D1 ('MetaData "Sporadicity" "Brassica.SoundChange.Types" "brassica-1.0.0-23v7eBGV3gz5i0Q0Z9IDsG" 'False) (C1 ('MetaCons "ApplyAlways" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PerWord" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PerApplication" '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.

Constructors

Flags 

Fields

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-1.0.0-23v7eBGV3gz5i0Q0Z9IDsG" '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 Sporadicity) :*: S1 ('MetaSel ('Just "nonOverlappingTarget") '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
    , nonOverlappingTarget = False
    }

That is: apply repeatedly and iteratively from left to right, non-sporadically, with the results available for highlighting.

Statements

data Filter c Source #

A filter, constraining the output to not match the given elements. (The String is the plaintext, as with Rule.)

Constructors

Filter String [Lexeme c 'Matched] 

Instances

Instances details
Generic (Filter c) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep (Filter c) :: Type -> Type #

Methods

from :: Filter c -> Rep (Filter c) x #

to :: Rep (Filter c) x -> Filter c #

(forall (a :: LexemeType). Show (c a)) => Show (Filter c) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

showsPrec :: Int -> Filter c -> ShowS #

show :: Filter c -> String #

showList :: [Filter c] -> ShowS #

(forall (a :: LexemeType). NFData (c a)) => NFData (Filter c) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Filter c -> () #

type Rep (Filter c) Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep (Filter c) = D1 ('MetaData "Filter" "Brassica.SoundChange.Types" "brassica-1.0.0-23v7eBGV3gz5i0Q0Z9IDsG" 'False) (C1 ('MetaCons "Filter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Lexeme c 'Matched])))

data Statement c decl Source #

A Statement within a sound change file can be a single sound change rule, a filter, an instruction to report intermediate results, or some other declaration.

The declaration type depends on the current sound change phase. Usually it will be Directive after parsing, or GraphemeList after expansion.

Constructors

RuleS (Rule c)

Sound change rule

FilterS (Filter c)

Filter

ReportS

Report intermediate result

DeclS decl

Declaration (phase-dependent)

Instances

Instances details
Generic (Statement c decl) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep (Statement c decl) :: Type -> Type #

Methods

from :: Statement c decl -> Rep (Statement c decl) x #

to :: Rep (Statement c decl) x -> Statement c decl #

(forall (a :: LexemeType). Show (c a), Show decl) => Show (Statement c decl) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

showsPrec :: Int -> Statement c decl -> ShowS #

show :: Statement c decl -> String #

showList :: [Statement c decl] -> ShowS #

(forall (a :: LexemeType). NFData (c a), NFData decl) => NFData (Statement c decl) Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Statement c decl -> () #

type Rep (Statement c decl) Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep (Statement c decl) = D1 ('MetaData "Statement" "Brassica.SoundChange.Types" "brassica-1.0.0-23v7eBGV3gz5i0Q0Z9IDsG" 'False) ((C1 ('MetaCons "RuleS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Rule c))) :+: C1 ('MetaCons "FilterS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Filter c)))) :+: (C1 ('MetaCons "ReportS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeclS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 decl))))

plaintext' :: Statement c decl -> String Source #

A simple wrapper around plaintext for Statements. Returns "<declaration>" for all DeclS inputs.

type SoundChanges c decl = [Statement c decl] Source #

A set of SoundChanges is simply a list of Statements.

Directives

data Directive Source #

A directive used in Brassica sound-change syntax: anything which occurs in a sound change file with the primary purpose of defining something for later use.

Constructors

Categories

Category definition block

Fields

ExtraGraphemes [String]

Extra graphemes declaration: extra …

Instances

Instances details
Generic Directive Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep Directive :: Type -> Type #

Show Directive Source # 
Instance details

Defined in Brassica.SoundChange.Types

NFData Directive Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Directive -> () #

Eq Directive Source # 
Instance details

Defined in Brassica.SoundChange.Types

Ord Directive Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep Directive Source # 
Instance details

Defined in Brassica.SoundChange.Types

data CategoryDefinition Source #

A single definition within a category definition block.

Constructors

DefineCategory String (CategorySpec 'AnyPart)

Defines a category with the given name and value

DefineFeature FeatureSpec

Defines a feature as a set of categories

DefineAuto String

Defines a category as autosegmental

Instances

Instances details
Generic CategoryDefinition Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep CategoryDefinition :: Type -> Type #

Show CategoryDefinition Source # 
Instance details

Defined in Brassica.SoundChange.Types

NFData CategoryDefinition Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: CategoryDefinition -> () #

Eq CategoryDefinition Source # 
Instance details

Defined in Brassica.SoundChange.Types

Ord CategoryDefinition Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep CategoryDefinition Source # 
Instance details

Defined in Brassica.SoundChange.Types

data FeatureSpec Source #

The specification of a suprasegmental feature in Brassica sound-change syntax.

Deprecated since 1.0.0.

Instances

Instances details
Generic FeatureSpec Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep FeatureSpec :: Type -> Type #

Show FeatureSpec Source # 
Instance details

Defined in Brassica.SoundChange.Types

NFData FeatureSpec Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: FeatureSpec -> () #

Eq FeatureSpec Source # 
Instance details

Defined in Brassica.SoundChange.Types

Ord FeatureSpec Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep FeatureSpec Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep FeatureSpec = D1 ('MetaData "FeatureSpec" "Brassica.SoundChange.Types" "brassica-1.0.0-23v7eBGV3gz5i0Q0Z9IDsG" 'False) (C1 ('MetaCons "FeatureSpec" 'PrefixI 'True) (S1 ('MetaSel ('Just "featureBaseName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Just "featureBaseValues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CategorySpec 'AnyPart)) :*: S1 ('MetaSel ('Just "featureDerived") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, CategorySpec 'AnyPart)]))))

data GraphemeList Source #

A list of graphemes, replacing Categories in expanded sound changes. These are used in tokenisation to determine which multigraphs are used, and in rule application to filter unwanted graphemes. The first Bool indicates whether filtration should occur for any particular categories block.

Constructors

GraphemeList Bool [Grapheme] 

Instances

Instances details
Generic GraphemeList Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep GraphemeList :: Type -> Type #

Show GraphemeList Source # 
Instance details

Defined in Brassica.SoundChange.Types

NFData GraphemeList Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: GraphemeList -> () #

Eq GraphemeList Source # 
Instance details

Defined in Brassica.SoundChange.Types

Ord GraphemeList Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep GraphemeList Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep GraphemeList = D1 ('MetaData "GraphemeList" "Brassica.SoundChange.Types" "brassica-1.0.0-23v7eBGV3gz5i0Q0Z9IDsG" 'False) (C1 ('MetaCons "GraphemeList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Grapheme])))