Copyright | See LICENSE file |
---|---|
License | BSD3 |
Maintainer | Brad Neimann |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
Rule
s - Sound changes are composed of
Lexeme
s denoting parts of the input and output words - Each word is a sequence of
Grapheme
s
For more details on the syntax and semantics of sound changes, refer to the reference guide.
Synopsis
- type Grapheme = [Char]
- type PWord = [Grapheme]
- addBoundaries :: PWord -> PWord
- removeBoundaries :: PWord -> PWord
- concatWithBoundary :: PWord -> String
- data Lexeme category (a :: LexemeType) where
- Grapheme :: Grapheme -> Lexeme category a
- Category :: category a -> Lexeme category a
- GreedyCategory :: category 'Matched -> Lexeme category 'Matched
- Optional :: [Lexeme category a] -> Lexeme category a
- GreedyOptional :: [Lexeme category 'Matched] -> Lexeme category 'Matched
- Metathesis :: Lexeme category 'Replacement
- Geminate :: Lexeme category a
- Wildcard :: Lexeme category a -> Lexeme category a
- Kleene :: Lexeme category a -> Lexeme category a
- Discard :: Lexeme category 'Replacement
- Backreference :: Either String Int -> category a -> Lexeme category a
- Multiple :: category 'Replacement -> Lexeme category 'Replacement
- Feature :: Bool -> String -> Maybe String -> [[Grapheme]] -> Lexeme category a -> Lexeme category a
- Autosegment :: Grapheme -> [[(Grapheme, Bool)]] -> [Grapheme] -> Lexeme category a
- data LexemeType
- generalise :: (c 'AnyPart -> c a) -> Lexeme c 'AnyPart -> Lexeme c a
- mapCategory :: (forall x. c x -> c' x) -> Lexeme c a -> Lexeme c' a
- mapCategoryA :: Applicative t => (forall x. c x -> t (c' x)) -> Lexeme c a -> t (Lexeme c' a)
- type CategoryElement category a = [Lexeme category a]
- data CategorySpec a
- data CategoryModification
- newtype Expanded a = FromElements {
- elements :: [CategoryElement Expanded a]
- generaliseExpanded :: Expanded 'AnyPart -> Expanded a
- data Rule c = Rule {
- target :: [Lexeme c 'Matched]
- replacement :: [Lexeme c 'Replacement]
- environment :: [Environment c]
- exception :: Maybe (Environment c)
- flags :: Flags
- plaintext :: String
- type Environment c = ([Lexeme c 'Matched], [Lexeme c 'Matched])
- data Direction
- data Sporadicity
- data Flags = Flags {}
- defFlags :: Flags
- data Filter c = Filter String [Lexeme c 'Matched]
- data Statement c decl
- plaintext' :: Statement c decl -> String
- type SoundChanges c decl = [Statement c decl]
- data Directive
- data CategoryDefinition
- data FeatureSpec = FeatureSpec {}
- data GraphemeList = GraphemeList Bool [Grapheme]
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
Grapheme
s. 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
from Word
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
.
concatWithBoundary :: PWord -> String Source #
Render a PWord
as a String
: does removeBoundaries
then concat
.
Lexemes
data Lexeme category (a :: LexemeType) where Source #
Each part of a sound change is made up of a sequence of
Lexeme
s. 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.
Grapheme :: Grapheme -> Lexeme category a | |
Category :: category a -> Lexeme category a | |
GreedyCategory :: category 'Matched -> Lexeme category 'Matched | Written |
Optional :: [Lexeme category a] -> Lexeme category a | Written |
GreedyOptional :: [Lexeme category 'Matched] -> Lexeme category 'Matched | Written |
Metathesis :: Lexeme category 'Replacement | Written |
Geminate :: Lexeme category a | Written |
Wildcard :: Lexeme category a -> Lexeme category a | Written |
Kleene :: Lexeme category a -> Lexeme category a | Written |
Discard :: Lexeme category 'Replacement | Written |
Backreference :: Either String Int -> category a -> Lexeme category a | Written |
Multiple :: category 'Replacement -> Lexeme category 'Replacement | Written |
Feature | Written |
Autosegment | Not directly available in Brassica syntax, inserted in expansion |
Instances
(forall (x :: LexemeType). Show (c x)) => Show (Lexeme c a) Source # | |
(forall (x :: LexemeType). NFData (c x)) => NFData (Lexeme c a) Source # | |
Defined in Brassica.SoundChange.Types | |
(forall (x :: LexemeType). Eq (c x)) => Eq (Lexeme c a) Source # | |
(forall (x :: LexemeType). Ord (c x)) => Ord (Lexeme c a) Source # | |
Defined in Brassica.SoundChange.Types |
data LexemeType Source #
Matched | In the target, environment or exception (‘matching’ position) |
Replacement | In the replacement only |
AnyPart | Not restricted to any one part |
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 #
data CategorySpec a Source #
The specification of a category in Brassica sound-change
syntax. Usually this will be as a CategorySpec
: a list of
CategoryElement
s, 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 Grapheme
s, and represented as
such.)
CategorySpec [(CategoryModification, CategoryElement CategorySpec a)] | |
MustInline String | A single grapheme assumed to have been specified earlier as a category |
Instances
data CategoryModification Source #
The individual operations used to construct a category in Brassica sound-change syntax.
Union | Written |
Intersect | Written |
Subtract | Written |
Instances
The type of a category after expansion: a simple list of
CategoryElement
s.
Instances
Monoid (Expanded a) Source # | |
Semigroup (Expanded a) Source # | |
Generic (Expanded a) Source # | |
Show (Expanded a) Source # | |
NFData (Expanded a) Source # | |
Defined in Brassica.SoundChange.Types | |
Eq (Expanded a) Source # | |
Ord (Expanded a) Source # | |
Defined in Brassica.SoundChange.Types | |
type Rep (Expanded a) Source # | |
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
A single sound change rule.
In Brassica sound-change syntax with all elements specified, this would be
-flags target / replacement / environment1 / environment2 / … / exception
.
Rule | |
|
Instances
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 ([], [])
.)
Specifies application direction of rule: either left-to-right or right-to-left.
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.
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
Flags which can be enabled, disabled or altered on a Rule
to
change how it is applied.
Flags | |
|
Instances
Generic Flags Source # | |
Show Flags Source # | |
NFData Flags Source # | |
Defined in Brassica.SoundChange.Types | |
type Rep Flags Source # | |
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))))) |
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
A filter, constraining the output to not match the given elements.
(The String
is the plaintext, as with Rule
.)
Instances
Generic (Filter c) Source # | |
(forall (a :: LexemeType). Show (c a)) => Show (Filter c) Source # | |
(forall (a :: LexemeType). NFData (c a)) => NFData (Filter c) Source # | |
Defined in Brassica.SoundChange.Types | |
type Rep (Filter c) Source # | |
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.
RuleS (Rule c) | Sound change rule |
FilterS (Filter c) | Filter |
ReportS | Report intermediate result |
DeclS decl | Declaration (phase-dependent) |
Instances
Generic (Statement c decl) Source # | |
(forall (a :: LexemeType). Show (c a), Show decl) => Show (Statement c decl) Source # | |
(forall (a :: LexemeType). NFData (c a), NFData decl) => NFData (Statement c decl) Source # | |
Defined in Brassica.SoundChange.Types | |
type Rep (Statement c decl) Source # | |
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 #
type SoundChanges c decl = [Statement c decl] Source #
A set of SoundChanges
is simply a list of Statement
s.
Directives
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.
Categories | Category definition block |
| |
ExtraGraphemes [String] | Extra graphemes declaration: |
Instances
Generic Directive Source # | |
Show Directive Source # | |
NFData Directive Source # | |
Defined in Brassica.SoundChange.Types | |
Eq Directive Source # | |
Ord Directive Source # | |
Defined in Brassica.SoundChange.Types | |
type Rep Directive Source # | |
Defined in Brassica.SoundChange.Types type Rep Directive = D1 ('MetaData "Directive" "Brassica.SoundChange.Types" "brassica-1.0.0-23v7eBGV3gz5i0Q0Z9IDsG" 'False) (C1 ('MetaCons "Categories" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CategoryDefinition]))) :+: C1 ('MetaCons "ExtraGraphemes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) |
data CategoryDefinition Source #
A single definition within a category definition block.
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
data FeatureSpec Source #
The specification of a suprasegmental feature in Brassica sound-change syntax.
Deprecated since 1.0.0.
Instances
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.