| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Brassica.SoundChange.Types
Synopsis
- type Grapheme = [Char]
- type PWord = [Grapheme]
- data Lexeme (a :: LexemeType) where
- Grapheme :: Grapheme -> Lexeme a
- Category :: [CategoryElement a] -> Lexeme a
- Boundary :: Lexeme 'Env
- Optional :: [Lexeme a] -> Lexeme a
- Metathesis :: Lexeme 'Replacement
- Geminate :: Lexeme a
- Wildcard :: OneOf a 'Target 'Env => Lexeme a -> Lexeme a
- Kleene :: OneOf a 'Target 'Env => Lexeme a -> Lexeme a
- Discard :: Lexeme 'Replacement
- data CategoryElement (a :: LexemeType) where
- GraphemeEl :: Grapheme -> CategoryElement a
- BoundaryEl :: CategoryElement 'Env
- data LexemeType
- = Target
- | Replacement
- | Env
- data Rule = Rule {
- target :: [Lexeme 'Target]
- replacement :: [Lexeme 'Replacement]
- environment :: Environment
- exception :: Maybe Environment
- flags :: Flags
- plaintext :: String
- type Environment = ([Lexeme 'Env], [Lexeme 'Env])
- data Direction
- data Flags = Flags {}
- defFlags :: Flags
- newtype CategoriesDecl = CategoriesDecl {}
- data Statement
- plaintext' :: Statement -> String
- type SoundChanges = [Statement]
- type family OneOf a x y :: Constraint where ...
Words and graphemes
type Grapheme = [Char] Source #
The type of graphemes, or more accurately multigraphs: for
instance, "a", "ch", "c̓" :: .Grapheme
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 |
| Kleene :: OneOf a 'Target 'Env => Lexeme a -> Lexeme a | In Brassica sound-change syntax, specified as |
| Discard :: Lexeme 'Replacement | In Brassica sound-change syntax, specified as |
data CategoryElement (a :: LexemeType) where Source #
Constructors
| GraphemeEl :: Grapheme -> CategoryElement a | |
| BoundaryEl :: CategoryElement 'Env |
Instances
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
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.)
Constructors
| Rule | |
Fields
| |
Instances
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 ([], []).
Specifies application direction of rule — either left-to-right or right-to-left.
Flags which can be enabled, disabled or altered on a Rule to
change how it is applied.
Constructors
| Flags | |
Fields
| |
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.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)))) | |
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 | |
Instances
| Generic CategoriesDecl Source # | |
Defined in Brassica.SoundChange.Types Associated Types type Rep CategoriesDecl :: Type -> Type # Methods from :: CategoriesDecl -> Rep CategoriesDecl x # to :: Rep CategoriesDecl x -> CategoriesDecl # | |
| Show CategoriesDecl Source # | |
Defined in Brassica.SoundChange.Types Methods showsPrec :: Int -> CategoriesDecl -> ShowS # show :: CategoriesDecl -> String # showList :: [CategoriesDecl] -> ShowS # | |
| NFData CategoriesDecl Source # | |
Defined in Brassica.SoundChange.Types Methods rnf :: CategoriesDecl -> () # | |
| type Rep CategoriesDecl Source # | |
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]))) | |
A Statement can be either a single sound change rule, or a
category declaration.
Constructors
| RuleS Rule | |
| CategoriesDeclS CategoriesDecl |
Instances
| Generic Statement Source # | |
| Show Statement Source # | |
| NFData Statement Source # | |
Defined in Brassica.SoundChange.Types | |
| type Rep Statement Source # | |
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.)