Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Grapheme
- 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
- Optional :: [Lexeme category a] -> Lexeme category a
- 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 :: Int -> category a -> Lexeme category a
- Multiple :: category 'Replacement -> Lexeme category 'Replacement
- pattern Boundary :: Lexeme c 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)
- newtype Expanded a = FromElements {}
- 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
- = RuleS (Rule c)
- | FilterS (Filter c)
- | DirectiveS decl
- plaintext' :: Statement c decl -> String
- type SoundChanges c decl = [Statement c decl]
- data CategoryModification
- data CategorySpec a
- data FeatureSpec = FeatureSpec {}
- data CategoryDefinition
- data Directive
Words and graphemes
The type of graphemes within a word.
GMulti [Char] | A multigraph: for instance |
GBoundary | A non-letter element representing a word boundary which sound changes can manipulate |
Instances
IsString Grapheme Source # | |
Defined in Brassica.SoundChange.Types fromString :: String -> Grapheme # | |
Generic Grapheme Source # | |
Show Grapheme Source # | |
NFData Grapheme Source # | |
Defined in Brassica.SoundChange.Types | |
Eq Grapheme Source # | |
Ord Grapheme Source # | |
Defined in Brassica.SoundChange.Types | |
type Rep Grapheme Source # | |
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)) |
addBoundaries :: PWord -> PWord Source #
removeBoundaries :: PWord -> PWord Source #
concatWithBoundary :: PWord -> String Source #
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 Lexeme
s: the phantom type
variable a
specifies where each different variety of Lexeme
may
occur. Lexeme
s are also parameterised by their category type,
which may be Expanded
or something else.
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 |
Kleene :: Lexeme category a -> Lexeme category a | In Brassica sound-change syntax, specified as |
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
(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 |
pattern Boundary :: Lexeme c a Source #
A Lexeme
matching a single word boundary, specified as #
in Brassica syntax.
data LexemeType 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 #
The type of a category after expansion.
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-0.3.0-LNHGd2ZODG75RcrVOMZ8jM" 'True) (C1 ('MetaCons "FromElements" 'PrefixI 'True) (S1 ('MetaSel ('Just "elements") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Either Grapheme [Lexeme Expanded a]]))) |
Rules
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.)
Rule | |
|
Instances
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 ([], [])
.
Specifies application direction of rule — either left-to-right or right-to-left.
data Sporadicity Source #
Specifies how regularly a rule should be applied.
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.
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-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)))) |
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
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-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).
RuleS (Rule c) | |
FilterS (Filter c) | |
DirectiveS decl |
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-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 Statement
s. Returns
"directive"
for all DirectiveS
inputs.
type SoundChanges c decl = [Statement c decl] Source #
A set of SoundChanges
is simply a list of Statement
s.
Directives
data CategoryModification Source #
The individual operations used to construct a category in Brassica sound-change syntax.
Instances
data CategorySpec a Source #
The specification of a category in Brassica sound-change syntax.
CategorySpec [(CategoryModification, Either Grapheme [Lexeme CategorySpec a])] | |
MustInline String | A single grapheme assumed to have been specified earlier as a category |
Instances
data FeatureSpec Source #
The specification of a suprasegmental feature in Brassica sound-change syntax.
Instances
data CategoryDefinition Source #
A definition of a new category, either directly or via features.
Instances
A directive used in Brassica sound-change syntax: anything which is not actually a sound change
Categories Bool Bool [CategoryDefinition] |
|
ExtraGraphemes [String] | extra … |
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-0.3.0-LNHGd2ZODG75RcrVOMZ8jM" '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]))) |