{-# LINE 1 "Data/Text/ICU/Number.hsc" #-}
{-# LANGUAGE CPP, DeriveDataTypeable, ForeignFunctionInterface #-}
module Data.Text.ICU.Number
(
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
data NumberFormatStyle
= NUM_PATTERN_DECIMAL Text
| NUM_DECIMAL
| NUM_CURRENCY
| NUM_PERCENT
| NUM_SCIENTIFIC
| NUM_SPELLOUT
| NUM_ORDINAL
| NUM_DURATION
| NUM_NUMBERING_SYSTEM
| NUM_PATTERN_RULEBASED Text
| NUM_CURRENCY_ISO
| NUM_CURRENCY_PLURAL
| NUM_CURRENCY_ACCOUNTING
| NUM_CASH_CURRENCY
| NUM_DECIMAL_COMPACT_SHORT
| NUM_DECIMAL_COMPACT_LONG
| NUM_CURRENCY_STANDARD
| NUM_FORMAT_STYLE_COUNT
| NUM_DEFAULT
| NUM_IGNORE
deriving (Eq, Show, Typeable)
type UNumberFormatStyle = CInt
toNFS :: NumberFormatStyle -> UNumberFormatStyle
toNFS (NUM_PATTERN_DECIMAL _) = 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" #-}
numberFormatter :: NumberFormatStyle
-> LocaleName
-> NumberFormat
numberFormatter sty@(NUM_PATTERN_DECIMAL pattern) loc = numberFormatter' (toNFS sty) pattern loc
numberFormatter sty@(NUM_PATTERN_RULEBASED pattern) loc = numberFormatter' (toNFS sty) pattern loc
numberFormatter style loc = numberFormatter' (toNFS style) T.empty loc
numberFormatter' :: UNumberFormatStyle
-> Text
-> LocaleName
-> NumberFormat
numberFormatter' style pattern loc =
System.IO.Unsafe.unsafePerformIO $ fmap C $ wrap $
useAsUCharPtr pattern $ \patternPtr patternLen ->
withLocaleName loc $
handleParseError (== u_PARSE_ERROR) . (unum_open style patternPtr (fromIntegral 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)
class FormattableNumber n where
formatNumber :: NumberFormat
-> n
-> Text
formatNumber' :: (FormattableNumber n)
=> NumberFormatStyle
-> LocaleName
-> n
-> Text
formatNumber' style loc x = formatNumber (numberFormatter style loc) x
instance FormattableNumber Integer where
formatNumber (C nf) x = numberFormatInt nf (fromIntegral x)
instance FormattableNumber Natural where
formatNumber (C nf) x = numberFormatInt nf (fromIntegral x)
instance FormattableNumber Int where
formatNumber (C nf) x = numberFormatInt nf x
instance FormattableNumber Double where
formatNumber (C nf) x = numberFormatDouble nf x
instance FormattableNumber Float where
formatNumber (C nf) x = numberFormatDouble nf (fromRational $ toRational x)
numberFormatInt :: MNumberFormat -> Int -> Text
numberFormatInt nf x = System.IO.Unsafe.unsafePerformIO $
withNumberFormat nf $ \nptr ->
handleOverflowError 100
(\dptr dlen ec -> unum_formatInt64 nptr (fromIntegral x) dptr (fromIntegral dlen) ec)
(\dptr dlen -> fromUCharPtr dptr (fromIntegral dlen))
numberFormatDouble :: MNumberFormat -> Double -> Text
numberFormatDouble nf x = System.IO.Unsafe.unsafePerformIO $
withNumberFormat nf $ \nptr ->
handleOverflowError 100
(\dptr dlen ec -> unum_formatDouble nptr (CDouble x) dptr (fromIntegral dlen) ec)
(\dptr dlen -> fromUCharPtr dptr (fromIntegral 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