Copyright | See LICENSE file |
---|---|
License | BSD3 |
Maintainer | Brad Neimann |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Brassica.SoundChange.Expand
Description
This module implements the process of expansion, from Brassica’s surface syntax to a simpler representation in which all categories, features and autosegments have been inlined. For further
In the surface syntax, each category is represented as a
CategorySpec
, a description in terms of predefined categories
combined with category operations. Expansion converts each one to
an Expanded
list of graphemes.
Similarly, category definitions are parsed as Directive
s. Once
inlined, these can be replaced with simple GraphemeList
s to be
used for filtering graphemes.
Synopsis
- expandSoundChanges :: SoundChanges CategorySpec Directive -> Either ExpandError (SoundChanges Expanded GraphemeList)
- data ExpandError
- expand :: Categories -> CategorySpec a -> Either ExpandError (Expanded a)
- expandRule :: Categories -> Rule CategorySpec -> Either ExpandError (Rule Expanded)
- extendCategories :: Categories -> (Bool, [CategoryDefinition]) -> Either ExpandError Categories
- type Categories = Map String (Either (Expanded 'AnyPart) AutosegmentDef)
- data AutosegmentDef = AutosegmentDef {
- autoFeature :: String
- autoGraphemes :: [String]
- lookup :: String -> Categories -> Maybe (Either (Expanded a) AutosegmentDef)
- values :: Categories -> [[Lexeme Expanded 'AnyPart]]
Main function
expandSoundChanges :: SoundChanges CategorySpec Directive -> Either ExpandError (SoundChanges Expanded GraphemeList) Source #
Expand a set of SoundChanges
. Expansion proceeds from beginning
to end as follows:
- Rules and filters are expanded by expanding all categories
within them (with
expand
). Graphemes are replaced with categories or autosegments if previously defined as such. - If a
Categories
definition block is found, the categories defined within it are expanded and added to (or replace) the list of current categories. The block is replaced with a list of currently defined graphemes. - If
ExtraGraphemes
are found, they are added to a list of currently defined graphemes. They are replaced with aGraphemeList
only if no categories are defined in theSoundChanges
.
data ExpandError Source #
Errors which can be emitted while inlining or expanding category definitions.
Constructors
NotFound String | A category with the given name was not found |
InvalidBaseValue | A |
InvalidDerivedValue | A |
MismatchedLengths | A phonetic feature or |
Instances
Generic ExpandError Source # | |
Defined in Brassica.SoundChange.Expand Associated Types type Rep ExpandError :: Type -> Type # | |
Show ExpandError Source # | |
Defined in Brassica.SoundChange.Expand Methods showsPrec :: Int -> ExpandError -> ShowS # show :: ExpandError -> String # showList :: [ExpandError] -> ShowS # | |
NFData ExpandError Source # | |
Defined in Brassica.SoundChange.Expand Methods rnf :: ExpandError -> () # | |
type Rep ExpandError Source # | |
Defined in Brassica.SoundChange.Expand type Rep ExpandError = D1 ('MetaData "ExpandError" "Brassica.SoundChange.Expand" "brassica-1.0.0-inplace" 'False) ((C1 ('MetaCons "NotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "InvalidBaseValue" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "InvalidDerivedValue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MismatchedLengths" 'PrefixI 'False) (U1 :: Type -> Type))) |
Expanding individual elements
expand :: Categories -> CategorySpec a -> Either ExpandError (Expanded a) Source #
Given an unexpanded category, return the list of values which it matches.
expandRule :: Categories -> Rule CategorySpec -> Either ExpandError (Rule Expanded) Source #
Expand all categories in a given sound change Rule
.
Arguments
:: Categories | |
-> (Bool, [CategoryDefinition]) | The fields of a |
-> Either ExpandError Categories |
Extend a set of previously defined Categories
to give the
resulting state after a Categories
directive.
Categories
type Categories = Map String (Either (Expanded 'AnyPart) AutosegmentDef) Source #
A map from names to the (expanded) categories or autosegments they reference. Used to resolve cross-references between categories.
data AutosegmentDef Source #
Expanding an autosegment from a grapheme requires knowing its
feature name, and a set of graphemes cross-cutting that feature.
(Note that autoGraphemes
includes the originally-written
grapheme.)
Constructors
AutosegmentDef | |
Fields
|
Instances
Show AutosegmentDef Source # | |
Defined in Brassica.SoundChange.Expand Methods showsPrec :: Int -> AutosegmentDef -> ShowS # show :: AutosegmentDef -> String # showList :: [AutosegmentDef] -> ShowS # | |
Eq AutosegmentDef Source # | |
Defined in Brassica.SoundChange.Expand Methods (==) :: AutosegmentDef -> AutosegmentDef -> Bool # (/=) :: AutosegmentDef -> AutosegmentDef -> Bool # |
lookup :: String -> Categories -> Maybe (Either (Expanded a) AutosegmentDef) Source #
Lookup a category name in Categories
.
values :: Categories -> [[Lexeme Expanded 'AnyPart]] Source #
Returns a list of every value mentioned in a set of
Categories