Copyright | (c) Noah Goodman 2018 |
---|---|
License | BSD3 |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
This is a library for interpresting the parsed Carnegie Mellon University Pronouncing
Dictionary. It is modelled after Allison Parrish's python library, pronouncing
.
- type CMUdict = Map Text [Text]
- type UsesBin = Bool
- type DictComp = Reader CMUdict
- type EntryWord = Text
- type Phones = Text
- type Stress = Text
- initDict :: Maybe FilePath -> UsesBin -> IO CMUdict
- stdDict :: IO CMUdict
- runPronounce :: DictComp a -> CMUdict -> a
- phonesForEntry :: EntryWord -> DictComp [Phones]
- stressesForEntry :: EntryWord -> DictComp [Stress]
- stresses :: Phones -> Stress
- syllableCount :: Phones -> Int
- searchDictBy :: (Phones -> Bool) -> DictComp CMUdict
- search :: Phones -> DictComp [EntryWord]
- searchStresses :: Stress -> DictComp [EntryWord]
- rhymingPart :: Phones -> Phones
- rhymes :: EntryWord -> DictComp [EntryWord]
- dictAppend :: (Applicative f, Monoid a) => DictComp (f a) -> DictComp (f a) -> DictComp (f a)
- (<||>) :: (Applicative f, Monoid a) => DictComp (f a) -> DictComp (f a) -> DictComp (f a)
- liftD :: Functor f => (a -> b) -> DictComp (f a) -> DictComp (f b)
Datatypes
type CMUdict = Map Text [Text] Source #
A Map from Entries to lists of possible pronunciations, serving as our representation of the CMU Pronouncing Dictionary
A type used to represent the option of decoding the dictionary from a binary file or parsing it from text
type DictComp = Reader CMUdict Source #
We are using the Reader monad to perform computations in the context of the CMU dictionary without having to pass it in or worry about initializing every time
Using Text.Pronounce
initDict :: Maybe FilePath -> UsesBin -> IO CMUdict Source #
Initializes the cmu pronunctiation dictionary into our program, given an optional file name of the dictionary
runPronounce :: DictComp a -> CMUdict -> a Source #
Get the value from a series of Dictionary Computations by supplying the
dictionary to the computation. This is just runReader
.
Basic Functions
phonesForEntry :: EntryWord -> DictComp [Phones] Source #
Look up the pronunciation (list of possible phones) of a word in the dictionary
stressesForEntry :: EntryWord -> DictComp [Stress] Source #
Gives the stress pattern for a given word in the dictionary
syllableCount :: Phones -> Int Source #
Gives the syllable count of a given pronunciation
Searching the Dictionary
searchDictBy :: (Phones -> Bool) -> DictComp CMUdict Source #
Initializes a dictionary computation based on a selector function that
operates on an individual phones. It returns a DictComp
containing a CMUdict
of all the entries that have at least one value satisfying the predicate.
search :: Phones -> DictComp [EntryWord] Source #
Given a sequence of phones, find all words that contain that sequence of phones
searchStresses :: Stress -> DictComp [EntryWord] Source #
Given a stress pattern, find all words that satisfy that pattern
Rhyming
rhymingPart :: Phones -> Phones Source #
Finds the rhyming part of the given phones.
rhymes :: EntryWord -> DictComp [EntryWord] Source #
Given a word, finds all other words that rhyme with it
Some Helper Functions
dictAppend :: (Applicative f, Monoid a) => DictComp (f a) -> DictComp (f a) -> DictComp (f a) Source #
Useful for nondeterministically combining several dictionary computations.
Generally, one would call foldr1 (<||>)
to get all the possible results of
mapping a DictComp
over a line of text (multiple words).
(<||>) :: (Applicative f, Monoid a) => DictComp (f a) -> DictComp (f a) -> DictComp (f a) infixl 3 Source #
Useful for nondeterministically combining several dictionary computations.
Generally, one would call foldr1 (<||>)
to get all the possible results of
mapping a DictComp
over a line of text (multiple words).