| Copyright | See LICENSE file |
|---|---|
| License | BSD3 |
| Maintainer | Brad Neimann |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Brassica.SoundChange.Apply.Internal
Description
Warning: This module is internal, and does not follow the Package Versioning Policy. It may be useful for extending Brassica, but be prepared to track development closely if you import this module.
This module contains the lower-level functions used by Brassica to match and apply sound changes. The overall algorithm is similar to that described by Howard (1973).
Some essential points:
- Words are represented as
MultiZippers, with a cursor index and zero or more tagged indices. A sound change can then be applied (applyRuleMZ) by advancing through the word from left to right. (Right-to-left application is achieved by reversing both word and rule.) - For each potential application site,
applyOncechecks the target, environments and exceptions. If they are all satisfied, it then replaces the target graphemes with the replacement graphemes. After runningapplyOnce,setupForNextApplicationcan be used to advance to the next application site. - The lowest-level function for matching is
match, which matches an individualLexemeat some point in a word. The lowest-level function for replacement ismkReplacement, which constructs replacement graphemes.
Synopsis
- data RuleTag
- data RuleStatus
- data MatchOutput = MatchOutput {
- matchedCatIxs :: [Int]
- matchedOptionals :: [Bool]
- matchedWildcards :: [[Grapheme]]
- matchedKleenes :: [Int]
- matchedGraphemes :: [Grapheme]
- matchedFeatures :: Map String [FeatureState]
- matchedBackrefIds :: Map String Int
- matchedFeatureIds :: Map String FeatureState
- data FeatureState
- newOutput :: MatchOutput -> MatchOutput
- initialOutput :: MatchOutput
- match :: MatchOutput -> Maybe Grapheme -> Lexeme Expanded 'Matched -> MultiZipper t Grapheme -> [(MatchOutput, MultiZipper t Grapheme)]
- matchMany :: MatchOutput -> Maybe Grapheme -> [Lexeme Expanded 'Matched] -> MultiZipper t Grapheme -> [(MatchOutput, MultiZipper t Grapheme)]
- mkReplacement :: MatchOutput -> [Lexeme Expanded 'Replacement] -> MultiZipper t Grapheme -> [MultiZipper t Grapheme]
- exceptionAppliesAtPoint :: [Lexeme Expanded 'Matched] -> Environment Expanded -> MultiZipper RuleTag Grapheme -> [Int]
- matchRuleAtPoint :: [Lexeme Expanded 'Matched] -> Environment Expanded -> MultiZipper RuleTag Grapheme -> [(MatchOutput, MultiZipper RuleTag Grapheme)]
- applyOnce :: Rule Expanded -> StateT (MultiZipper RuleTag Grapheme) [] RuleStatus
- setupForNextApplication :: RuleStatus -> Rule Expanded -> MultiZipper RuleTag Grapheme -> Maybe (MultiZipper RuleTag Grapheme)
- applyRuleMZ :: Rule Expanded -> MultiZipper RuleTag Grapheme -> [MultiZipper RuleTag Grapheme]
- checkGraphemes :: [Grapheme] -> MultiZipper RuleTag Grapheme -> MultiZipper RuleTag Grapheme
- applyStatementMZ :: Statement Expanded GraphemeList -> MultiZipper RuleTag Grapheme -> [MultiZipper RuleTag Grapheme]
- applyRuleStr :: Rule Expanded -> PWord -> [PWord]
- applyStatementStr :: Statement Expanded GraphemeList -> PWord -> [PWord]
- data LogItem r
- = ActionApplied r (Maybe PWord)
- | ReportWord PWord
- data Log r = Log {
- inputWord :: PWord
- derivations :: [LogItem r]
- reportAsHtmlRows :: (r -> String) -> Log r -> String
- reportAsText :: (r -> String) -> Log r -> String
- applyStatement :: Statement Expanded GraphemeList -> PWord -> [LogItem (Statement Expanded GraphemeList)]
- applyChanges :: SoundChanges Expanded GraphemeList -> PWord -> [Log (Statement Expanded GraphemeList)]
- getOutput :: Log r -> Maybe PWord
- getReports :: Log r -> [PWord]
- getChangedOutputs :: Log (Statement c d) -> Maybe (PWord, Bool)
- getChangedReports :: Log (Statement c d) -> [(PWord, Bool)]
Lexeme matching
Defines the tags used when applying a Rule.
Constructors
| AppStart | The start of a rule application |
| TargetStart | The start of the target |
| TargetEnd | The end of the target |
| PrevEnd | The end of the replacement from the last rule application (used to avoid infinite loops from iterative rules) |
data RuleStatus Source #
Status of a rule application at a single location.
Constructors
| SuccessNormal | Rule was successful, with no need for special handling |
| SuccessEpenthesis | Rule was successful, but cursor was not advanced (need to avoid infinite loop) |
| Failure | Rule failed |
Instances
| Show RuleStatus Source # | |
Defined in Brassica.SoundChange.Apply.Internal Methods showsPrec :: Int -> RuleStatus -> ShowS # show :: RuleStatus -> String # showList :: [RuleStatus] -> ShowS # | |
| Eq RuleStatus Source # | |
Defined in Brassica.SoundChange.Apply.Internal | |
data MatchOutput Source #
Describes the output of a match operation.
Constructors
| MatchOutput | |
Fields
| |
Instances
| Show MatchOutput Source # | |
Defined in Brassica.SoundChange.Apply.Internal Methods showsPrec :: Int -> MatchOutput -> ShowS # show :: MatchOutput -> String # showList :: [MatchOutput] -> ShowS # | |
data FeatureState Source #
The result of matching a Feature or Autosegment: either a
specific index in the Feature, or an indeterminate result (when
no indices matched)
Constructors
| Index Int | |
| Indeterminate |
Instances
| Show FeatureState Source # | |
Defined in Brassica.SoundChange.Apply.Internal Methods showsPrec :: Int -> FeatureState -> ShowS # show :: FeatureState -> String # showList :: [FeatureState] -> ShowS # | |
| Eq FeatureState Source # | |
Defined in Brassica.SoundChange.Apply.Internal | |
newOutput :: MatchOutput -> MatchOutput Source #
Create MatchOutput for next section of rule given last output
(preserving backreferences but emptying all other fields)
initialOutput :: MatchOutput Source #
The empty MatchOutput
Arguments
| :: MatchOutput | The previous |
| -> Maybe Grapheme | The previously-matched grapheme, if any. (Used to match a |
| -> Lexeme Expanded 'Matched | The lexeme to match. |
| -> MultiZipper t Grapheme | The |
| -> [(MatchOutput, MultiZipper t Grapheme)] | The output: a tuple |
Match a single Lexeme against a MultiZipper, and advance the
MultiZipper past the match. For each match found, returns the
updated MatchOutput tupled with the updated MultiZipper.
matchMany :: MatchOutput -> Maybe Grapheme -> [Lexeme Expanded 'Matched] -> MultiZipper t Grapheme -> [(MatchOutput, MultiZipper t Grapheme)] Source #
Match a list of several Lexemes against a
MultiZipper. Arguments and output are as with match.
Arguments
| :: MatchOutput | The result of matching against the target |
| -> [Lexeme Expanded 'Replacement] | The |
| -> MultiZipper t Grapheme | |
| -> [MultiZipper t Grapheme] |
Given a list of Lexemes specifying a replacement, generate all
possible replacements and apply them to the given input.
exceptionAppliesAtPoint Source #
Arguments
| :: [Lexeme Expanded 'Matched] | Target |
| -> Environment Expanded | Exceptional environment |
| -> MultiZipper RuleTag Grapheme | |
| -> [Int] |
Given a Rule and a MultiZipper, determines whether the
exception of that rule (if any) applies starting at the current
position of the MultiZipper; if it does, returns the index at
which each matching target begins.
Arguments
| :: [Lexeme Expanded 'Matched] | Target |
| -> Environment Expanded | Environment |
| -> MultiZipper RuleTag Grapheme | |
| -> [(MatchOutput, MultiZipper RuleTag Grapheme)] |
Given a target and environment, determine if the rule matches at
the current position of the MultiZipper. If so, for each match,
return the MatchOutput and the output MultiZipper. The output
MultiZipper is advanced past the matched environment, and has its
RuleTags set as appropriate.
Sound change application
applyOnce :: Rule Expanded -> StateT (MultiZipper RuleTag Grapheme) [] RuleStatus Source #
Given a Rule, determine if the rule matches at the current
point; if so, apply the rule, adding appropriate tags.
setupForNextApplication :: RuleStatus -> Rule Expanded -> MultiZipper RuleTag Grapheme -> Maybe (MultiZipper RuleTag Grapheme) Source #
Remove tags and advance the current index to the next Grapheme
after the rule application.
applyRuleMZ :: Rule Expanded -> MultiZipper RuleTag Grapheme -> [MultiZipper RuleTag Grapheme] Source #
Apply a Rule to a MultiZipper. The application will start at
the beginning of the MultiZipper, and will be repeated as many
times as possible. Returns all valid results.
Note: unlike applyRuleStr, this can produce duplicate outputs.
checkGraphemes :: [Grapheme] -> MultiZipper RuleTag Grapheme -> MultiZipper RuleTag Grapheme Source #
Check that the MultiZipper contains only graphemes listed in
the given list, replacing all unlisted graphemes other than "#"
with U+FFFD.
applyStatementMZ :: Statement Expanded GraphemeList -> MultiZipper RuleTag Grapheme -> [MultiZipper RuleTag Grapheme] Source #
Apply a Statement to a MultiZipper, returning zero, one or
more results.
applyRuleStr :: Rule Expanded -> PWord -> [PWord] Source #
Apply a single sound change Rule to a word.
applyStatementStr :: Statement Expanded GraphemeList -> PWord -> [PWord] Source #
Apply a single Statement to a word. The statement can be a
sound change, a filter, or any other element which remains in a
sound change file after expansion.
Logging
A log item representing a single action r (usually a
Statement), and the result from that action.
Constructors
| ActionApplied r (Maybe PWord) | The word was modified: gives the output word, or |
| ReportWord PWord | Corresponds to |
Instances
| Functor LogItem Source # | |
| Generic (LogItem r) Source # | |
| Show r => Show (LogItem r) Source # | |
| NFData r => NFData (LogItem r) Source # | |
Defined in Brassica.SoundChange.Apply.Internal | |
| type Rep (LogItem r) Source # | |
Defined in Brassica.SoundChange.Apply.Internal type Rep (LogItem r) = D1 ('MetaData "LogItem" "Brassica.SoundChange.Apply.Internal" "brassica-1.0.0-inplace" 'False) (C1 ('MetaCons "ActionApplied" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 r) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PWord))) :+: C1 ('MetaCons "ReportWord" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PWord))) | |
Logs the evolution of a word as it undergoes sound changes and other actions.
Constructors
| Log | |
Fields
| |
Instances
| Functor Log Source # | |
| Generic (Log r) Source # | |
| Show r => Show (Log r) Source # | |
| NFData r => NFData (Log r) Source # | |
Defined in Brassica.SoundChange.Apply.Internal | |
| type Rep (Log r) Source # | |
Defined in Brassica.SoundChange.Apply.Internal type Rep (Log r) = D1 ('MetaData "Log" "Brassica.SoundChange.Apply.Internal" "brassica-1.0.0-inplace" 'False) (C1 ('MetaCons "Log" 'PrefixI 'True) (S1 ('MetaSel ('Just "inputWord") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PWord) :*: S1 ('MetaSel ('Just "derivations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LogItem r]))) | |
Pretty-print a single Log as rows of an HTML table. For
instance, the example log given in the documentation for
reportAsText would be converted to the following HTML:
<tr><td>tara</td><td>→</td><td>tazha</td><td>(r / zh)</td></tr><tr><td></td><td>→</td><td>tazh</td><td>(V / / _ #)</td></tr>
Which might be displayed in a browser as follows:
| tara | → | tazha | (r / zh) |
| → | tazh | (V _ #) |
Pretty-print a Log as plain text. For instance, this log:
Log{inputWord= ["t", "a", "r", "a"] ,derivations= [ (Just["t", "a", "zh", "a"], "r / zh") , (Just["t", "a", "zh"], "V / / _ #") ] }
Would be pretty-printed by as:reportAsText id
tara -> tazha (r / zh) -> tazh (V / / _ #)
applyStatement :: Statement Expanded GraphemeList -> PWord -> [LogItem (Statement Expanded GraphemeList)] Source #
applyChanges :: SoundChanges Expanded GraphemeList -> PWord -> [Log (Statement Expanded GraphemeList)] Source #
Apply a set of SoundChanges to a word, returning a log of which
sound changes applied to produce each output word.
getReports :: Log r -> [PWord] Source #
Returns, in order: the input word, any intermediate results from
ReportS, and then the final output.
getChangedOutputs :: Log (Statement c d) -> Maybe (PWord, Bool) Source #
Returns the final output from a sound change log, as well as an
indication of whether any sound changes have applied to it
(accounting for highlightChanges flags).
getChangedReports :: Log (Statement c d) -> [(PWord, Bool)] Source #
A combination of getOutput and getChangedOutputs: returns all
intermediate results, as well as whether each has undergone any
sound changes.