Safe Haskell | None |
---|---|
Language | Haskell98 |
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
- data Catalog
- loadCatalog :: FilePath -> IO Catalog
- lookup :: ByteString -> Catalog -> Maybe [Text]
- gettext :: Catalog -> ByteString -> Text
- cgettext :: Catalog -> ByteString -> ByteString -> Text
- ngettext :: Catalog -> ByteString -> ByteString -> Int -> Text
- cngettext :: Catalog -> ByteString -> ByteString -> ByteString -> Int -> Text
- ngettext' :: Catalog -> ByteString -> Int -> Text
- assocs :: Catalog -> [(ByteString, [Text])]
- getHeaders :: Catalog -> Maybe Headers
- getPluralDefinition :: Catalog -> Maybe (Int, Expr)
- choosePluralForm :: Catalog -> Int -> Int
- parseGmo :: Get GmoFile
- unpackGmoFile :: GmoFile -> Catalog
Data structures
This structure describes data in Gettext's .mo/.gmo
file in ready-to-use format.
Loading and using translations
:: Catalog | |
-> ByteString | Original string |
-> Text |
Translate a string.
Original message must be defined in po
file in msgid
line.
:: Catalog | |
-> ByteString | Message context ( |
-> ByteString | Original string |
-> Text |
Translate a string within specific context.
:: 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.
:: Catalog | |
-> ByteString | Message context ( |
-> 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.
:: 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]
.
Utilities for plural forms
getHeaders :: Catalog -> Maybe Headers Source #
Obtain headers of the catalog. Headers are defined as a translation for empty string.
Utilities for custom parsers implementation
unpackGmoFile :: GmoFile -> Catalog Source #
Prepare the data parsed from file for lookups.