{-# LANGUAGE OverloadedStrings #-}
module Text.Pronounce (
CMUdict
, UsesBin
, DictComp
, EntryWord
, Phones
, Stress
, initDict
, stdDict
, runPronounce
, phonesForEntry
, stressesForEntry
, stresses
, syllableCount
, searchDictBy
, search
, searchStresses
, rhymingPart
, rhymes
, dictAppend
, (<||>)
, liftD
) where
import Text.Pronounce.ParseDict
import Control.Monad.Reader
import Data.Char (isDigit)
import qualified Data.Text as T
import qualified Data.Map as Map
type DictComp = Reader CMUdict
type EntryWord = T.Text
type Phones = T.Text
type Stress = T.Text
phonesForEntry :: EntryWord -> DictComp [Phones]
phonesForEntry = fmap concat . asks . Map.lookup
stressesForEntry :: EntryWord -> DictComp [Stress]
stressesForEntry = liftD stresses . phonesForEntry
stresses :: Phones -> Stress
stresses = T.filter isDigit
syllableCount :: Phones -> Int
syllableCount = T.length . stresses
rhymingPart :: Phones -> Phones
rhymingPart = T.unwords
. reverse
. takeWhileInc (not . (`T.isInfixOf` "12") . T.singleton . T.last)
. reverse
. T.words
where takeWhileInc _ [] = []
takeWhileInc p (x:xs) = x : if p x then takeWhileInc p xs else []
searchDictBy :: (Phones -> Bool) -> DictComp CMUdict
searchDictBy = asks . Map.filter . any
search :: Phones -> DictComp [EntryWord]
search = fmap Map.keys . searchDictBy . T.isInfixOf
searchStresses :: Stress -> DictComp [EntryWord]
searchStresses = fmap Map.keys . searchDictBy . (==) . stresses
rhymes :: EntryWord -> DictComp [EntryWord]
rhymes word = (\entryPart -> fmap (filter (/= word) . Map.keys)
. return
. Map.filter (or . ((==) <$> entryPart <*>) . fmap rhymingPart)
=<< ask
) =<< (liftD rhymingPart . phonesForEntry $ word)
dictAppend, (<||>) :: (Applicative f, Monoid a) => DictComp (f a) -> DictComp (f a) -> DictComp (f a)
dictAppend = ((<*>) . fmap ((<*>) . fmap mappend))
infixl 3 <||>
(<||>) = dictAppend
liftD :: (Functor f) => (a -> b) -> DictComp (f a) -> DictComp (f b)
liftD = fmap . fmap
runPronounce :: DictComp a -> CMUdict -> a
runPronounce = runReader