Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- applyRuleStr :: Rule Expanded -> PWord -> [PWord]
- applyStatementStr :: Statement Expanded [Grapheme] -> PWord -> [PWord]
- applyChanges :: SoundChanges Expanded [Grapheme] -> PWord -> [PWord]
- applyChangesWithLogs :: SoundChanges Expanded [Grapheme] -> PWord -> [PWordLog (Statement Expanded [Grapheme])]
- applyChangesWithChanges :: SoundChanges Expanded [Grapheme] -> PWord -> [(PWord, Bool)]
- data PWordLog r = PWordLog {
- initialWord :: PWord
- derivations :: [(PWord, r)]
- reportAsText :: (r -> String) -> PWordLog r -> String
- reportAsHtmlRows :: (r -> String) -> PWordLog r -> String
Sound change application
applyStatementStr :: Statement Expanded [Grapheme] -> PWord -> [PWord] Source #
Apply a single Statement
to a word.
Note: as with applyRuleStr
, duplicate outputs from this function
are removed. To keep duplicates, use the lower-level internal
function applyStatement
directly.
applyChanges :: SoundChanges Expanded [Grapheme] -> PWord -> [PWord] Source #
Apply a set of SoundChanges
to a word.
Logging
applyChangesWithLogs :: SoundChanges Expanded [Grapheme] -> PWord -> [PWordLog (Statement Expanded [Grapheme])] Source #
Apply SoundChanges
to a word, returning an PWordLog
for each possible result.
applyChangesWithChanges :: SoundChanges Expanded [Grapheme] -> PWord -> [(PWord, Bool)] Source #
Apply SoundChanges
to a word returning the final results, as
well as a boolean value indicating whether the word should be
highlighted in a UI due to changes from its initial value. (Note
that this accounts for highlightChanges
values.)
Logs the evolution of a PWord
as various actions are applied to
it. The actions (usually Statement
s) are of type r
.
PWordLog | |
|
Instances
Functor PWordLog Source # | |
Generic (PWordLog r) Source # | |
Show r => Show (PWordLog r) Source # | |
NFData r => NFData (PWordLog r) Source # | |
Defined in Brassica.SoundChange.Apply.Internal | |
type Rep (PWordLog r) Source # | |
Defined in Brassica.SoundChange.Apply.Internal type Rep (PWordLog r) = D1 ('MetaData "PWordLog" "Brassica.SoundChange.Apply.Internal" "brassica-0.2.0-6DYGqWgsRcQ5pGt1m6P3TU" 'False) (C1 ('MetaCons "PWordLog" 'PrefixI 'True) (S1 ('MetaSel ('Just "initialWord") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PWord) :*: S1 ('MetaSel ('Just "derivations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(PWord, r)]))) |
reportAsText :: (r -> String) -> PWordLog r -> String Source #
Render a single PWordLog
to plain text. For instance, this log:
PWordLog { initialWord = ["t", "a", "r", "a"] , derivations = [ (["t", "a", "zh", "a"], "r / zh") , (["t", "a", "zh"], "V / / _ #") ] }
Would render as:
tara -> tazha (r / zh) -> tazh (V / / _ #)
reportAsHtmlRows :: (r -> String) -> PWordLog r -> String Source #
Render a single PWordLog
to 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 an HTML table as something like the following:
tara | → | tazha | (r / zh) |
→ | tazh | (V _ #) |