microsoft-translator-0.1.1: Bindings to the Microsoft Translator API

Safe HaskellNone
LanguageHaskell2010

Microsoft.Translator

Contents

Synopsis

Basic Types

data AuthToken Source #

The JSON Web Token issued by MS Microsoft.Translator token service. Consists of wrapped text. Valid for ten minutes.

Instances

Show AuthToken Source # 
Generic AuthToken Source # 

Associated Types

type Rep AuthToken :: * -> * #

ToHttpApiData AuthToken Source # 
type Rep AuthToken Source # 
type Rep AuthToken = D1 * (MetaData "AuthToken" "Microsoft.Translator.API.Auth" "microsoft-translator-0.1.1-SJQ3sfTzucJoM4Lfl3DNf" True) (C1 * (MetaCons "AuthToken" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data AuthData Source #

An AuthToken together with the time it was recieved. Each token is valid for 10 minutes.

Constructors

AuthData 

data TransData Source #

The data to hold onto for making translation requests. Includes your SubscriptionKey, an AuthData and an HTTPS Manager.

newtype ArrayResponse Source #

Constructors

ArrayResponse 

Instances

Show ArrayResponse Source # 
Generic ArrayResponse Source # 

Associated Types

type Rep ArrayResponse :: * -> * #

type Rep ArrayResponse Source # 
type Rep ArrayResponse = D1 * (MetaData "ArrayResponse" "Microsoft.Translator.API" "microsoft-translator-0.1.1-SJQ3sfTzucJoM4Lfl3DNf" True) (C1 * (MetaCons "ArrayResponse" PrefixI True) (S1 * (MetaSel (Just Symbol "getArrayResponse") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TransItem])))

data TransItem Source #

Constructors

TransItem 

Instances

Show TransItem Source # 
Generic TransItem Source # 

Associated Types

type Rep TransItem :: * -> * #

type Rep TransItem Source # 
type Rep TransItem = D1 * (MetaData "TransItem" "Microsoft.Translator.API" "microsoft-translator-0.1.1-SJQ3sfTzucJoM4Lfl3DNf" False) (C1 * (MetaCons "TransItem" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "transText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "originalBreaks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Int])) (S1 * (MetaSel (Just Symbol "translatedBreaks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Int])))))

data Sentence Source #

An original/translated sentence pair.

Constructors

Sentence 

Fields

Instances

Eq Sentence Source # 
Show Sentence Source # 
Generic Sentence Source # 

Associated Types

type Rep Sentence :: * -> * #

Methods

from :: Sentence -> Rep Sentence x #

to :: Rep Sentence x -> Sentence #

type Rep Sentence Source # 
type Rep Sentence = D1 * (MetaData "Sentence" "Microsoft.Translator" "microsoft-translator-0.1.1-SJQ3sfTzucJoM4Lfl3DNf" False) (C1 * (MetaCons "Sentence" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "fromText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "toText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))

API functions

Authorization

lookupSubKey :: ExceptT TranslatorException IO SubscriptionKey Source #

Retrieve your subscription key from the TRANSLATOR_SUBSCRIPTION_KEY environment variable.

issueToken :: Manager -> SubscriptionKey -> IO (Either TranslatorException AuthToken) Source #

Retrieve a token from the API. It will be valid for 10 minutes.

issueAuth :: Manager -> SubscriptionKey -> ExceptT TranslatorException IO AuthData Source #

Retrieve a token, via issueToken, and save it together with a timestamp.

initTransData :: SubscriptionKey -> ExceptT TranslatorException IO TransData Source #

Retrieve an AuthData token and hold on to the new HTTPS manager.

initTransDataWith :: SubscriptionKey -> Manager -> ExceptT TranslatorException IO TransData Source #

Retrieve an AuthData token and hold on to the HTTPS manager. For when you want to supply a particular manager. Otherwise use initTransData.

checkAuth :: TransData -> ExceptT TranslatorException IO AuthData Source #

If a token contained in a TransData is expired or about to expire, refresh it.

keepFreshAuth :: SubscriptionKey -> ExceptT TranslatorException IO TransData Source #

Create a TransData with a new auth token and fork a thread to refresh it every 9 minutes. This is mostly a quick-and-dirty function for demo purposes and one-off projects. You'll want to roll something more robust for production applications.

Translation

ExceptT variants

translateArray :: TransData -> Language -> Language -> [Text] -> ExceptT TranslatorException IO ArrayResponse Source #

Translate a text array. The ArrayResponse you get back includes sentence break information.

translateArrayText :: TransData -> Language -> Language -> [Text] -> ExceptT TranslatorException IO [Text] Source #

Translate a text array, and just return the list of texts.

translateArraySentences :: TransData -> Language -> Language -> [Text] -> ExceptT TranslatorException IO [[Sentence]] Source #

Translate a text array, and split all the texts into constituent sentences, paired with the originals.

IO variants

lookupSubKeyIO :: IO (Either TranslatorException SubscriptionKey) Source #

Retrieve your subscription key from the TRANSLATOR_SUBSCRIPTION_KEY environment variable.

issueAuthIO :: Manager -> SubscriptionKey -> IO (Either TranslatorException AuthData) Source #

Retrieve a token, via issueToken, and save it together with a timestamp.

initTransDataIO :: SubscriptionKey -> IO (Either TranslatorException TransData) Source #

Retrieve an AuthData token and start up an HTTPS manager.

checkAuthIO :: TransData -> IO (Either TranslatorException AuthData) Source #

If a token contained in a TransData is expired or about to expire, refresh it.

translateArrayTextIO :: TransData -> Language -> Language -> [Text] -> IO (Either TranslatorException [Text]) Source #

Translate a text array, and just return the list of texts.

translateArraySentencesIO :: TransData -> Language -> Language -> [Text] -> IO (Either TranslatorException [[Sentence]]) Source #

Translate a text array, and split all the texts into constituent sentences paired with the originals.

Minimalistic variants

simpleTranslate :: SubscriptionKey -> Manager -> Maybe Language -> Language -> Text -> IO (Either TranslatorException Text) Source #

Simplest possible translation function. Always needs to make a request for the JWT token first.

basicTranslate :: Manager -> AuthToken -> Maybe Language -> Language -> Text -> IO (Either TranslatorException Text) Source #

Most basic possible text translation function. For typical use-cases it will be much more convenient to use functions from the Microsoft.Translator module, namely translateIO. See the README example.

basicTranslateArray :: Manager -> AuthToken -> Language -> Language -> [Text] -> IO (Either TranslatorException ArrayResponse) Source #

Most basic possible text list translation function. For typical use-cases it will be much more convenient to use functions from the Microsoft.Translator module, namely translateArrayIO. See the README example.

Pure functions

mkSentences :: [Text] -> ArrayResponse -> [[Sentence]] Source #

Take the original texts and the ArrayResponse object, and apply the sentence break information to pair each sentence in the request to the translated text.