{-# LINE 1 "Data/Text/ICU/Number.hsc" #-}
{-# LANGUAGE CPP, DeriveDataTypeable, ForeignFunctionInterface #-}
-- |
-- Module      : Data.Text.ICU.Number
-- Copyright   : (c) 2020 Torsten Kemps-Benedix
--
-- License     : BSD-style
-- Maintainer  : tkx68@icloud.com
-- Stability   : experimental
-- Portability : GHC
--
-- New users with are strongly encouraged to see
-- if Data.Text.ICU.NumberFormatter fits their use case.
-- Although not deprecated, this header is provided for backwards
-- compatibility only.

module Data.Text.ICU.Number
    (
    -- * Unicode number formatting API
    -- $api
    numberFormatter
    , FormattableNumber, formatNumber, formatNumber'
    , NumberFormatStyle(..)
    , NumberFormat
) where


{-# LINE 29 "Data/Text/ICU/Number.hsc" #-}




import GHC.Natural
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.ICU.Error
import Data.Text.ICU.Error.Internal (UErrorCode, UParseError, handleParseError, handleOverflowError)
import Data.Text.ICU.Internal (UChar, useAsUCharPtr, fromUCharPtr)
import Data.Text.ICU.Internal (LocaleName, withLocaleName)
import Data.Typeable (Typeable)
import Data.Int (Int32)
import Foreign.C.Types (CInt(..), CDouble(..))
import Foreign.Ptr (Ptr)
import System.IO.Unsafe (unsafePerformIO)
import Prelude hiding (compare)
import Foreign.C.String (CString)
import Data.Text.ICU.Number.Internal
-- $api
--
-- This module helps you to format and parse numbers for any locale. Your code
-- can be completely independent of the locale conventions for decimal points,
-- thousands-separators, or even the particular decimal digits used, or whether
-- the number format is even decimal. There are different number format styles
-- like decimal, currency, percent and spelled-out.
--
-- Use 'formatter' to create a formatter and 'format' to format numbers.

-- | The possible number format styles.
data NumberFormatStyle
    = NUM_PATTERN_DECIMAL Text -- ^ Decimal format defined by a pattern string. See the section \"Patterns\" at <https://unicode-org.github.io/icu-docs/apidoc/released/icu4c/classDecimalFormat.html#Patterns> for further details regarding pattern strings.
    | NUM_DECIMAL -- ^ Decimal format ("normal" style).
    | NUM_CURRENCY -- ^ Currency format (generic). Defaults to UNUM_CURRENCY_STANDARD style (using currency symbol, e.g., "$1.00", with non-accounting style for negative values e.g. using minus sign). The specific style may be specified using the -cf- locale key.
    | NUM_PERCENT -- ^ Percent format.
    | NUM_SCIENTIFIC -- ^ Scientific format.
    | NUM_SPELLOUT -- ^ Spellout rule-based format. The default ruleset can be specified/changed using unum_setTextAttribute with UNUM_DEFAULT_RULESET; the available public rulesets can be listed using unum_getTextAttribute with UNUM_PUBLIC_RULESETS.
    | NUM_ORDINAL -- ^ Ordinal rule-based format. The default ruleset can be specified/changed using unum_setTextAttribute with UNUM_DEFAULT_RULESET; the available public rulesets can be listed using unum_getTextAttribute with UNUM_PUBLIC_RULESETS.
    | NUM_DURATION -- ^ Duration rule-based format.
    | NUM_NUMBERING_SYSTEM -- ^ Numbering system rule-based format.
    | NUM_PATTERN_RULEBASED Text -- ^ Rule-based format defined by a pattern string.  See the section \"Patterns\" at <https://unicode-org.github.io/icu-docs/apidoc/released/icu4c/classDecimalFormat.html#Patterns> for further details regarding pattern strings.
    | NUM_CURRENCY_ISO -- ^ Currency format with an ISO currency code, e.g., "USD1.00".
    | NUM_CURRENCY_PLURAL -- ^ Currency format with a pluralized currency name, e.g., "1.00 US dollar" and "3.00 US dollars".
    | NUM_CURRENCY_ACCOUNTING -- ^ Currency format for accounting, e.g., "($3.00)" for negative currency amount instead of "-$3.00" (UNUM_CURRENCY). Overrides any style specified using -cf- key in locale.
    | NUM_CASH_CURRENCY -- ^ Currency format with a currency symbol given CASH usage, e.g., "NT$3" instead of "NT$3.23".
    | NUM_DECIMAL_COMPACT_SHORT -- ^ Decimal format expressed using compact notation (short form, corresponds to UNumberCompactStyle=UNUM_SHORT) e.g. "23K", "45B"
    | NUM_DECIMAL_COMPACT_LONG -- ^ Decimal format expressed using compact notation (long form, corresponds to UNumberCompactStyle=UNUM_LONG) e.g. "23 thousand", "45 billion"
    | NUM_CURRENCY_STANDARD -- ^ Currency format with a currency symbol, e.g., "$1.00", using non-accounting style for negative values (e.g. minus sign). Overrides any style specified using -cf- key in locale.
    | NUM_FORMAT_STYLE_COUNT -- ^ One more than the highest normal UNumberFormatStyle value. Deprecated: ICU 58 The numeric value may change over time, see ICU ticket #12420.
    | NUM_DEFAULT -- ^ Default format.
    | NUM_IGNORE -- ^ Alias for NUM_PATTERN_DECIMAL.
      deriving (NumberFormatStyle -> NumberFormatStyle -> Bool
(NumberFormatStyle -> NumberFormatStyle -> Bool)
-> (NumberFormatStyle -> NumberFormatStyle -> Bool)
-> Eq NumberFormatStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NumberFormatStyle -> NumberFormatStyle -> Bool
== :: NumberFormatStyle -> NumberFormatStyle -> Bool
$c/= :: NumberFormatStyle -> NumberFormatStyle -> Bool
/= :: NumberFormatStyle -> NumberFormatStyle -> Bool
Eq, Int -> NumberFormatStyle -> ShowS
[NumberFormatStyle] -> ShowS
NumberFormatStyle -> String
(Int -> NumberFormatStyle -> ShowS)
-> (NumberFormatStyle -> String)
-> ([NumberFormatStyle] -> ShowS)
-> Show NumberFormatStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NumberFormatStyle -> ShowS
showsPrec :: Int -> NumberFormatStyle -> ShowS
$cshow :: NumberFormatStyle -> String
show :: NumberFormatStyle -> String
$cshowList :: [NumberFormatStyle] -> ShowS
showList :: [NumberFormatStyle] -> ShowS
Show, Typeable)

type UNumberFormatStyle = CInt

toNFS :: NumberFormatStyle -> UNumberFormatStyle
toNFS :: NumberFormatStyle -> UNumberFormatStyle
toNFS (NUM_PATTERN_DECIMAL Text
_) = UNumberFormatStyle
0
{-# LINE 86 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_DECIMAL = 1
{-# LINE 87 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_CURRENCY = 2
{-# LINE 88 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_PERCENT = 3
{-# LINE 89 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_SCIENTIFIC = 4
{-# LINE 90 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_SPELLOUT = 5
{-# LINE 91 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_ORDINAL = 6
{-# LINE 92 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_DURATION = 7
{-# LINE 93 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_NUMBERING_SYSTEM = 8
{-# LINE 94 "Data/Text/ICU/Number.hsc" #-}
toNFS (NUM_PATTERN_RULEBASED _) = 9
{-# LINE 95 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_CURRENCY_ISO = 10
{-# LINE 96 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_CURRENCY_PLURAL = 11
{-# LINE 97 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_CURRENCY_ACCOUNTING = 12
{-# LINE 98 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_CASH_CURRENCY = 13
{-# LINE 99 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_DECIMAL_COMPACT_SHORT = 14
{-# LINE 100 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_DECIMAL_COMPACT_LONG = 15
{-# LINE 101 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_CURRENCY_STANDARD = 16
{-# LINE 102 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_FORMAT_STYLE_COUNT = 17
{-# LINE 103 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_DEFAULT = 1
{-# LINE 104 "Data/Text/ICU/Number.hsc" #-}
toNFS NUM_IGNORE = 0
{-# LINE 105 "Data/Text/ICU/Number.hsc" #-}

-- | Create and return a new NumberFormat for formatting and parsing numbers.
--
-- A NumberFormat may be used to format numbers by calling unum_format, and
-- to parse numbers by calling unum_parse. The caller must call unum_close when
-- done to release resources used by this object.
numberFormatter :: NumberFormatStyle -- ^ The type of number format to open. If NUM_PATTERN_DECIMAL or NUM_PATTERN_RULEBASED is passed then the number format is opened using the given pattern, which must conform to the syntax described in DecimalFormat or RuleBasedNumberFormat, respectively.
        -> LocaleName -- ^ 	A locale identifier to use to determine formatting and parsing conventions, or NULL to use the default locale, e.g. "de_DE".
        -> NumberFormat
numberFormatter :: NumberFormatStyle -> LocaleName -> NumberFormat
numberFormatter sty :: NumberFormatStyle
sty@(NUM_PATTERN_DECIMAL Text
pattern) LocaleName
loc = UNumberFormatStyle -> Text -> LocaleName -> NumberFormat
numberFormatter' (NumberFormatStyle -> UNumberFormatStyle
toNFS NumberFormatStyle
sty) Text
pattern LocaleName
loc
numberFormatter sty :: NumberFormatStyle
sty@(NUM_PATTERN_RULEBASED Text
pattern) LocaleName
loc = UNumberFormatStyle -> Text -> LocaleName -> NumberFormat
numberFormatter' (NumberFormatStyle -> UNumberFormatStyle
toNFS NumberFormatStyle
sty) Text
pattern LocaleName
loc
numberFormatter NumberFormatStyle
style LocaleName
loc = UNumberFormatStyle -> Text -> LocaleName -> NumberFormat
numberFormatter' (NumberFormatStyle -> UNumberFormatStyle
toNFS NumberFormatStyle
style) Text
T.empty LocaleName
loc

numberFormatter' :: UNumberFormatStyle -- ^ The type of number format to open. If NUM_PATTERN_DECIMAL or NUM_PATTERN_RULEBASED is passed then the number format is opened using the given pattern, which must conform to the syntax described in DecimalFormat or RuleBasedNumberFormat, respectively.
        -> Text
        -> LocaleName -- ^ 	A locale identifier to use to determine formatting and parsing conventions, or NULL to use the default locale, e.g. "de_DE".
        -> NumberFormat
numberFormatter' :: UNumberFormatStyle -> Text -> LocaleName -> NumberFormat
numberFormatter' UNumberFormatStyle
style Text
pattern LocaleName
loc =
    IO NumberFormat -> NumberFormat
forall a. IO a -> a
System.IO.Unsafe.unsafePerformIO (IO NumberFormat -> NumberFormat)
-> IO NumberFormat -> NumberFormat
forall a b. (a -> b) -> a -> b
$ (MNumberFormat -> NumberFormat)
-> IO MNumberFormat -> IO NumberFormat
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MNumberFormat -> NumberFormat
C (IO MNumberFormat -> IO NumberFormat)
-> IO MNumberFormat -> IO NumberFormat
forall a b. (a -> b) -> a -> b
$ IO (Ptr UNumberFormat) -> IO MNumberFormat
wrap (IO (Ptr UNumberFormat) -> IO MNumberFormat)
-> IO (Ptr UNumberFormat) -> IO MNumberFormat
forall a b. (a -> b) -> a -> b
$
    Text
-> (Ptr UChar -> I16 -> IO (Ptr UNumberFormat))
-> IO (Ptr UNumberFormat)
forall a. Text -> (Ptr UChar -> I16 -> IO a) -> IO a
useAsUCharPtr Text
pattern ((Ptr UChar -> I16 -> IO (Ptr UNumberFormat))
 -> IO (Ptr UNumberFormat))
-> (Ptr UChar -> I16 -> IO (Ptr UNumberFormat))
-> IO (Ptr UNumberFormat)
forall a b. (a -> b) -> a -> b
$ \Ptr UChar
patternPtr I16
patternLen ->
            LocaleName
-> (CString -> IO (Ptr UNumberFormat)) -> IO (Ptr UNumberFormat)
forall a. LocaleName -> (CString -> IO a) -> IO a
withLocaleName LocaleName
loc ((CString -> IO (Ptr UNumberFormat)) -> IO (Ptr UNumberFormat))
-> (CString -> IO (Ptr UNumberFormat)) -> IO (Ptr UNumberFormat)
forall a b. (a -> b) -> a -> b
$
                (ICUError -> Bool)
-> (Ptr UParseError
    -> Ptr UNumberFormatStyle -> IO (Ptr UNumberFormat))
-> IO (Ptr UNumberFormat)
forall a.
(ICUError -> Bool)
-> (Ptr UParseError -> Ptr UNumberFormatStyle -> IO a) -> IO a
handleParseError (ICUError -> ICUError -> Bool
forall a. Eq a => a -> a -> Bool
== ICUError
u_PARSE_ERROR) ((Ptr UParseError
  -> Ptr UNumberFormatStyle -> IO (Ptr UNumberFormat))
 -> IO (Ptr UNumberFormat))
-> (CString
    -> Ptr UParseError
    -> Ptr UNumberFormatStyle
    -> IO (Ptr UNumberFormat))
-> CString
-> IO (Ptr UNumberFormat)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UNumberFormatStyle
-> Ptr UChar
-> Int32
-> CString
-> Ptr UParseError
-> Ptr UNumberFormatStyle
-> IO (Ptr UNumberFormat)
unum_open UNumberFormatStyle
style Ptr UChar
patternPtr (I16 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral I16
patternLen))

foreign import ccall unsafe "hs_text_icu.h __hs_unum_open" unum_open
    :: UNumberFormatStyle -> Ptr UChar -> Int32 -> CString -> Ptr UParseError  -> Ptr UErrorCode -> IO (Ptr UNumberFormat)

-- | Format an integer using a NumberFormat.
--
-- The integer will be formatted according to the UNumberFormat's locale.
class FormattableNumber n where
    formatNumber :: NumberFormat -- ^ The formatter to use.
                -> n -- ^ The number to format.
                -> Text

-- | Create a formatter and apply it in one step.
formatNumber' :: (FormattableNumber n)
            => NumberFormatStyle -- ^ The type of number format to open. If NUM_PATTERN_DECIMAL or NUM_PATTERN_RULEBASED is passed then the number format is opened using the given pattern, which must conform to the syntax described in DecimalFormat or RuleBasedNumberFormat, respectively.
            -> LocaleName -- ^ 	A locale identifier to use to determine formatting and parsing conventions, or NULL to use the default locale, e.g. "de_DE".
            -> n -- ^ The number to format.
            -> Text
formatNumber' :: forall n.
FormattableNumber n =>
NumberFormatStyle -> LocaleName -> n -> Text
formatNumber' NumberFormatStyle
style LocaleName
loc n
x = NumberFormat -> n -> Text
forall n. FormattableNumber n => NumberFormat -> n -> Text
formatNumber (NumberFormatStyle -> LocaleName -> NumberFormat
numberFormatter NumberFormatStyle
style LocaleName
loc) n
x

instance FormattableNumber Integer where
    formatNumber :: NumberFormat -> Integer -> Text
formatNumber (C MNumberFormat
nf) Integer
x = MNumberFormat -> Int -> Text
numberFormatInt MNumberFormat
nf (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x)

instance FormattableNumber Natural where
    formatNumber :: NumberFormat -> Natural -> Text
formatNumber (C MNumberFormat
nf) Natural
x = MNumberFormat -> Int -> Text
numberFormatInt MNumberFormat
nf (Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
x)

instance FormattableNumber Int where
    formatNumber :: NumberFormat -> Int -> Text
formatNumber (C MNumberFormat
nf) Int
x = MNumberFormat -> Int -> Text
numberFormatInt MNumberFormat
nf Int
x

instance FormattableNumber Double where
    formatNumber :: NumberFormat -> Double -> Text
formatNumber (C MNumberFormat
nf) Double
x = MNumberFormat -> Double -> Text
numberFormatDouble MNumberFormat
nf Double
x

instance FormattableNumber Float where
    formatNumber :: NumberFormat -> Float -> Text
formatNumber (C MNumberFormat
nf) Float
x = MNumberFormat -> Double -> Text
numberFormatDouble MNumberFormat
nf (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double) -> Rational -> Double
forall a b. (a -> b) -> a -> b
$ Float -> Rational
forall a. Real a => a -> Rational
toRational Float
x)

-- | Create a number format.
numberFormatInt :: MNumberFormat -> Int -> Text
numberFormatInt :: MNumberFormat -> Int -> Text
numberFormatInt MNumberFormat
nf Int
x = IO Text -> Text
forall a. IO a -> a
System.IO.Unsafe.unsafePerformIO (IO Text -> Text) -> IO Text -> Text
forall a b. (a -> b) -> a -> b
$
  MNumberFormat -> (Ptr UNumberFormat -> IO Text) -> IO Text
forall a. MNumberFormat -> (Ptr UNumberFormat -> IO a) -> IO a
withNumberFormat MNumberFormat
nf ((Ptr UNumberFormat -> IO Text) -> IO Text)
-> (Ptr UNumberFormat -> IO Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ \Ptr UNumberFormat
nptr ->
    Int
-> (Ptr UChar -> Int32 -> Ptr UNumberFormatStyle -> IO Int32)
-> (Ptr UChar -> Int -> IO Text)
-> IO Text
forall a b.
Storable a =>
Int
-> (Ptr a -> Int32 -> Ptr UNumberFormatStyle -> IO Int32)
-> (Ptr a -> Int -> IO b)
-> IO b
handleOverflowError Int
100
        (\Ptr UChar
dptr Int32
dlen Ptr UNumberFormatStyle
ec -> Ptr UNumberFormat
-> Int -> Ptr UChar -> Int32 -> Ptr UNumberFormatStyle -> IO Int32
unum_formatInt64 Ptr UNumberFormat
nptr (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x) Ptr UChar
dptr (Int32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
dlen) Ptr UNumberFormatStyle
ec)
        (\Ptr UChar
dptr Int
dlen -> Ptr UChar -> I16 -> IO Text
fromUCharPtr Ptr UChar
dptr (Int -> I16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
dlen))

-- | Format a number.
numberFormatDouble :: MNumberFormat -> Double -> Text
numberFormatDouble :: MNumberFormat -> Double -> Text
numberFormatDouble MNumberFormat
nf Double
x = IO Text -> Text
forall a. IO a -> a
System.IO.Unsafe.unsafePerformIO (IO Text -> Text) -> IO Text -> Text
forall a b. (a -> b) -> a -> b
$
  MNumberFormat -> (Ptr UNumberFormat -> IO Text) -> IO Text
forall a. MNumberFormat -> (Ptr UNumberFormat -> IO a) -> IO a
withNumberFormat MNumberFormat
nf ((Ptr UNumberFormat -> IO Text) -> IO Text)
-> (Ptr UNumberFormat -> IO Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ \Ptr UNumberFormat
nptr ->
    Int
-> (Ptr UChar -> Int32 -> Ptr UNumberFormatStyle -> IO Int32)
-> (Ptr UChar -> Int -> IO Text)
-> IO Text
forall a b.
Storable a =>
Int
-> (Ptr a -> Int32 -> Ptr UNumberFormatStyle -> IO Int32)
-> (Ptr a -> Int -> IO b)
-> IO b
handleOverflowError Int
100
        (\Ptr UChar
dptr Int32
dlen Ptr UNumberFormatStyle
ec -> Ptr UNumberFormat
-> CDouble
-> Ptr UChar
-> Int32
-> Ptr UNumberFormatStyle
-> IO Int32
unum_formatDouble Ptr UNumberFormat
nptr (Double -> CDouble
CDouble Double
x) Ptr UChar
dptr (Int32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
dlen) Ptr UNumberFormatStyle
ec)
        (\Ptr UChar
dptr Int
dlen -> Ptr UChar -> I16 -> IO Text
fromUCharPtr Ptr UChar
dptr (Int -> I16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
dlen))

foreign import ccall unsafe "hs_text_icu.h __hs_unum_formatInt64" unum_formatInt64
    :: Ptr UNumberFormat -> Int -> Ptr UChar -> Int32 -> Ptr UErrorCode -> IO Int32
foreign import ccall unsafe "hs_text_icu.h __hs_unum_formatDouble" unum_formatDouble
    :: Ptr UNumberFormat -> CDouble -> Ptr UChar -> Int32 -> Ptr UErrorCode -> IO Int32