pronounce-1.2.0.0: A library for interfacing with the CMU Pronouncing Dictionary

Copyright(c) Noah Goodman 2018
LicenseBSD3
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Text.Pronounce

Contents

Description

This is a library for interpreting the parsed Carnegie Mellon University Pronouncing Dictionary. It is modelled after Allison Parrish's python library, pronouncing.

Synopsis

Fundamentals

Basic Datatypes

type CMUdict = Map Entry [Phones] Source #

A Map from Entrys to lists of possible pronunciations (Phones), serving as our representation of the CMU Pronouncing Dictionary

type Entry = Text Source #

Represents an entry word in the cmu pronouncing dictionary (simply an alias for Text to improve type specificity and readability

type Phones = [Text] Source #

Represents a string containing the phonetic breakdown of a word, in a similar manner to the EntryWord type

type Stress = [Int] Source #

Type alias for a stress pattern, which is a list of integers 0-2 indicating stress.

  • 0 -> unstressed
  • 1 -> primary stress
  • 2 -> secondary stress

The Dictionary Computation Monad

type DictComp = ReaderT CMUdict [] Source #

We are using the List monad inside the ReaderT monad to perform nondeterministic computations (due to the possibility of multiple Phones patterns per Entry) in the context of the CMU dictionary without having to pass it as an argument to every function.

dictcomp :: (CMUdict -> [a]) -> DictComp a Source #

Contruct a Dictionary Computation based on a selector function on the CMUdict that returns a list of possible results. This is just a synonym for the ReaderT constructor.

runPronounce :: DictComp a -> CMUdict -> [a] Source #

Get the possible values resulting from a series of Dictionary Computations by supplying the dictionary to the computation. This is just runReaderT.

Using Text.Pronounce

initDict :: Maybe FilePath -> DictSource -> IO CMUdict Source #

Initializes the cmu pronunctiation dictionary into our program, given an optional file name of the dictionary

stdDict :: IO CMUdict Source #

Default settings for initDict

data DictSource Source #

Options for the initial source of the CMUDict. Currently, we can either parse from plaintext file or load preprocessed binary

Basic Functions

phonesForEntry :: Entry -> DictComp Phones Source #

Look up the pronunciation (list of possible phones) of a word in the dictionary

stressesForEntry :: Entry -> DictComp Stress Source #

Gives the stress pattern for a given word in the dictionary

noStress :: Phones -> Phones Source #

Strips the stress-indicating numbers off of a phones

stresses :: Phones -> Stress Source #

Isolates the stress pattern from a sequence of phones

syllableCount :: Phones -> Int Source #

Gives the syllable count of a given pronunciation

Searching the Dictionary

Field Selectors

entries :: DictComp Entry Source #

A Dictionary Computation that returns a list of all the entry words in the CMUdict

phoneses :: DictComp [Phones] Source #

A Dictionary Computation that returns a list of all the lists of phones in the CMUdict

pairs :: DictComp (Entry, [Phones]) Source #

A Dictionary Computation that returns a list of all the (key,value) pairs in the CMUdict@

Filtering Searches

class DictField a Source #

A class that provides a generalized function filterDict for filtering the CMUdict based on a choice of different "fields"

Minimal complete definition

filterDict

Instances
DictField Phones Source # 
Instance details

Defined in Text.Pronounce

DictField Entry Source # 
Instance details

Defined in Text.Pronounce

Methods

filterDict :: (Entry -> Bool) -> CMUdict -> CMUdict Source #

DictField [Phones] Source # 
Instance details

Defined in Text.Pronounce

Methods

filterDict :: ([Phones] -> Bool) -> CMUdict -> CMUdict Source #

DictField (Entry, [Phones]) Source # 
Instance details

Defined in Text.Pronounce

Methods

filterDict :: ((Entry, [Phones]) -> Bool) -> CMUdict -> CMUdict Source #

DictField (Entry, Phones) Source # 
Instance details

Defined in Text.Pronounce

Methods

filterDict :: ((Entry, Phones) -> Bool) -> CMUdict -> CMUdict Source #

filterComp :: DictField a => (a -> Bool) -> DictComp b -> DictComp b Source #

Filter a the results of a DictComp, taking only those whose corresponing entries conform to the selector function

Specific Searches

search :: Phones -> DictComp Entry Source #

Given a sequence of phones, find all words that contain that sequence of phones

searchStresses :: Stress -> DictComp Entry 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, where the rhyming part is defined as everything in a word after and including the last stressed or semistressed phone. Note that this is merely one interpretation of what constitutes a rhyme. There exist both stricter and looser definitions that may be suited to different purposes.

rhymesUsing :: (Phones -> Phones -> Bool) -> Entry -> DictComp Entry Source #

Given a function that tells whether or not two sets of phones rhyme, and an entry, find all words that rhyme with that entry according to the provided definition of a rhyme

rhymes :: Entry -> DictComp Entry Source #

Given a word, finds all other words that rhyme with it, using the default rhymingPart definition