{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 902
{-# LANGUAGE FieldSelectors #-}
#else
{-# OPTIONS_GHC -Wno-name-shadowing #-}
#endif
module Data.PhoneNumber.Number
( PhoneNumber
, pattern PhoneNumber
, extension
, rawInput
, preferredDomesticCarrierCode
, nationalNumber
, countryCode
, italianLeadingZero
, countryCodeSource
, numberOfLeadingZeros
, CountryCode(..)
, CountryCodeSource(..)
) where
import Data.ByteString (ByteString)
import Data.PhoneNumber.Internal.Number
( CPhoneNumber(CPhoneNumber), PhoneNumber, CountryCodeSource, toCPhoneNumber
, fromCPhoneNumber
)
import qualified Data.PhoneNumber.Internal.Number as I
newtype CountryCode = CountryCode Int
deriving newtype (CountryCode -> CountryCode -> Bool
(CountryCode -> CountryCode -> Bool)
-> (CountryCode -> CountryCode -> Bool) -> Eq CountryCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CountryCode -> CountryCode -> Bool
== :: CountryCode -> CountryCode -> Bool
$c/= :: CountryCode -> CountryCode -> Bool
/= :: CountryCode -> CountryCode -> Bool
Eq, Eq CountryCode
Eq CountryCode =>
(CountryCode -> CountryCode -> Ordering)
-> (CountryCode -> CountryCode -> Bool)
-> (CountryCode -> CountryCode -> Bool)
-> (CountryCode -> CountryCode -> Bool)
-> (CountryCode -> CountryCode -> Bool)
-> (CountryCode -> CountryCode -> CountryCode)
-> (CountryCode -> CountryCode -> CountryCode)
-> Ord CountryCode
CountryCode -> CountryCode -> Bool
CountryCode -> CountryCode -> Ordering
CountryCode -> CountryCode -> CountryCode
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CountryCode -> CountryCode -> Ordering
compare :: CountryCode -> CountryCode -> Ordering
$c< :: CountryCode -> CountryCode -> Bool
< :: CountryCode -> CountryCode -> Bool
$c<= :: CountryCode -> CountryCode -> Bool
<= :: CountryCode -> CountryCode -> Bool
$c> :: CountryCode -> CountryCode -> Bool
> :: CountryCode -> CountryCode -> Bool
$c>= :: CountryCode -> CountryCode -> Bool
>= :: CountryCode -> CountryCode -> Bool
$cmax :: CountryCode -> CountryCode -> CountryCode
max :: CountryCode -> CountryCode -> CountryCode
$cmin :: CountryCode -> CountryCode -> CountryCode
min :: CountryCode -> CountryCode -> CountryCode
Ord, Int -> CountryCode -> ShowS
[CountryCode] -> ShowS
CountryCode -> String
(Int -> CountryCode -> ShowS)
-> (CountryCode -> String)
-> ([CountryCode] -> ShowS)
-> Show CountryCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CountryCode -> ShowS
showsPrec :: Int -> CountryCode -> ShowS
$cshow :: CountryCode -> String
show :: CountryCode -> String
$cshowList :: [CountryCode] -> ShowS
showList :: [CountryCode] -> ShowS
Show, Integer -> CountryCode
CountryCode -> CountryCode
CountryCode -> CountryCode -> CountryCode
(CountryCode -> CountryCode -> CountryCode)
-> (CountryCode -> CountryCode -> CountryCode)
-> (CountryCode -> CountryCode -> CountryCode)
-> (CountryCode -> CountryCode)
-> (CountryCode -> CountryCode)
-> (CountryCode -> CountryCode)
-> (Integer -> CountryCode)
-> Num CountryCode
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: CountryCode -> CountryCode -> CountryCode
+ :: CountryCode -> CountryCode -> CountryCode
$c- :: CountryCode -> CountryCode -> CountryCode
- :: CountryCode -> CountryCode -> CountryCode
$c* :: CountryCode -> CountryCode -> CountryCode
* :: CountryCode -> CountryCode -> CountryCode
$cnegate :: CountryCode -> CountryCode
negate :: CountryCode -> CountryCode
$cabs :: CountryCode -> CountryCode
abs :: CountryCode -> CountryCode
$csignum :: CountryCode -> CountryCode
signum :: CountryCode -> CountryCode
$cfromInteger :: Integer -> CountryCode
fromInteger :: Integer -> CountryCode
Num)
pattern PhoneNumber
:: Maybe ByteString
-> Maybe ByteString
-> Maybe ByteString
-> Word
-> CountryCode
-> Maybe Bool
-> Maybe CountryCodeSource
-> Maybe Int
-> PhoneNumber
pattern $mPhoneNumber :: forall {r}.
PhoneNumber
-> (Maybe ByteString
-> Maybe ByteString
-> Maybe ByteString
-> Word
-> CountryCode
-> Maybe Bool
-> Maybe CountryCodeSource
-> Maybe Int
-> r)
-> ((# #) -> r)
-> r
$bPhoneNumber :: Maybe ByteString
-> Maybe ByteString
-> Maybe ByteString
-> Word
-> CountryCode
-> Maybe Bool
-> Maybe CountryCodeSource
-> Maybe Int
-> PhoneNumber
PhoneNumber
{ PhoneNumber -> Maybe ByteString
extension
, PhoneNumber -> Maybe ByteString
rawInput
, PhoneNumber -> Maybe ByteString
preferredDomesticCarrierCode
, PhoneNumber -> Word
nationalNumber
, PhoneNumber -> CountryCode
countryCode
, PhoneNumber -> Maybe Bool
italianLeadingZero
, PhoneNumber -> Maybe CountryCodeSource
countryCodeSource
, PhoneNumber -> Maybe Int
numberOfLeadingZeros
}
<- (toCPhoneNumber -> CPhoneNumber
{ I.nationalNumber = fromIntegral -> nationalNumber
, I.countryCode = fromIntegral -> CountryCode -> countryCode
, I.numberOfLeadingZeros = fmap fromIntegral -> numberOfLeadingZeros
, .. })
where
PhoneNumber Maybe ByteString
extension Maybe ByteString
rawInput Maybe ByteString
preferredDomesticCarrierCode
(Word -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> CULong
nationalNumber)
(CountryCode (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> CInt
countryCode)) Maybe Bool
italianLeadingZero
Maybe CountryCodeSource
countryCodeSource ((Int -> CInt) -> Maybe Int -> Maybe CInt
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Maybe CInt
numberOfLeadingZeros)
= CPhoneNumber -> PhoneNumber
fromCPhoneNumber (CPhoneNumber -> PhoneNumber) -> CPhoneNumber -> PhoneNumber
forall a b. (a -> b) -> a -> b
$ CPhoneNumber{Maybe Bool
Maybe CInt
Maybe ByteString
Maybe CountryCodeSource
CULong
CInt
$sel:nationalNumber:CPhoneNumber :: CULong
$sel:countryCode:CPhoneNumber :: CInt
$sel:numberOfLeadingZeros:CPhoneNumber :: Maybe CInt
$sel:extension:CPhoneNumber :: Maybe ByteString
$sel:rawInput:CPhoneNumber :: Maybe ByteString
$sel:preferredDomesticCarrierCode:CPhoneNumber :: Maybe ByteString
$sel:italianLeadingZero:CPhoneNumber :: Maybe Bool
$sel:countryCodeSource:CPhoneNumber :: Maybe CountryCodeSource
extension :: Maybe ByteString
rawInput :: Maybe ByteString
preferredDomesticCarrierCode :: Maybe ByteString
nationalNumber :: CULong
countryCode :: CInt
italianLeadingZero :: Maybe Bool
countryCodeSource :: Maybe CountryCodeSource
numberOfLeadingZeros :: Maybe CInt
..}
{-# COMPLETE PhoneNumber #-}
extension :: PhoneNumber -> Maybe ByteString
rawInput :: PhoneNumber -> Maybe ByteString
preferredDomesticCarrierCode :: PhoneNumber -> Maybe ByteString
nationalNumber :: PhoneNumber -> Word
countryCode :: PhoneNumber -> CountryCode
italianLeadingZero :: PhoneNumber -> Maybe Bool
countryCodeSource :: PhoneNumber -> Maybe CountryCodeSource
numberOfLeadingZeros :: PhoneNumber -> Maybe Int