brassica-1.0.0: Featureful sound change applier
CopyrightSee LICENSE file
LicenseBSD3
MaintainerBrad Neimann
Safe HaskellSafe-Inferred
LanguageHaskell2010

Brassica.SoundChange.Apply

Description

This module contains functions to apply one or more expanded sound changes to words.

The most important function is applyChanges, which applies a set of SoundChanges to an input word. It returns a log of all sound changes and other actions which were applied to produce intermediate forms and the final result. The results can be summarised using the functions in Reporting results.

Synopsis

Applying single rules

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.

Applying multiple sound changes

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.

data Log r Source #

Logs the evolution of a word as it undergoes sound changes and other actions.

Constructors

Log 

Fields

  • inputWord :: PWord

    The input word, before any actions have been applied

  • derivations :: [LogItem r]

    All actions which were applied, with the state of the word at each point

Instances

Instances details
Functor Log Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal

Methods

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

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

Generic (Log r) Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal

Associated Types

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

Methods

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

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

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

Defined in Brassica.SoundChange.Apply.Internal

Methods

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

show :: Log r -> String #

showList :: [Log r] -> ShowS #

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

Defined in Brassica.SoundChange.Apply.Internal

Methods

rnf :: Log r -> () #

type Rep (Log r) Source # 
Instance details

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])))

data LogItem r Source #

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 Nothing if the wordwas deleted

ReportWord PWord

Corresponds to ReportS, giving the intermediate form to report

Instances

Instances details
Functor LogItem Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal

Methods

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

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

Generic (LogItem r) Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal

Associated Types

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

Methods

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

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

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

Defined in Brassica.SoundChange.Apply.Internal

Methods

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

show :: LogItem r -> String #

showList :: [LogItem r] -> ShowS #

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

Defined in Brassica.SoundChange.Apply.Internal

Methods

rnf :: LogItem r -> () #

type Rep (LogItem r) Source # 
Instance details

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)))

Reporting results

getOutput :: Log r -> Maybe PWord Source #

Returns the final output from a sound change log.

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.

reportAsText Source #

Arguments

:: (r -> String)

Specifies how to pretty-print actions as text

-> Log r 
-> String 

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 reportAsText id as:

tara
  -> tazha  (r / zh)
  -> tazh   (V / / _ #)

reportAsHtmlRows Source #

Arguments

:: (r -> String)

Specifies how to pretty-print actions as text

-> Log r 
-> String 

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>&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 a browser as follows:

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