localization tutorial =====================
> {-# LANGUAGE DataKinds #-}             -- for type-level locales (EN, FR, …)
> {-# LANGUAGE LambdaCase #-}            -- for less verbose case switching
> {-# LANGUAGE MultiParamTypeClasses #-} -- for messages as a type class (Msg2)
> {-# LANGUAGE OverloadedStrings #-}     -- for Text encoding of locales
> {-# LANGUAGE FlexibleInstances #-}     -- for localization instances
> module Data.Locale.Tutorial where
> import Data.Locale
> import Data.Semigroup ((<>))
> import Data.Text (Text)
> import qualified Data.Map.Strict as Map
Locales ------- Type-level locale ~~~~~~~~~~~~~~~~~ At the type-level, each locale is an independant type (eg. `data FR`), which does need inhabitant, but a `FullLocale` data instance to list the full locales it gathers. (eg. `data instance FullLocale FR = FR_BE | FR_CA | FR_CH | FR_FR | FR_LU`) Supported locales must be gathered into a type-level list:
> type SupportedLocales = [EN, FR]
Here using two library-defined locales: - `EN` for english, - `FR` for french. NOTE: To define custom locales: copy and adapt the corresponding section of source code defining one of the library-defined ones. Term-level locale ~~~~~~~~~~~~~~~~~ A specific term-level locale is an index (a so-called singleton using `GADTs`) within the `SupportedLocales`, eg:
> fr_BE :: Locale SupportedLocales FR
> fr_BE =  localeInj FR_BE
And a generic term-level locale hides the type-level locale (using `ExistentialQuantification` in `LocaleIn`):
> selectedLocaleHardCoded :: LocaleIn SupportedLocales
> selectedLocaleHardCoded =  LocaleIn fr_BE
The same can be achieved without hardcoding:
> selectedLocale :: LocaleIn SupportedLocales
> selectedLocale = case  Map.lookup "fr_BE" locales of
>                   Nothing -> error "Unsupported locale"
>                   Just l  -> l
First method: messages as a data type ------------------------------------- Each message is a variant within a data type:
> data Msg1 out
>    = Msg1_Hello
>    | Msg1_Bang out
Each localization is an instance of `LocalizeIn`:
> instance LocalizeIn EN Text (Msg1 Text) where
>   localizeIn _l = \case
>     Msg1_Hello  -> "Hello"
>     Msg1_Bang n -> n<>"!"
>
> instance LocalizeIn FR Text (Msg1 Text) where
>   localizeIn l = \case
>     Msg1_Hello ->
>       case l of
>         FR_BE -> "Bonjour une fois"
>         _     -> "Bonjour"
>     Msg1_Bang n -> n<>" !"
A localization can be selected with `localize`, which selects the `localizeIn` indexed by `selectedLocale`:
> l10n1 :: Msg1 Text -> Text
> l10n1 = localize selectedLocale
A message can then be localized by applying `l10n1` to a variant of `Msg1`:
> helloWorld1 :: Text
> helloWorld1 = l10n1 Msg1_Hello <> " " <> l10n1 (Msg1_Bang "World")
Second method: messages as a type class --------------------------------------- Each message is a class method:
> class Msg2 out l where
>   msg2_Hello ::        FullLocale l -> out
>   msg2_Bang  :: out -> FullLocale l -> out
Each localization is an instance of `Msg2`:
> instance Msg2 Text EN where
>   msg2_Hello  _l = "Hello"
>   msg2_Bang n _l = n<>"!"
>
> instance Msg2 Text FR where
>   msg2_Hello = \case
>     FR_BE -> "Bonjour une fois"
>     _     -> "Bonjour"
>   msg2_Bang n _l = n<>" !"
A localization can be selected with `loqualize`, which embeds the type class dictionnary (aka. type qualification) indexed by `selectedLocale` (using `ExistentialQuantification` in `Loqualization`):
> l10n2 :: Loqualization (Msg2 Text)
> l10n2 = loqualize selectedLocale
A message can then be localized by bringing into scope the class dictionnary of `Msg2` embedded by `l10n2`, and using its methods:
> helloWorld2 :: Text
> helloWorld2
>  | Loqualization l <- l10n2
>  = msg2_Hello l <> " " <> msg2_Bang "World" l