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

Brassica.SoundChange.Types

Synopsis

Words and graphemes

data Grapheme Source #

The type of graphemes within a word.

Constructors

GMulti [Char]

A multigraph: for instance GMulti "a", GMulti "ch", GMulti "c̓" :: Grapheme.

GBoundary

A non-letter element representing a word boundary which sound changes can manipulate

Instances

Instances details
IsString Grapheme Source # 
Instance details

Defined in Brassica.SoundChange.Types

Generic Grapheme Source # 
Instance details

Defined in Brassica.SoundChange.Types

Associated Types

type Rep Grapheme :: Type -> Type #

Methods

from :: Grapheme -> Rep Grapheme x #

to :: Rep Grapheme x -> Grapheme #

Show Grapheme Source # 
Instance details

Defined in Brassica.SoundChange.Types

NFData Grapheme Source # 
Instance details

Defined in Brassica.SoundChange.Types

Methods

rnf :: Grapheme -> () #

Eq Grapheme Source # 
Instance details

Defined in Brassica.SoundChange.Types

Ord Grapheme Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep Grapheme Source # 
Instance details

Defined in Brassica.SoundChange.Types

type Rep Grapheme = D1 ('MetaData "Grapheme" "Brassica.SoundChange.Types" "brassica-0.3.0-LNHGd2ZODG75RcrVOMZ8jM" 'False) (C1 ('MetaCons "GMulti" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Char])) :+: C1 ('MetaCons "GBoundary" 'PrefixI 'False) (U1 :: Type -> Type))

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.)

concatWithBoundary :: PWord -> String Source #

Render a PWord as a String. Very much like concat, but treating GBoundarys specially. Word-external boundaries are deleted, while word-internal boundaries are converted to "#".

Lexemes

data Lexeme category (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 a specifies where each different variety of Lexeme may occur. Lexemes are also parameterised by their category type, which may be Expanded or something else.

Constructors

Grapheme :: Grapheme -> Lexeme category a

In Brassica sound-change syntax, one or more letters without intervening whitespace, or a word boundary specified as #

Category :: category a -> Lexeme category a

In Brassica sound-change syntax, delimited by square brackets

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

In Brassica sound-change syntax, delimited by parentheses

Metathesis :: Lexeme category 'Replacement

In Brassica sound-change syntax, specified as @@

Geminate :: Lexeme category a

In Brassica sound-change syntax, specified as >

Wildcard :: Lexeme category a -> Lexeme category a

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

Kleene :: Lexeme category a -> Lexeme category a

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

Discard :: Lexeme category 'Replacement

In Brassica sound-change syntax, specified as ~

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

In Brassica sound-change syntax, specified as @i before a category

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

In Brassica sound-change syntax, specified as @? before a category

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 #

pattern Boundary :: Lexeme c a Source #

A Lexeme matching a single word boundary, specified as # in Brassica syntax.

data LexemeType Source #

The part of a Rule in which a Lexeme may occur: in a matched part (target or environment), in replacement, or in either of those.

Constructors

Matched 
Replacement 
AnyPart 

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

Categories

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

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

newtype Expanded a Source #

The type of a category after expansion.

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-0.3.0-LNHGd2ZODG75RcrVOMZ8jM" 'True) (C1 ('MetaCons "FromElements" 'PrefixI 'True) (S1 ('MetaSel ('Just "elements") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Either Grapheme [Lexeme Expanded a]])))

Rules

data Rule c Source #

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

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 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.3.0-LNHGd2ZODG75RcrVOMZ8jM" '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.

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-0.3.0-LNHGd2ZODG75RcrVOMZ8jM" '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.

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.3.0-LNHGd2ZODG75RcrVOMZ8jM" '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))))

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.

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-0.3.0-LNHGd2ZODG75RcrVOMZ8jM" '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 can be a single sound change rule, a filter, or a directive (e.g. category definition).

Constructors

RuleS (Rule c) 
FilterS (Filter c) 
DirectiveS decl 

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-0.3.0-LNHGd2ZODG75RcrVOMZ8jM" '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 "DirectiveS" '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 "directive" for all DirectiveS inputs.

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

A set of SoundChanges is simply a list of Statements.

Directives

data CategoryModification Source #

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

Constructors

Union 
Intersect 
Subtract 

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-0.3.0-LNHGd2ZODG75RcrVOMZ8jM" '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)))

data CategorySpec a Source #

The specification of a category in Brassica sound-change syntax.

Constructors

CategorySpec [(CategoryModification, Either Grapheme [Lexeme 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-0.3.0-LNHGd2ZODG75RcrVOMZ8jM" 'False) (C1 ('MetaCons "CategorySpec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(CategoryModification, Either Grapheme [Lexeme CategorySpec a])])) :+: C1 ('MetaCons "MustInline" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data FeatureSpec Source #

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

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-0.3.0-LNHGd2ZODG75RcrVOMZ8jM" '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 CategoryDefinition Source #

A definition of a new category, either directly or via features.

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 Directive Source #

A directive used in Brassica sound-change syntax: anything which is not actually a sound change

Constructors

Categories Bool Bool [CategoryDefinition]

categories … end: first Bool for new, second for noreplace

ExtraGraphemes [String]
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