-- | -- Module : EspeakNG_IPA -- Copyright : (c) OleksandrZhabenko 2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Is intended to use internally \"espeak-ng\" or \"espeak\" executable to produce the IPA phonemes output -- of the given 'String'. -- The prerequisite is installed espeak-ng or espeak executable in the path that is in the PATH -- environment variable. module EspeakNG_IPA where import System.Process (readProcessWithExitCode) import EndOfExe (showE) import System.Exit (ExitCode(..)) import Data.Maybe (fromJust) {-| Given a language 'String' supported by the espeak-ng or espeak (which one is installed properly, the espeak-ng is a preferred one) and the needed text returns the IPA representation. Is just some wrapper around the espeak functionality. -} espeakNG_IPA :: String -> String -> IO String espeakNG_IPA = espeakNG_IPA_G id {-# INLINE espeakNG_IPA #-} {-| Given a language 'String' supported by the espeak-ng or espeak (which one is installed properly, the espeak-ng is a preferred one) and the needed text returns the IPA representation filtered of the \'ˈ\' and \'ː\' characters. Is just some wrapper around the espeak functionality. -} espeakNG_IPA1 :: String -> String -> IO String espeakNG_IPA1 = espeakNG_IPA_G (filter (\x -> x /= 'ˈ' && x /= 'ː')) {-# INLINE espeakNG_IPA1 #-} {-| Given a language 'String' supported by the espeak-ng or espeak (which one is installed properly, the espeak-ng is a preferred one) and the needed text prints the IPA representation. Is just some wrapper around the espeak functionality. -} espeakNG_IPA_ :: String -> String -> IO () espeakNG_IPA_ = espeakNG_IPA_G_ id {-# INLINE espeakNG_IPA_ #-} {-| Given a language 'String' supported by the espeak-ng or espeak (which one is installed properly, the espeak-ng is a preferred one) and the needed text prints the IPA representation filtered of the \'ˈ\' and \'ː\' characters. Is just some wrapper around the espeak functionality. -} espeakNG_IPA1_ :: String -> String -> IO () espeakNG_IPA1_ = espeakNG_IPA_G_ (filter (\x -> x /= 'ˈ' && x /= 'ː')) {-# INLINE espeakNG_IPA1_ #-} {-| Given a conversion function that is applied to the resulting 'String' before it is returned, a language 'String' supported by the espeak-ng or espeak (which one is installed properly, the espeak-ng is a preferred one) and the needed text returns the IPA representation. Is just some wrapper around the espeak functionality. -} espeakNG_IPA_G :: (String -> String) -> String -> String -> IO String espeakNG_IPA_G g voice xs = case showE "espeak-ng" of Just path -> readProcessWithExitCode path ("-xq":"--ipa":"-v":[voice]) xs >>= \(hcode,hout,herr) -> case hcode of ExitSuccess -> return (g . unwords . lines $ hout) _ -> error ("EspeakNG_IPA.espeakNG_IPA_G: " ++ show herr) _ -> case showE "espeak" of Just path2 -> readProcessWithExitCode path2 ("-xq":"--ipa":"-v":[voice]) xs >>= \(hcode,hout,herr) -> case hcode of ExitSuccess -> return (g . unwords . lines $ hout) _ -> error ("EspeakNG_IPA.espeakNG_IPA_G: " ++ show herr) _ -> error ("EspeakNG_IPA.espeakNG_IPA_G: No espeak or espeak-ng executable is installed in the PATH directories. ") {-| Given a conversion function that is applied to the resulting 'String' before it is printed, a language 'String' supported by the espeak-ng or espeak (which one is installed properly, the espeak-ng is a preferred one) and the needed text prints the IPA representation. Is just some wrapper around the espeak functionality. -} espeakNG_IPA_G_ :: (String -> String) -> String -> String -> IO () espeakNG_IPA_G_ g voice xs = case showE "espeak-ng" of Just path -> readProcessWithExitCode path ("-xq":"--ipa":"-v":[voice]) xs >>= \(hcode,hout,herr) -> case hcode of ExitSuccess -> putStrLn (g . unwords . lines $ hout) _ -> error ("EspeakNG_IPA.espeakNG_IPA_G_: " ++ show herr) _ -> case showE "espeak" of Just path2 -> readProcessWithExitCode path2 ("-xq":"--ipa":"-v":[voice]) xs >>= \(hcode,hout,herr) -> case hcode of ExitSuccess -> putStrLn (g . unwords . lines $ hout) _ -> error ("EspeakNG_IPA.espeakNG_IPA_G_: " ++ show herr) _ -> error ("EspeakNG_IPA.espeakNG_IPA_G_: No espeak or espeak-ng executable is installed in the PATH directories. ")