localize-0.2.0.0: GNU Gettext-based messages localization library

Safe HaskellNone
LanguageHaskell2010

Text.Localize

Contents

Description

This is the main module of the localize package. It contains definitions of general use and reexport generally required internal modules.

Synopsis

Documentation

This is the main module of the localize package. In most cases, you have to import only this module. In specific cases, you may also want to import Text.Localize.IO or Text.Localize.State.

All functions exported by localize package work with any instance of the Localized type class. There are two simple examples of this type class implementation provided in separate modules (IO and State); however, in complex applications it may be more convinient to implement Localized instance for the monadic stack you already have.

Example of usage is:

import qualified Data.Text as T
import qualified Data.Text.Lazy.IO as TLIO
import Text.Localize

newtype MyMonad a = MyMonad {unMyMonad :: ... }
  deriving (Monad)

instance Localized MyMonad where
  ...

runMyMonad :: Translations -> MyMonad a -> IO a
runMyMonad = ...

hello :: T.Text -> MyMonad ()
hello name = do
  liftIO $ TLIO.putStrLn =<< __ "Your name: "
  liftIO $ hFlush stdout
  name <- liftIO $ TLIO.getLine
  greeting <- __f "Hello, {}!" (Single name)
  liftIO $ TLIO.putStrLn greeting

main :: IO ()
main = do
  translations <- locateTranslations $ linuxLocation "hello"
  runMyMonad translations hello

See also working examples under examples/ directory.

__ :: Localized m => TranslationSource -> m Text Source #

Short alias for translate.

__n :: (Localized m, VarContainer c) => TranslationSource -> TranslationSource -> Int -> c -> m Text Source #

Short alias for translateNFormat.

__f :: (Localized m, VarContainer c) => TranslationSource -> c -> m Text Source #

Short alias for translateFormat.

Basic functions

translate :: Localized m => TranslationSource -> m Text Source #

Translate a string.

translateN Source #

Arguments

:: Localized m 
=> TranslationSource

Single form in original language

-> TranslationSource

Plural form in original language

-> Int

Number

-> m Text 

Translate a string, taking plural forms into account.

translateNFormat Source #

Arguments

:: (Localized m, VarContainer vars) 
=> TranslationSource

Single form of formatting string in original language

-> TranslationSource

Plural form of formatting string in original language

-> Int

Number

-> vars

Substitution variables

-> m Text 

Translate a string, taking plural forms into account, and substitute variables into it. Data.Text.Format.Heavy.format syntax is used.

lookup :: Translations -> LanguageId -> TranslationSource -> Text Source #

Look up for translation. Returns source string if translation not found.

withTranslation Source #

Arguments

:: Localized m 
=> (b -> r)

Function to be executed if there is no translation for current language loaded.

-> (Catalog -> Maybe Context -> b -> r)

Function to be executed on current catalog.

-> b -> m r

Function lifted into Localized monad.

Execute function depending on current translation catalog and context.

Reexports