bcp47-0.1.0.0: Language tags as specified by BCP 47

Safe HaskellNone
LanguageHaskell2010

Data.BCP47

Contents

Description

Human beings on our planet have, past and present, used a number of languages. There are many reasons why one would want to identify the language used when presenting or requesting information.

The language of an information item or a user's language preferences often need to be identified so that appropriate processing can be applied. For example, the user's language preferences in a Web browser can be used to select Web pages appropriately. Language information can also be used to select among tools (such as dictionaries) to assist in the processing or understanding of content in different languages. Knowledge about the particular language used by some piece of information content might be useful or even required by some types of processing, for example, spell-checking, computer-synthesized speech, Braille transcription, or high-quality print renderings.

- https://tools.ietf.org/html/bcp47

Synopsis

Documentation

data BCP47 Source #

A language tag

Language tags are used to help identify languages, whether spoken, written, signed, or otherwise signaled, for the purpose of communication. This includes constructed and artificial languages but excludes languages not intended primarily for human communication, such as programming languages.

Instances
Eq BCP47 Source # 
Instance details

Defined in Data.BCP47

Methods

(==) :: BCP47 -> BCP47 -> Bool #

(/=) :: BCP47 -> BCP47 -> Bool #

Ord BCP47 Source # 
Instance details

Defined in Data.BCP47

Methods

compare :: BCP47 -> BCP47 -> Ordering #

(<) :: BCP47 -> BCP47 -> Bool #

(<=) :: BCP47 -> BCP47 -> Bool #

(>) :: BCP47 -> BCP47 -> Bool #

(>=) :: BCP47 -> BCP47 -> Bool #

max :: BCP47 -> BCP47 -> BCP47 #

min :: BCP47 -> BCP47 -> BCP47 #

Read BCP47 Source # 
Instance details

Defined in Data.BCP47

Show BCP47 Source # 
Instance details

Defined in Data.BCP47

Methods

showsPrec :: Int -> BCP47 -> ShowS #

show :: BCP47 -> String #

showList :: [BCP47] -> ShowS #

Arbitrary BCP47 Source # 
Instance details

Defined in Data.BCP47

Methods

arbitrary :: Gen BCP47 #

shrink :: BCP47 -> [BCP47] #

ToJSON BCP47 Source # 
Instance details

Defined in Data.BCP47

FromJSON BCP47 Source # 
Instance details

Defined in Data.BCP47

inits :: BCP47 -> [BCP47] Source #

Produce a list of (<= priority) language tags

>>> inits enGBTJP
[en,en-GB,en-GB-t-jp]

Construction

mkLanguage :: ISO639_1 -> BCP47 Source #

Construct a simple language tag

mkLocalized :: ISO639_1 -> Country -> BCP47 Source #

Construct a localized tag

fromText :: Text -> Either Text BCP47 Source #

Parse a language tag from text

>>> fromText $ pack "en"
Right en
>>> fromText $ pack "de-CH"
Right de-CH
>>> fromText $ pack "ru-USR"
Left "fromText:1:3:\n  |\n1 | ru-USR\n  |   ^\nunexpected '-'\n"
>>> fromText $ pack "en-a-ccc-v-qqq-a-bbb"
Right en-a-bbb-a-ccc-v-qqq
>>> fromText $ pack "de-Latn-DE"
Right de-Latn-DE
>>> fromText $ pack "de-Latf-DE"
Right de-Latf-DE
>>> fromText $ pack "de-CH-1996"
Right de-CH-1996
>>> fromText $ pack "de-Deva"
Right de-Deva
>>> fromText $ pack "zh-Hant-CN-x-private1-private2"
Right zh-Hant-CN-x-private1-private2
>>> fromText $ pack "zh-Hant-CN-x-private1"
Right zh-Hant-CN-x-private1
>>> fromText $ pack "zh-Hant-CN"
Right zh-Hant-CN
>>> fromText $ pack "zh-Hant"
Right zh-Hant
>>> fromText $ pack "zh"
Right zh

Serialization

toText :: BCP47 -> Text Source #

Serialize BCP47 to Text

Subtags are serialized in the order described in the BCP 47 specification. Private-use subtags only appear at the end prefixed with an x.

Subtags

A language tag is composed from a sequence of one or more "subtags", each of which refines or narrows the range of language identified by the overall tag. Subtags, in turn, are a sequence of alphanumeric characters (letters and digits), distinguished and separated from other subtags in a tag by a hyphen ("-", [Unicode] U+002D).

toSubtags :: BCP47 -> [Subtags] Source #

Convert tag to list of subtags

Language

