haskell-gettext-0.1.2.0: GetText runtime library implementation in pure Haskell

Safe HaskellSafe
LanguageHaskell98

Data.Gettext

Contents

Description

This is the main module of haskell-gettext package. For most cases, it is enough to import only this module. Other modules of the package might be useful for other libraries working with gettext's files.

Simple example of usage of this module is:

{-# LANGUAGE OverloadedStrings #-}
module Main where

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

import Data.Gettext

main :: IO ()
main = do
  catalog <- loadCatalog "locale/ru/messages.mo"
  TLIO.putStrLn $ gettext catalog "Simple translated message"
  let n = 78
  let template = ngettext catalog "There is %d file" "There are %d files" n
  printf (T.unpack template) n
Synopsis

Data structures

data Catalog Source #

This structure describes data in Gettext's .mo/.gmo file in ready-to-use format.

Instances
Show Catalog Source # 
Instance details

Defined in Data.Gettext

Loading and using translations

loadCatalog :: FilePath -> IO Catalog Source #

Load gettext file

lookup :: ByteString -> Catalog -> Maybe [Text] Source #

Look up for string translation

gettext Source #

Arguments

:: Catalog 
-> ByteString

Original string

-> Text 

Translate a string. Original message must be defined in po file in msgid line.

cgettext Source #

Arguments

:: Catalog 
-> ByteString

Message context (msgctxt line in po file)

-> ByteString

Original string

-> Text 

Translate a string within specific context.

ngettext Source #

Arguments

:: Catalog 
-> ByteString

Single form in original language

-> ByteString

Plural form in original language

-> Int

Number

-> Text 

Translate a string and select correct plural form. Original single form must be defined in po file in msgid line. Original plural form must be defined in po file in msgid_plural line.

cngettext Source #

Arguments

:: Catalog 
-> ByteString

Message context (msgctxt line in po file)

-> ByteString

Single form in original language

-> ByteString

Plural form in original language

-> Int

Number

-> Text 

Translate a string and select correct plural form, within specific context Original single form must be defined in po file in msgid line. Original plural form must be defined in po file in msgid_plural line.

ngettext' Source #

Arguments

:: Catalog 
-> ByteString

Single form in original language

-> Int

Number

-> Text 

Variant of ngettext for case when for some reason there is only msgid defined in po file, and no msgid_plural, but there are some msgstr[n].

context Source #

Arguments

:: Catalog 
-> ByteString

Context

-> Catalog 

Get sub-catalog for specific context

assocs :: Catalog -> [(ByteString, [Text])] Source #

Get all translation pairs

Utilities for plural forms

getHeaders :: Catalog -> Maybe Headers Source #

Obtain headers of the catalog. Headers are defined as a translation for empty string.

getPluralDefinition :: Catalog -> Maybe (Int, Expr) Source #

Get plural forms selection definition.

choosePluralForm :: Catalog -> Int -> Int Source #

Choose plural form index by number

Utilities for custom parsers implementation

parseGmo :: Get GmoFile Source #

Data.Binary parser for GmoFile structure

unpackGmoFile :: GmoFile -> Catalog Source #

Prepare the data parsed from file for lookups.