- type Lang = ByteString
- type Locale = ByteString
- data AUSResponse
- data LangsStatus
- langs :: Maybe Locale -> Int -> IO (Either ByteString AUSResponse)
- accentuate :: Lang -> Maybe Locale -> Text -> IO (Either ByteString AUSResponse)
- feedback :: Lang -> Maybe Locale -> Text -> IO (Either ByteString AUSResponse)
Documentation
This package implements the Accentuate.us (http://accentuate.us/) API as it is described at http://accentuate.us/api.
The documentation's examples assume the following conditions:
{-# LANGUAGE OverloadedStrings #-} import Text.AccentuateUs import Control.Monad (liftM) import Data.Either (either) import Data.Maybe (fromMaybe) import Data.Text.Encoding (decodeUtf8) import qualified Data.Text.IO as TIO
= ByteString | An ISO-639 code. |
= ByteString | An ISO-639 code. |
data LangsStatus Source
Represents languages response status
langs :: Maybe Locale -> Int -> IO (Either ByteString AUSResponse)Source
Get langs and their localized names. E.g.,
getEnglishName langs = fromMaybe "Not Found" $ "en" `lookup` langs TIO.putStrLn =<< liftM (either decodeUtf8 (getEnglishName . languages)) (langs (Just "ga") 0)
The above example will get the localized name for English (ISO-639: en) for localized into Irish (ISO-639: ga).
accentuate :: Lang -> Maybe Locale -> Text -> IO (Either ByteString AUSResponse)Source
For a given language, and optionally a locale, accentuates text. This function is that which does the heavy lifting, restoring diacritics (special characters) to otherwise plain text. E.g.,
TIO.putStrLn =<< liftM (either decodeUtf8 text) (accentuate "vie" (Just "en") "My tu bo ke hoach la chan ten lua")
The above example accentuates the input text (My tu...) in Vietnamese with an English localization of error responses.
feedback :: Lang -> Maybe Locale -> Text -> IO (Either ByteString AUSResponse)Source
Submits corrected text as feedback to Accentuate.us. It is helpful for all users if developers make good use of this function as it helps improve the Accentuate.us language models by retraining them.
feedback "ht" (Just "en") "Bon, la f sa apre demen pito, l la w mwen andy."
This example submits the *correct* input text (all diacritics in their proper places) to the Accentuate.us servers to be queued for language model retraining.