brassica-0.0.3: Featureful sound change applier
Safe HaskellSafe-Inferred
LanguageHaskell2010

Brassica.SoundChange.Apply

Synopsis

Sound change application

applyRuleStr :: Rule -> PWord -> [PWord] Source #

Apply a single Rule to a word.

Note: duplicate outputs from this function are removed. To keep duplicates, use the lower-level internal function applyRule directly.

applyStatementStr :: Statement -> 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 -> PWord -> [PWord] Source #

Apply a set of SoundChanges to a word.

Logging

applyChangesWithLogs :: SoundChanges -> PWord -> [PWordLog Statement] Source #

Apply SoundChanges to a word, returning an PWordLog for each possible result.

applyChangesWithChanges :: SoundChanges -> 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.)

data PWordLog r Source #

Logs the evolution of a PWord as various actions are applied to it. The actions (usually Statements) are of type r.

Constructors

PWordLog 

Fields

  • initialWord :: PWord

    The initial word, before any actions have been applied

  • derivations :: [(PWord, r)]

    The state of the word after each action r, stored alongside the action which was applied at each point

Instances

Instances details
Functor PWordLog Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal

Methods

fmap :: (a -> b) -> PWordLog a -> PWordLog b #

(<$) :: a -> PWordLog b -> PWordLog a #

Generic (PWordLog r) Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal

Associated Types

type Rep (PWordLog r) :: Type -> Type #

Methods

from :: PWordLog r -> Rep (PWordLog r) x #

to :: Rep (PWordLog r) x -> PWordLog r #

Show r => Show (PWordLog r) Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal

Methods

showsPrec :: Int -> PWordLog r -> ShowS #

show :: PWordLog r -> String #

showList :: [PWordLog r] -> ShowS #

NFData r => NFData (PWordLog r) Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal

Methods

rnf :: PWordLog r -> () #

type Rep (PWordLog r) Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal

type Rep (PWordLog r) = D1 ('MetaData "PWordLog" "Brassica.SoundChange.Apply.Internal" "brassica-0.0.3-KZvvTDsX9bO8hsF2GF232f" '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>&rarr;</td><td>tazha</td><td>(r / zh)</td></tr><tr><td></td><td>&rarr;</td><td>tazh</td><td>(V / / _ #)</td></tr>"

Which might be displayed in an HTML table as something like the following:

taratazha(r / zh)
tazh(V _ #)