language :: BCP47 -> ISO639_1 Source #

The language subtag

languageFromText :: Text -> Either Text ISO639_1 Source #

Parse a language subtag from Text

Language Extension

extendedLanguageSubtags :: BCP47 -> Set LanguageExtension Source #

Look up all language extension subtags

Language Script

data Script Source #

Script subtags

Script subtags are used to indicate the script or writing system variations that distinguish the written forms of a language or its dialects.

Instances
Eq Script Source # 
Instance details

Defined in Data.BCP47.Internal.Script

Methods

(==) :: Script -> Script -> Bool #

(/=) :: Script -> Script -> Bool #

Ord Script Source # 
Instance details

Defined in Data.BCP47.Internal.Script

Show Script Source # 
Instance details

Defined in Data.BCP47.Internal.Script

Arbitrary Script Source # 
Instance details

Defined in Data.BCP47.Internal.Script

script :: BCP47 -> Maybe Script Source #

Look up the script subtag

Region

data Country #

A country recognized by ISO 3166.

Instances
Bounded Country 
Instance details

Defined in Country.Unexposed.Names

Enum Country 
Instance details

Defined in Country.Unexposed.Names

Eq Country 
Instance details

Defined in Country.Unexposed.Names

Methods

(==) :: Country -> Country -> Bool #

(/=) :: Country -> Country -> Bool #

Ord Country 
Instance details

Defined in Country.Unexposed.Names

Show Country 
Instance details

Defined in Country.Unexposed.Names

Generic Country 
Instance details

Defined in Country.Unexposed.Names

Associated Types

type Rep Country :: Type -> Type #

Methods

from :: Country -> Rep Country x #

to :: Rep Country x -> Country #

Hashable Country 
Instance details

Defined in Country.Unexposed.Names

Methods

hashWithSalt :: Int -> Country -> Int #

hash :: Country -> Int #

ToJSON Country 
Instance details

Defined in Country.Unexposed.Names

FromJSON Country 
Instance details

Defined in Country.Unexposed.Names

Storable Country 
Instance details

Defined in Country.Unexposed.Names

NFData Country 
Instance details

Defined in Country.Unexposed.Names

Methods

rnf :: Country -> () #

Prim Country 
Instance details

Defined in Country.Unexposed.Names

type Rep Country 
Instance details

Defined in Country.Unexposed.Names

type Rep Country = D1 (MetaData "Country" "Country.Unexposed.Names" "country-0.1.6-Ii4TkuGBe7OJhhbgT8y7Xv" True) (C1 (MetaCons "Country" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16)))

region :: BCP47 -> Maybe Country Source #

Look up the region subtag

regionFromText :: Text -> Either Text Country Source #

Parse a region subtag from Text

>>> regionFromText $ pack "ZW"
Right zimbabwe
>>> regionFromText $ pack "012"
Right algeria
>>> regionFromText $ pack "asdf"
Left "regionFromText:1:1:\n  |\n1 | asdf\n  | ^\nunexpected 'a'\nexpecting 2 or 3 character country code\n"

Variant

data Variant Source #

Variant subtags

Variant subtags are used to indicate additional, well-recognized variations that define a language or its dialects that are not covered by other available subtags.

Instances
Eq Variant Source # 
Instance details

Defined in Data.BCP47.Internal.Variant

Methods

(==) :: Variant -> Variant -> Bool #

(/=) :: Variant -> Variant -> Bool #

Ord Variant Source # 
Instance details

Defined in Data.BCP47.Internal.Variant

Show Variant Source # 
Instance details

Defined in Data.BCP47.Internal.Variant

Arbitrary Variant Source # 
Instance details

Defined in Data.BCP47.Internal.Variant

variants :: BCP47 -> Set Variant Source #

Look up all variant subtags

Extension

data Extension Source #

Extension subtags

Extensions provide a mechanism for extending language tags for use in various applications. They are intended to identify information that is commonly used in association with languages or language tags but that is not part of language identification.

extensions :: BCP47 -> Set Extension Source #

Look up all extension subtags

Private Use

data PrivateUse Source #

Private Use subtags

Private use subtags are used to indicate distinctions in language that are important in a given context by private agreement.

privateUse :: BCP47 -> Set PrivateUse Source #

Look up all private use subtags

For testing

en :: BCP47 Source #

English

es :: BCP47 Source #

Spanish

sw :: BCP47 Source #

Swahili

enGB :: BCP47 Source #

British English

enUS :: BCP47 Source #

American English

enTJP :: BCP47 Source #

A nonsense tag en-t-jp

enGBTJP :: BCP47 Source #

A nonsense tag en-GB-t-jp