module Data.PhoneNumber.Util
(
parseNumber
, ParseMode(..)
, ErrorType(..)
, formatNumber
, PhoneNumberFormat(..)
, matchNumbers
, MatchType(..)
, regionForNumber
, nationalSignificantNumber
, isValidNumber
, numberType
, PhoneNumberType(..)
, possibleNumber
, ValidationResult(..)
, canBeInternationallyDialed
, isGeographicalNumber
, isGeographicalNumberType
, isAlphaNumber
, supportedRegions
, supportedGlobalNetworkCallingCodes
, supportedCallingCodes
, supportedTypesForRegion
, supportedTypesForNonGeoEntity
, Region(..)
, NonGeoRegion(..)
, CountryCode(..)
, countryCodeForRegion
, regionForCountryCode
, regionsForCountryCode
, isNANPACountry
, countryMobileToken
, nddPrefixForRegion
, truncateTooLongNumber
, convertAlphaNumber
, normalizeNumber
, Normalize(..)
, PhoneNumber
)
where
import Control.DeepSeq
import Data.ByteString (ByteString)
import Data.Coerce
import Data.Data
import Data.PhoneNumber.Number
import Data.PhoneNumber.Internal.Util hiding (ErrorType(..), PhoneNumberFormat(..))
import qualified Data.PhoneNumber.Internal.Util as I
import qualified Data.Set as S
import GHC.Generics
import GHC.Exts
import GHC.IO
newtype Region = Region ByteString
deriving newtype (Region -> Region -> Bool
(Region -> Region -> Bool)
-> (Region -> Region -> Bool) -> Eq Region
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Region -> Region -> Bool
== :: Region -> Region -> Bool
$c/= :: Region -> Region -> Bool
/= :: Region -> Region -> Bool
Eq, Eq Region
Eq Region =>
(Region -> Region -> Ordering)
-> (Region -> Region -> Bool)
-> (Region -> Region -> Bool)
-> (Region -> Region -> Bool)
-> (Region -> Region -> Bool)
-> (Region -> Region -> Region)
-> (Region -> Region -> Region)
-> Ord Region
Region -> Region -> Bool
Region -> Region -> Ordering
Region -> Region -> Region
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 :: Region -> Region -> Ordering
compare :: Region -> Region -> Ordering
$c< :: Region -> Region -> Bool
< :: Region -> Region -> Bool
$c<= :: Region -> Region -> Bool
<= :: Region -> Region -> Bool
$c> :: Region -> Region -> Bool
> :: Region -> Region -> Bool
$c>= :: Region -> Region -> Bool
>= :: Region -> Region -> Bool
$cmax :: Region -> Region -> Region
max :: Region -> Region -> Region
$cmin :: Region -> Region -> Region
min :: Region -> Region -> Region
Ord, Int -> Region -> ShowS
[Region] -> ShowS
Region -> String
(Int -> Region -> ShowS)
-> (Region -> String) -> ([Region] -> ShowS) -> Show Region
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Region -> ShowS
showsPrec :: Int -> Region -> ShowS
$cshow :: Region -> String
show :: Region -> String
$cshowList :: [Region] -> ShowS
showList :: [Region] -> ShowS
Show, ReadPrec [Region]
ReadPrec Region
Int -> ReadS Region
ReadS [Region]
(Int -> ReadS Region)
-> ReadS [Region]
-> ReadPrec Region
-> ReadPrec [Region]
-> Read Region
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Region
readsPrec :: Int -> ReadS Region
$creadList :: ReadS [Region]
readList :: ReadS [Region]
$creadPrec :: ReadPrec Region
readPrec :: ReadPrec Region
$creadListPrec :: ReadPrec [Region]
readListPrec :: ReadPrec [Region]
Read, String -> Region
(String -> Region) -> IsString Region
forall a. (String -> a) -> IsString a
$cfromString :: String -> Region
fromString :: String -> Region
IsString, Region -> ()
(Region -> ()) -> NFData Region
forall a. (a -> ()) -> NFData a
$crnf :: Region -> ()
rnf :: Region -> ()
NFData)
deriving stock (Typeable Region
Typeable Region =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Region -> c Region)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Region)
-> (Region -> Constr)
-> (Region -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Region))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region))
-> ((forall b. Data b => b -> b) -> Region -> Region)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Region -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Region -> r)
-> (forall u. (forall d. Data d => d -> u) -> Region -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Region -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Region -> m Region)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Region -> m Region)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Region -> m Region)
-> Data Region
Region -> Constr
Region -> DataType
(forall b. Data b => b -> b) -> Region -> Region
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Region -> u
forall u. (forall d. Data d => d -> u) -> Region -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Region -> m Region
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Region -> m Region
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Region
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Region -> c Region
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Region)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Region -> c Region
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Region -> c Region
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Region
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Region
$ctoConstr :: Region -> Constr
toConstr :: Region -> Constr
$cdataTypeOf :: Region -> DataType
dataTypeOf :: Region -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Region)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Region)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region)
$cgmapT :: (forall b. Data b => b -> b) -> Region -> Region
gmapT :: (forall b. Data b => b -> b) -> Region -> Region
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Region -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Region -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Region -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Region -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Region -> m Region
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Region -> m Region
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Region -> m Region
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Region -> m Region
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Region -> m Region
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Region -> m Region
Data, (forall x. Region -> Rep Region x)
-> (forall x. Rep Region x -> Region) -> Generic Region
forall x. Rep Region x -> Region
forall x. Region -> Rep Region x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Region -> Rep Region x
from :: forall x. Region -> Rep Region x
$cto :: forall x. Rep Region x -> Region
to :: forall x. Rep Region x -> Region
Generic)
data NonGeoRegion = Region001
deriving stock (NonGeoRegion -> NonGeoRegion -> Bool
(NonGeoRegion -> NonGeoRegion -> Bool)
-> (NonGeoRegion -> NonGeoRegion -> Bool) -> Eq NonGeoRegion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NonGeoRegion -> NonGeoRegion -> Bool
== :: NonGeoRegion -> NonGeoRegion -> Bool
$c/= :: NonGeoRegion -> NonGeoRegion -> Bool
/= :: NonGeoRegion -> NonGeoRegion -> Bool
Eq, Eq NonGeoRegion
Eq NonGeoRegion =>
(NonGeoRegion -> NonGeoRegion -> Ordering)
-> (NonGeoRegion -> NonGeoRegion -> Bool)
-> (NonGeoRegion -> NonGeoRegion -> Bool)
-> (NonGeoRegion -> NonGeoRegion -> Bool)
-> (NonGeoRegion -> NonGeoRegion -> Bool)
-> (NonGeoRegion -> NonGeoRegion -> NonGeoRegion)
-> (NonGeoRegion -> NonGeoRegion -> NonGeoRegion)
-> Ord NonGeoRegion
NonGeoRegion -> NonGeoRegion -> Bool
NonGeoRegion -> NonGeoRegion -> Ordering
NonGeoRegion -> NonGeoRegion -> NonGeoRegion
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 :: NonGeoRegion -> NonGeoRegion -> Ordering
compare :: NonGeoRegion -> NonGeoRegion -> Ordering
$c< :: NonGeoRegion -> NonGeoRegion -> Bool
< :: NonGeoRegion -> NonGeoRegion -> Bool
$c<= :: NonGeoRegion -> NonGeoRegion -> Bool
<= :: NonGeoRegion -> NonGeoRegion -> Bool
$c> :: NonGeoRegion -> NonGeoRegion -> Bool
> :: NonGeoRegion -> NonGeoRegion -> Bool
$c>= :: NonGeoRegion -> NonGeoRegion -> Bool
>= :: NonGeoRegion -> NonGeoRegion -> Bool
$cmax :: NonGeoRegion -> NonGeoRegion -> NonGeoRegion
max :: NonGeoRegion -> NonGeoRegion -> NonGeoRegion
$cmin :: NonGeoRegion -> NonGeoRegion -> NonGeoRegion
min :: NonGeoRegion -> NonGeoRegion -> NonGeoRegion
Ord, Int -> NonGeoRegion -> ShowS
[NonGeoRegion] -> ShowS
NonGeoRegion -> String
(Int -> NonGeoRegion -> ShowS)
-> (NonGeoRegion -> String)
-> ([NonGeoRegion] -> ShowS)
-> Show NonGeoRegion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NonGeoRegion -> ShowS
showsPrec :: Int -> NonGeoRegion -> ShowS
$cshow :: NonGeoRegion -> String
show :: NonGeoRegion -> String
$cshowList :: [NonGeoRegion] -> ShowS
showList :: [NonGeoRegion] -> ShowS
Show, ReadPrec [NonGeoRegion]
ReadPrec NonGeoRegion
Int -> ReadS NonGeoRegion
ReadS [NonGeoRegion]
(Int -> ReadS NonGeoRegion)
-> ReadS [NonGeoRegion]
-> ReadPrec NonGeoRegion
-> ReadPrec [NonGeoRegion]
-> Read NonGeoRegion
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NonGeoRegion
readsPrec :: Int -> ReadS NonGeoRegion
$creadList :: ReadS [NonGeoRegion]
readList :: ReadS [NonGeoRegion]
$creadPrec :: ReadPrec NonGeoRegion
readPrec :: ReadPrec NonGeoRegion
$creadListPrec :: ReadPrec [NonGeoRegion]
readListPrec :: ReadPrec [NonGeoRegion]
Read, Typeable NonGeoRegion
Typeable NonGeoRegion =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonGeoRegion -> c NonGeoRegion)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NonGeoRegion)
-> (NonGeoRegion -> Constr)
-> (NonGeoRegion -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NonGeoRegion))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NonGeoRegion))
-> ((forall b. Data b => b -> b) -> NonGeoRegion -> NonGeoRegion)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonGeoRegion -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonGeoRegion -> r)
-> (forall u. (forall d. Data d => d -> u) -> NonGeoRegion -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> NonGeoRegion -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NonGeoRegion -> m NonGeoRegion)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NonGeoRegion -> m NonGeoRegion)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NonGeoRegion -> m NonGeoRegion)
-> Data NonGeoRegion
NonGeoRegion -> Constr
NonGeoRegion -> DataType
(forall b. Data b => b -> b) -> NonGeoRegion -> NonGeoRegion
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> NonGeoRegion -> u
forall u. (forall d. Data d => d -> u) -> NonGeoRegion -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonGeoRegion -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonGeoRegion -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NonGeoRegion -> m NonGeoRegion
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NonGeoRegion -> m NonGeoRegion
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NonGeoRegion
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonGeoRegion -> c NonGeoRegion
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NonGeoRegion)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NonGeoRegion)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonGeoRegion -> c NonGeoRegion
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NonGeoRegion -> c NonGeoRegion
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NonGeoRegion
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NonGeoRegion
$ctoConstr :: NonGeoRegion -> Constr
toConstr :: NonGeoRegion -> Constr
$cdataTypeOf :: NonGeoRegion -> DataType
dataTypeOf :: NonGeoRegion -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NonGeoRegion)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NonGeoRegion)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NonGeoRegion)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NonGeoRegion)
$cgmapT :: (forall b. Data b => b -> b) -> NonGeoRegion -> NonGeoRegion
gmapT :: (forall b. Data b => b -> b) -> NonGeoRegion -> NonGeoRegion
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonGeoRegion -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NonGeoRegion -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonGeoRegion -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NonGeoRegion -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NonGeoRegion -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> NonGeoRegion -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NonGeoRegion -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NonGeoRegion -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NonGeoRegion -> m NonGeoRegion
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NonGeoRegion -> m NonGeoRegion
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NonGeoRegion -> m NonGeoRegion
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NonGeoRegion -> m NonGeoRegion
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NonGeoRegion -> m NonGeoRegion
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NonGeoRegion -> m NonGeoRegion
Data, (forall x. NonGeoRegion -> Rep NonGeoRegion x)
-> (forall x. Rep NonGeoRegion x -> NonGeoRegion)
-> Generic NonGeoRegion
forall x. Rep NonGeoRegion x -> NonGeoRegion
forall x. NonGeoRegion -> Rep NonGeoRegion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NonGeoRegion -> Rep NonGeoRegion x
from :: forall x. NonGeoRegion -> Rep NonGeoRegion x
$cto :: forall x. Rep NonGeoRegion x -> NonGeoRegion
to :: forall x. Rep NonGeoRegion x -> NonGeoRegion
Generic)
deriving anyclass (NonGeoRegion -> ()
(NonGeoRegion -> ()) -> NFData NonGeoRegion
forall a. (a -> ()) -> NFData a
$crnf :: NonGeoRegion -> ()
rnf :: NonGeoRegion -> ()
NFData)
filter001 :: ByteString -> Either NonGeoRegion Region
filter001 :: ByteString -> Either NonGeoRegion Region
filter001 ByteString
region
| ByteString
region ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
"001" = NonGeoRegion -> Either NonGeoRegion Region
forall a b. a -> Either a b
Left NonGeoRegion
Region001
| Bool
otherwise = Region -> Either NonGeoRegion Region
forall a b. b -> Either a b
Right (Region -> Either NonGeoRegion Region)
-> Region -> Either NonGeoRegion Region
forall a b. (a -> b) -> a -> b
$ ByteString -> Region
Region ByteString
region
filter001ZZ :: ByteString -> Maybe (Either NonGeoRegion Region)
filter001ZZ :: ByteString -> Maybe (Either NonGeoRegion Region)
filter001ZZ ByteString
region
| ByteString
region ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
"ZZ" = Maybe (Either NonGeoRegion Region)
forall a. Maybe a
Nothing
| ByteString
region ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
"001" = Either NonGeoRegion Region -> Maybe (Either NonGeoRegion Region)
forall a. a -> Maybe a
Just (Either NonGeoRegion Region -> Maybe (Either NonGeoRegion Region))
-> Either NonGeoRegion Region -> Maybe (Either NonGeoRegion Region)
forall a b. (a -> b) -> a -> b
$ NonGeoRegion -> Either NonGeoRegion Region
forall a b. a -> Either a b
Left NonGeoRegion
Region001
| Bool
otherwise = Either NonGeoRegion Region -> Maybe (Either NonGeoRegion Region)
forall a. a -> Maybe a
Just (Either NonGeoRegion Region -> Maybe (Either NonGeoRegion Region))
-> Either NonGeoRegion Region -> Maybe (Either NonGeoRegion Region)
forall a b. (a -> b) -> a -> b
$ Region -> Either NonGeoRegion Region
forall a b. b -> Either a b
Right (Region -> Either NonGeoRegion Region)
-> Region -> Either NonGeoRegion Region
forall a b. (a -> b) -> a -> b
$ ByteString -> Region
Region ByteString
region
filter0 :: Int -> Maybe CountryCode
filter0 :: Int -> Maybe CountryCode
filter0 Int
0 = Maybe CountryCode
forall a. Maybe a
Nothing
filter0 Int
cc = CountryCode -> Maybe CountryCode
forall a. a -> Maybe a
Just (CountryCode -> Maybe CountryCode)
-> CountryCode -> Maybe CountryCode
forall a b. (a -> b) -> a -> b
$ Int -> CountryCode
CountryCode Int
cc
supportedRegions :: S.Set Region
supportedRegions :: Set Region
supportedRegions = [Region] -> Set Region
forall a. Ord a => [a] -> Set a
S.fromList ([Region] -> Set Region) -> [Region] -> Set Region
forall a b. (a -> b) -> a -> b
$ IO [Region] -> [Region]
forall a. IO a -> a
unsafeDupablePerformIO (IO [Region] -> [Region]) -> IO [Region] -> [Region]
forall a b. (a -> b) -> a -> b
$ IO [Region] -> IO [Region]
forall a. IO a -> IO a
mask_ (IO [Region] -> IO [Region]) -> IO [Region] -> IO [Region]
forall a b. (a -> b) -> a -> b
$
IO [ByteString] -> IO [Region]
forall a b. Coercible a b => a -> b
coerce IO [ByteString]
c_phone_number_util_get_supported_regions
supportedGlobalNetworkCallingCodes :: S.Set CountryCode
supportedGlobalNetworkCallingCodes :: Set CountryCode
supportedGlobalNetworkCallingCodes = [CountryCode] -> Set CountryCode
forall a. Ord a => [a] -> Set a
S.fromList ([CountryCode] -> Set CountryCode)
-> [CountryCode] -> Set CountryCode
forall a b. (a -> b) -> a -> b
$ (CInt -> CountryCode) -> [CInt] -> [CountryCode]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> CountryCode
CountryCode (Int -> CountryCode) -> (CInt -> Int) -> CInt -> CountryCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) ([CInt] -> [CountryCode]) -> [CInt] -> [CountryCode]
forall a b. (a -> b) -> a -> b
$
IO [CInt] -> [CInt]
forall a. IO a -> a
unsafeDupablePerformIO (IO [CInt] -> [CInt]) -> IO [CInt] -> [CInt]
forall a b. (a -> b) -> a -> b
$ IO [CInt] -> IO [CInt]
forall a. IO a -> IO a
mask_ (IO [CInt] -> IO [CInt]) -> IO [CInt] -> IO [CInt]
forall a b. (a -> b) -> a -> b
$
IO [CInt]
c_phone_number_util_get_supported_global_network_calling_codes
supportedCallingCodes :: S.Set CountryCode
supportedCallingCodes :: Set CountryCode
supportedCallingCodes = [CountryCode] -> Set CountryCode
forall a. Ord a => [a] -> Set a
S.fromList ([CountryCode] -> Set CountryCode)
-> [CountryCode] -> Set CountryCode
forall a b. (a -> b) -> a -> b
$ (CInt -> CountryCode) -> [CInt] -> [CountryCode]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> CountryCode
CountryCode (Int -> CountryCode) -> (CInt -> Int) -> CInt -> CountryCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) ([CInt] -> [CountryCode]) -> [CInt] -> [CountryCode]
forall a b. (a -> b) -> a -> b
$
IO [CInt] -> [CInt]
forall a. IO a -> a
unsafeDupablePerformIO (IO [CInt] -> [CInt]) -> IO [CInt] -> [CInt]
forall a b. (a -> b) -> a -> b
$ IO [CInt] -> IO [CInt]
forall a. IO a -> IO a
mask_ (IO [CInt] -> IO [CInt]) -> IO [CInt] -> IO [CInt]
forall a b. (a -> b) -> a -> b
$
IO [CInt]
c_phone_number_util_get_supported_calling_codes
supportedTypesForRegion :: Region -> S.Set PhoneNumberType
supportedTypesForRegion :: Region -> Set PhoneNumberType
supportedTypesForRegion (Region ByteString
region) = [PhoneNumberType] -> Set PhoneNumberType
forall a. Ord a => [a] -> Set a
S.fromList ([PhoneNumberType] -> Set PhoneNumberType)
-> [PhoneNumberType] -> Set PhoneNumberType
forall a b. (a -> b) -> a -> b
$
IO [PhoneNumberType] -> [PhoneNumberType]
forall a. IO a -> a
unsafeDupablePerformIO (IO [PhoneNumberType] -> [PhoneNumberType])
-> IO [PhoneNumberType] -> [PhoneNumberType]
forall a b. (a -> b) -> a -> b
$ IO [PhoneNumberType] -> IO [PhoneNumberType]
forall a. IO a -> IO a
mask_ (IO [PhoneNumberType] -> IO [PhoneNumberType])
-> IO [PhoneNumberType] -> IO [PhoneNumberType]
forall a b. (a -> b) -> a -> b
$
ByteString -> IO [PhoneNumberType]
c_phone_number_util_get_supported_types_for_region ByteString
region
supportedTypesForNonGeoEntity :: CountryCode -> S.Set PhoneNumberType
supportedTypesForNonGeoEntity :: CountryCode -> Set PhoneNumberType
supportedTypesForNonGeoEntity (CountryCode Int
cc) = [PhoneNumberType] -> Set PhoneNumberType
forall a. Ord a => [a] -> Set a
S.fromList ([PhoneNumberType] -> Set PhoneNumberType)
-> [PhoneNumberType] -> Set PhoneNumberType
forall a b. (a -> b) -> a -> b
$
IO [PhoneNumberType] -> [PhoneNumberType]
forall a. IO a -> a
unsafeDupablePerformIO (IO [PhoneNumberType] -> [PhoneNumberType])
-> IO [PhoneNumberType] -> [PhoneNumberType]
forall a b. (a -> b) -> a -> b
$ IO [PhoneNumberType] -> IO [PhoneNumberType]
forall a. IO a -> IO a
mask_ (IO [PhoneNumberType] -> IO [PhoneNumberType])
-> IO [PhoneNumberType] -> IO [PhoneNumberType]
forall a b. (a -> b) -> a -> b
$
CInt -> IO [PhoneNumberType]
c_phone_number_util_get_supported_types_for_non_geo_entity (CInt -> IO [PhoneNumberType]) -> CInt -> IO [PhoneNumberType]
forall a b. (a -> b) -> a -> b
$ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
cc
isAlphaNumber :: ByteString -> Bool
isAlphaNumber :: ByteString -> Bool
isAlphaNumber ByteString
bs = IO Bool -> Bool
forall a. IO a -> a
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
ByteString -> IO Bool
c_phone_number_util_is_alpha_number ByteString
bs
convertAlphaNumber :: ByteString -> ByteString
convertAlphaNumber :: ByteString -> ByteString
convertAlphaNumber ByteString
bs = IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
ByteString -> IO ByteString
c_phone_number_util_convert_alpha_characters_in_number ByteString
bs
data Normalize
= Digits
| Dialable
deriving stock (Normalize -> Normalize -> Bool
(Normalize -> Normalize -> Bool)
-> (Normalize -> Normalize -> Bool) -> Eq Normalize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Normalize -> Normalize -> Bool
== :: Normalize -> Normalize -> Bool
$c/= :: Normalize -> Normalize -> Bool
/= :: Normalize -> Normalize -> Bool
Eq, Eq Normalize
Eq Normalize =>
(Normalize -> Normalize -> Ordering)
-> (Normalize -> Normalize -> Bool)
-> (Normalize -> Normalize -> Bool)
-> (Normalize -> Normalize -> Bool)
-> (Normalize -> Normalize -> Bool)
-> (Normalize -> Normalize -> Normalize)
-> (Normalize -> Normalize -> Normalize)
-> Ord Normalize
Normalize -> Normalize -> Bool
Normalize -> Normalize -> Ordering
Normalize -> Normalize -> Normalize
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 :: Normalize -> Normalize -> Ordering
compare :: Normalize -> Normalize -> Ordering
$c< :: Normalize -> Normalize -> Bool
< :: Normalize -> Normalize -> Bool
$c<= :: Normalize -> Normalize -> Bool
<= :: Normalize -> Normalize -> Bool
$c> :: Normalize -> Normalize -> Bool
> :: Normalize -> Normalize -> Bool
$c>= :: Normalize -> Normalize -> Bool
>= :: Normalize -> Normalize -> Bool
$cmax :: Normalize -> Normalize -> Normalize
max :: Normalize -> Normalize -> Normalize
$cmin :: Normalize -> Normalize -> Normalize
min :: Normalize -> Normalize -> Normalize
Ord, Int -> Normalize -> ShowS
[Normalize] -> ShowS
Normalize -> String
(Int -> Normalize -> ShowS)
-> (Normalize -> String)
-> ([Normalize] -> ShowS)
-> Show Normalize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Normalize -> ShowS
showsPrec :: Int -> Normalize -> ShowS
$cshow :: Normalize -> String
show :: Normalize -> String
$cshowList :: [Normalize] -> ShowS
showList :: [Normalize] -> ShowS
Show, ReadPrec [Normalize]
ReadPrec Normalize
Int -> ReadS Normalize
ReadS [Normalize]
(Int -> ReadS Normalize)
-> ReadS [Normalize]
-> ReadPrec Normalize
-> ReadPrec [Normalize]
-> Read Normalize
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Normalize
readsPrec :: Int -> ReadS Normalize
$creadList :: ReadS [Normalize]
readList :: ReadS [Normalize]
$creadPrec :: ReadPrec Normalize
readPrec :: ReadPrec Normalize
$creadListPrec :: ReadPrec [Normalize]
readListPrec :: ReadPrec [Normalize]
Read, Typeable Normalize
Typeable Normalize =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Normalize -> c Normalize)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Normalize)
-> (Normalize -> Constr)
-> (Normalize -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Normalize))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Normalize))
-> ((forall b. Data b => b -> b) -> Normalize -> Normalize)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Normalize -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Normalize -> r)
-> (forall u. (forall d. Data d => d -> u) -> Normalize -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Normalize -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Normalize -> m Normalize)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Normalize -> m Normalize)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Normalize -> m Normalize)
-> Data Normalize
Normalize -> Constr
Normalize -> DataType
(forall b. Data b => b -> b) -> Normalize -> Normalize
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Normalize -> u
forall u. (forall d. Data d => d -> u) -> Normalize -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Normalize -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Normalize -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Normalize -> m Normalize
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Normalize -> m Normalize
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Normalize
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Normalize -> c Normalize
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Normalize)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Normalize)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Normalize -> c Normalize
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Normalize -> c Normalize
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Normalize
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Normalize
$ctoConstr :: Normalize -> Constr
toConstr :: Normalize -> Constr
$cdataTypeOf :: Normalize -> DataType
dataTypeOf :: Normalize -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Normalize)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Normalize)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Normalize)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Normalize)
$cgmapT :: (forall b. Data b => b -> b) -> Normalize -> Normalize
gmapT :: (forall b. Data b => b -> b) -> Normalize -> Normalize
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Normalize -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Normalize -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Normalize -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Normalize -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Normalize -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Normalize -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Normalize -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Normalize -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Normalize -> m Normalize
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Normalize -> m Normalize
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Normalize -> m Normalize
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Normalize -> m Normalize
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Normalize -> m Normalize
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Normalize -> m Normalize
Data, (forall x. Normalize -> Rep Normalize x)
-> (forall x. Rep Normalize x -> Normalize) -> Generic Normalize
forall x. Rep Normalize x -> Normalize
forall x. Normalize -> Rep Normalize x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Normalize -> Rep Normalize x
from :: forall x. Normalize -> Rep Normalize x
$cto :: forall x. Rep Normalize x -> Normalize
to :: forall x. Rep Normalize x -> Normalize
Generic)
deriving anyclass (Normalize -> ()
(Normalize -> ()) -> NFData Normalize
forall a. (a -> ()) -> NFData a
$crnf :: Normalize -> ()
rnf :: Normalize -> ()
NFData)
normalizeNumber :: Normalize -> ByteString -> ByteString
normalizeNumber :: Normalize -> ByteString -> ByteString
normalizeNumber Normalize
Digits ByteString
bs = IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
ByteString -> IO ByteString
c_phone_number_util_normalize_digits_only ByteString
bs
normalizeNumber Normalize
Dialable ByteString
bs = IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
ByteString -> IO ByteString
c_phone_number_util_normalize_dialable_chars_only ByteString
bs
nationalSignificantNumber :: PhoneNumber -> ByteString
nationalSignificantNumber :: PhoneNumber -> ByteString
nationalSignificantNumber PhoneNumber
pn = IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> IO ByteString
c_phone_number_util_get_national_significant_number PhoneNumber
pn
countryMobileToken :: CountryCode -> ByteString
countryMobileToken :: CountryCode -> ByteString
countryMobileToken (CountryCode Int
cc) = IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
CInt -> IO ByteString
c_phone_number_util_get_country_mobile_token (CInt -> IO ByteString) -> CInt -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
cc
data PhoneNumberFormat
= International
| National
| E164
| RFC3966
| NationalWithCarrierCodeOverride ByteString
| NationalWithCarrierCodeFallback ByteString
| ForMobileDialing
{ PhoneNumberFormat -> Region
from :: Region
, PhoneNumberFormat -> Bool
withFormatting :: Bool
}
| OutOfCountry
{ from :: Region
, PhoneNumberFormat -> Bool
keepAlphaChars :: Bool
}
| Original
{ from :: Region
}
formatNumber :: PhoneNumberFormat -> PhoneNumber -> ByteString
formatNumber :: PhoneNumberFormat -> PhoneNumber -> ByteString
formatNumber PhoneNumberFormat
fmt PhoneNumber
pn = case PhoneNumberFormat
fmt of
PhoneNumberFormat
E164 -> IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> PhoneNumberFormat -> IO ByteString
c_phone_number_util_format PhoneNumber
pn PhoneNumberFormat
I.E164
PhoneNumberFormat
International -> IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> PhoneNumberFormat -> IO ByteString
c_phone_number_util_format PhoneNumber
pn PhoneNumberFormat
I.International
PhoneNumberFormat
National -> IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> PhoneNumberFormat -> IO ByteString
c_phone_number_util_format PhoneNumber
pn PhoneNumberFormat
I.National
PhoneNumberFormat
RFC3966 -> IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> PhoneNumberFormat -> IO ByteString
c_phone_number_util_format PhoneNumber
pn PhoneNumberFormat
I.Rfc3966
NationalWithCarrierCodeOverride ByteString
cc -> IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> ByteString -> IO ByteString
c_phone_number_util_format_national_number_with_carrier_code PhoneNumber
pn ByteString
cc
NationalWithCarrierCodeFallback ByteString
cc -> IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> ByteString -> IO ByteString
c_phone_number_util_format_national_number_with_preferred_carrier_code PhoneNumber
pn ByteString
cc
ForMobileDialing (Region ByteString
region) Bool
keepFmt -> IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> ByteString -> Bool -> IO ByteString
c_phone_number_util_format_number_for_mobile_dialing PhoneNumber
pn ByteString
region Bool
keepFmt
Original (Region ByteString
region) -> IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> ByteString -> IO ByteString
c_phone_number_util_format_in_original_format PhoneNumber
pn ByteString
region
OutOfCountry (Region ByteString
region) Bool
False -> IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> ByteString -> IO ByteString
c_phone_number_util_format_out_of_country_calling_number PhoneNumber
pn ByteString
region
OutOfCountry (Region ByteString
region) Bool
True -> IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> ByteString -> IO ByteString
c_phone_number_util_format_out_of_country_keeping_alpha_chars PhoneNumber
pn ByteString
region
truncateTooLongNumber :: PhoneNumber -> Maybe PhoneNumber
truncateTooLongNumber :: PhoneNumber -> Maybe PhoneNumber
truncateTooLongNumber PhoneNumber
pn = IO (Maybe PhoneNumber) -> Maybe PhoneNumber
forall a. IO a -> a
unsafeDupablePerformIO (IO (Maybe PhoneNumber) -> Maybe PhoneNumber)
-> IO (Maybe PhoneNumber) -> Maybe PhoneNumber
forall a b. (a -> b) -> a -> b
$ IO (Maybe PhoneNumber) -> IO (Maybe PhoneNumber)
forall a. IO a -> IO a
mask_ (IO (Maybe PhoneNumber) -> IO (Maybe PhoneNumber))
-> IO (Maybe PhoneNumber) -> IO (Maybe PhoneNumber)
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> IO (Maybe PhoneNumber)
c_phone_number_util_truncate_too_long_number PhoneNumber
pn
numberType :: PhoneNumber -> PhoneNumberType
numberType :: PhoneNumber -> PhoneNumberType
numberType PhoneNumber
pn = IO PhoneNumberType -> PhoneNumberType
forall a. IO a -> a
unsafeDupablePerformIO (IO PhoneNumberType -> PhoneNumberType)
-> IO PhoneNumberType -> PhoneNumberType
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> IO PhoneNumberType
c_phone_number_util_get_number_type PhoneNumber
pn
isValidNumber :: Maybe (Either NonGeoRegion Region) -> PhoneNumber -> Bool
isValidNumber :: Maybe (Either NonGeoRegion Region) -> PhoneNumber -> Bool
isValidNumber Maybe (Either NonGeoRegion Region)
Nothing PhoneNumber
pn = IO Bool -> Bool
forall a. IO a -> a
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> IO Bool
c_phone_number_util_is_valid_number PhoneNumber
pn
isValidNumber (Just (Left NonGeoRegion
Region001)) PhoneNumber
pn = IO Bool -> Bool
forall a. IO a -> a
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> ByteString -> IO Bool
c_phone_number_util_is_valid_number_for_region PhoneNumber
pn ByteString
"001"
isValidNumber (Just (Right (Region ByteString
region))) PhoneNumber
pn = IO Bool -> Bool
forall a. IO a -> a
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> ByteString -> IO Bool
c_phone_number_util_is_valid_number_for_region PhoneNumber
pn ByteString
region
regionForNumber :: PhoneNumber -> Maybe (Either NonGeoRegion Region)
regionForNumber :: PhoneNumber -> Maybe (Either NonGeoRegion Region)
regionForNumber PhoneNumber
pn = ByteString -> Maybe (Either NonGeoRegion Region)
filter001ZZ (ByteString -> Maybe (Either NonGeoRegion Region))
-> ByteString -> Maybe (Either NonGeoRegion Region)
forall a b. (a -> b) -> a -> b
$
IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> IO ByteString
c_phone_number_util_get_region_code_for_number PhoneNumber
pn
countryCodeForRegion :: Region -> Maybe CountryCode
countryCodeForRegion :: Region -> Maybe CountryCode
countryCodeForRegion (Region ByteString
region) = Int -> Maybe CountryCode
filter0 (Int -> Maybe CountryCode) -> Int -> Maybe CountryCode
forall a b. (a -> b) -> a -> b
$ CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> CInt -> Int
forall a b. (a -> b) -> a -> b
$
IO CInt -> CInt
forall a. IO a -> a
unsafeDupablePerformIO (IO CInt -> CInt) -> IO CInt -> CInt
forall a b. (a -> b) -> a -> b
$
ByteString -> IO CInt
c_phone_number_util_get_country_code_for_region ByteString
region
regionForCountryCode :: CountryCode -> Maybe (Either NonGeoRegion Region)
regionForCountryCode :: CountryCode -> Maybe (Either NonGeoRegion Region)
regionForCountryCode (CountryCode Int
cc) = ByteString -> Maybe (Either NonGeoRegion Region)
filter001ZZ (ByteString -> Maybe (Either NonGeoRegion Region))
-> ByteString -> Maybe (Either NonGeoRegion Region)
forall a b. (a -> b) -> a -> b
$
IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
Int -> IO ByteString
c_phone_number_util_get_region_code_for_country_code (Int -> IO ByteString) -> Int -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
cc
regionsForCountryCode :: CountryCode -> [Either NonGeoRegion Region]
regionsForCountryCode :: CountryCode -> [Either NonGeoRegion Region]
regionsForCountryCode (CountryCode Int
cc) = (ByteString -> Either NonGeoRegion Region)
-> [ByteString] -> [Either NonGeoRegion Region]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> Either NonGeoRegion Region
filter001 ([ByteString] -> [Either NonGeoRegion Region])
-> [ByteString] -> [Either NonGeoRegion Region]
forall a b. (a -> b) -> a -> b
$
IO [ByteString] -> [ByteString]
forall a. IO a -> a
unsafeDupablePerformIO (IO [ByteString] -> [ByteString])
-> IO [ByteString] -> [ByteString]
forall a b. (a -> b) -> a -> b
$ IO [ByteString] -> IO [ByteString]
forall a. IO a -> IO a
mask_ (IO [ByteString] -> IO [ByteString])
-> IO [ByteString] -> IO [ByteString]
forall a b. (a -> b) -> a -> b
$
Int -> IO [ByteString]
c_phone_number_util_get_region_codes_for_country_calling_code (Int -> IO [ByteString]) -> Int -> IO [ByteString]
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
cc
isNANPACountry :: Region -> Bool
isNANPACountry :: Region -> Bool
isNANPACountry (Region ByteString
region) = IO Bool -> Bool
forall a. IO a -> a
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
ByteString -> IO Bool
c_phone_number_util_is_nanpa_country ByteString
region
nddPrefixForRegion
:: Bool
-> Region
-> ByteString
nddPrefixForRegion :: Bool -> Region -> ByteString
nddPrefixForRegion Bool
strip (Region ByteString
region) = IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO ByteString
forall a. IO a -> IO a
mask_ (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$
ByteString -> Bool -> IO ByteString
c_phone_number_util_get_ndd_prefix_for_region ByteString
region Bool
strip
possibleNumber :: PhoneNumberType -> PhoneNumber -> ValidationResult
possibleNumber :: PhoneNumberType -> PhoneNumber -> ValidationResult
possibleNumber PhoneNumberType
ntype PhoneNumber
pn = IO ValidationResult -> ValidationResult
forall a. IO a -> a
unsafeDupablePerformIO (IO ValidationResult -> ValidationResult)
-> IO ValidationResult -> ValidationResult
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> PhoneNumberType -> IO ValidationResult
c_phone_number_util_is_possible_number_for_type_with_reason PhoneNumber
pn PhoneNumberType
ntype
canBeInternationallyDialed :: PhoneNumber -> Bool
canBeInternationallyDialed :: PhoneNumber -> Bool
canBeInternationallyDialed PhoneNumber
pn = IO Bool -> Bool
forall a. IO a -> a
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> IO Bool
c_phone_number_util_can_be_internationally_dialed PhoneNumber
pn
isGeographicalNumber :: PhoneNumber -> Bool
isGeographicalNumber :: PhoneNumber -> Bool
isGeographicalNumber PhoneNumber
pn = IO Bool -> Bool
forall a. IO a -> a
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> IO Bool
c_phone_number_util_is_number_geographical_1 PhoneNumber
pn
isGeographicalNumberType :: PhoneNumberType -> CountryCode -> Bool
isGeographicalNumberType :: PhoneNumberType -> CountryCode -> Bool
isGeographicalNumberType PhoneNumberType
ntype (CountryCode Int
cc) = IO Bool -> Bool
forall a. IO a -> a
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$
PhoneNumberType -> CInt -> IO Bool
c_phone_number_util_is_number_geographical_2 PhoneNumberType
ntype (CInt -> IO Bool) -> CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
cc
data ErrorType
= InvalidCountryCodeError
| NotANumber
| TooShortAfterIdd
| TooShortNsn
| TooLongNsn
deriving stock (ErrorType -> ErrorType -> Bool
(ErrorType -> ErrorType -> Bool)
-> (ErrorType -> ErrorType -> Bool) -> Eq ErrorType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ErrorType -> ErrorType -> Bool
== :: ErrorType -> ErrorType -> Bool
$c/= :: ErrorType -> ErrorType -> Bool
/= :: ErrorType -> ErrorType -> Bool
Eq, Eq ErrorType
Eq ErrorType =>
(ErrorType -> ErrorType -> Ordering)
-> (ErrorType -> ErrorType -> Bool)
-> (ErrorType -> ErrorType -> Bool)
-> (ErrorType -> ErrorType -> Bool)
-> (ErrorType -> ErrorType -> Bool)
-> (ErrorType -> ErrorType -> ErrorType)
-> (ErrorType -> ErrorType -> ErrorType)
-> Ord ErrorType
ErrorType -> ErrorType -> Bool
ErrorType -> ErrorType -> Ordering
ErrorType -> ErrorType -> ErrorType
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 :: ErrorType -> ErrorType -> Ordering
compare :: ErrorType -> ErrorType -> Ordering
$c< :: ErrorType -> ErrorType -> Bool
< :: ErrorType -> ErrorType -> Bool
$c<= :: ErrorType -> ErrorType -> Bool
<= :: ErrorType -> ErrorType -> Bool
$c> :: ErrorType -> ErrorType -> Bool
> :: ErrorType -> ErrorType -> Bool
$c>= :: ErrorType -> ErrorType -> Bool
>= :: ErrorType -> ErrorType -> Bool
$cmax :: ErrorType -> ErrorType -> ErrorType
max :: ErrorType -> ErrorType -> ErrorType
$cmin :: ErrorType -> ErrorType -> ErrorType
min :: ErrorType -> ErrorType -> ErrorType
Ord, Int -> ErrorType -> ShowS
[ErrorType] -> ShowS
ErrorType -> String
(Int -> ErrorType -> ShowS)
-> (ErrorType -> String)
-> ([ErrorType] -> ShowS)
-> Show ErrorType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ErrorType -> ShowS
showsPrec :: Int -> ErrorType -> ShowS
$cshow :: ErrorType -> String
show :: ErrorType -> String
$cshowList :: [ErrorType] -> ShowS
showList :: [ErrorType] -> ShowS
Show, ReadPrec [ErrorType]
ReadPrec ErrorType
Int -> ReadS ErrorType
ReadS [ErrorType]
(Int -> ReadS ErrorType)
-> ReadS [ErrorType]
-> ReadPrec ErrorType
-> ReadPrec [ErrorType]
-> Read ErrorType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ErrorType
readsPrec :: Int -> ReadS ErrorType
$creadList :: ReadS [ErrorType]
readList :: ReadS [ErrorType]
$creadPrec :: ReadPrec ErrorType
readPrec :: ReadPrec ErrorType
$creadListPrec :: ReadPrec [ErrorType]
readListPrec :: ReadPrec [ErrorType]
Read, Typeable ErrorType
Typeable ErrorType =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ErrorType -> c ErrorType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ErrorType)
-> (ErrorType -> Constr)
-> (ErrorType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ErrorType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ErrorType))
-> ((forall b. Data b => b -> b) -> ErrorType -> ErrorType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorType -> r)
-> (forall u. (forall d. Data d => d -> u) -> ErrorType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ErrorType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ErrorType -> m ErrorType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorType -> m ErrorType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorType -> m ErrorType)
-> Data ErrorType
ErrorType -> Constr
ErrorType -> DataType
(forall b. Data b => b -> b) -> ErrorType -> ErrorType
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ErrorType -> u
forall u. (forall d. Data d => d -> u) -> ErrorType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ErrorType -> m ErrorType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorType -> m ErrorType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ErrorType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ErrorType -> c ErrorType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ErrorType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ErrorType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ErrorType -> c ErrorType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ErrorType -> c ErrorType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ErrorType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ErrorType
$ctoConstr :: ErrorType -> Constr
toConstr :: ErrorType -> Constr
$cdataTypeOf :: ErrorType -> DataType
dataTypeOf :: ErrorType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ErrorType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ErrorType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ErrorType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ErrorType)
$cgmapT :: (forall b. Data b => b -> b) -> ErrorType -> ErrorType
gmapT :: (forall b. Data b => b -> b) -> ErrorType -> ErrorType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ErrorType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ErrorType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ErrorType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ErrorType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ErrorType -> m ErrorType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ErrorType -> m ErrorType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorType -> m ErrorType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorType -> m ErrorType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorType -> m ErrorType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorType -> m ErrorType
Data, (forall x. ErrorType -> Rep ErrorType x)
-> (forall x. Rep ErrorType x -> ErrorType) -> Generic ErrorType
forall x. Rep ErrorType x -> ErrorType
forall x. ErrorType -> Rep ErrorType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ErrorType -> Rep ErrorType x
from :: forall x. ErrorType -> Rep ErrorType x
$cto :: forall x. Rep ErrorType x -> ErrorType
to :: forall x. Rep ErrorType x -> ErrorType
Generic)
deriving anyclass (ErrorType -> ()
(ErrorType -> ()) -> NFData ErrorType
forall a. (a -> ()) -> NFData a
$crnf :: ErrorType -> ()
rnf :: ErrorType -> ()
NFData)
data ParseMode
= Canonicalize
| KeepRawInput
deriving stock (ParseMode -> ParseMode -> Bool
(ParseMode -> ParseMode -> Bool)
-> (ParseMode -> ParseMode -> Bool) -> Eq ParseMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParseMode -> ParseMode -> Bool
== :: ParseMode -> ParseMode -> Bool
$c/= :: ParseMode -> ParseMode -> Bool
/= :: ParseMode -> ParseMode -> Bool
Eq, Eq ParseMode
Eq ParseMode =>
(ParseMode -> ParseMode -> Ordering)
-> (ParseMode -> ParseMode -> Bool)
-> (ParseMode -> ParseMode -> Bool)
-> (ParseMode -> ParseMode -> Bool)
-> (ParseMode -> ParseMode -> Bool)
-> (ParseMode -> ParseMode -> ParseMode)
-> (ParseMode -> ParseMode -> ParseMode)
-> Ord ParseMode
ParseMode -> ParseMode -> Bool
ParseMode -> ParseMode -> Ordering
ParseMode -> ParseMode -> ParseMode
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 :: ParseMode -> ParseMode -> Ordering
compare :: ParseMode -> ParseMode -> Ordering
$c< :: ParseMode -> ParseMode -> Bool
< :: ParseMode -> ParseMode -> Bool
$c<= :: ParseMode -> ParseMode -> Bool
<= :: ParseMode -> ParseMode -> Bool
$c> :: ParseMode -> ParseMode -> Bool
> :: ParseMode -> ParseMode -> Bool
$c>= :: ParseMode -> ParseMode -> Bool
>= :: ParseMode -> ParseMode -> Bool
$cmax :: ParseMode -> ParseMode -> ParseMode
max :: ParseMode -> ParseMode -> ParseMode
$cmin :: ParseMode -> ParseMode -> ParseMode
min :: ParseMode -> ParseMode -> ParseMode
Ord, Int -> ParseMode -> ShowS
[ParseMode] -> ShowS
ParseMode -> String
(Int -> ParseMode -> ShowS)
-> (ParseMode -> String)
-> ([ParseMode] -> ShowS)
-> Show ParseMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParseMode -> ShowS
showsPrec :: Int -> ParseMode -> ShowS
$cshow :: ParseMode -> String
show :: ParseMode -> String
$cshowList :: [ParseMode] -> ShowS
showList :: [ParseMode] -> ShowS
Show, ReadPrec [ParseMode]
ReadPrec ParseMode
Int -> ReadS ParseMode
ReadS [ParseMode]
(Int -> ReadS ParseMode)
-> ReadS [ParseMode]
-> ReadPrec ParseMode
-> ReadPrec [ParseMode]
-> Read ParseMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ParseMode
readsPrec :: Int -> ReadS ParseMode
$creadList :: ReadS [ParseMode]
readList :: ReadS [ParseMode]
$creadPrec :: ReadPrec ParseMode
readPrec :: ReadPrec ParseMode
$creadListPrec :: ReadPrec [ParseMode]
readListPrec :: ReadPrec [ParseMode]
Read, Typeable ParseMode
Typeable ParseMode =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParseMode -> c ParseMode)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParseMode)
-> (ParseMode -> Constr)
-> (ParseMode -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParseMode))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParseMode))
-> ((forall b. Data b => b -> b) -> ParseMode -> ParseMode)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParseMode -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParseMode -> r)
-> (forall u. (forall d. Data d => d -> u) -> ParseMode -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ParseMode -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ParseMode -> m ParseMode)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParseMode -> m ParseMode)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParseMode -> m ParseMode)
-> Data ParseMode
ParseMode -> Constr
ParseMode -> DataType
(forall b. Data b => b -> b) -> ParseMode -> ParseMode
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ParseMode -> u
forall u. (forall d. Data d => d -> u) -> ParseMode -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParseMode -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParseMode -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ParseMode -> m ParseMode
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParseMode -> m ParseMode
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParseMode
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParseMode -> c ParseMode
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParseMode)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParseMode)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParseMode -> c ParseMode
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParseMode -> c ParseMode
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParseMode
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParseMode
$ctoConstr :: ParseMode -> Constr
toConstr :: ParseMode -> Constr
$cdataTypeOf :: ParseMode -> DataType
dataTypeOf :: ParseMode -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParseMode)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParseMode)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParseMode)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParseMode)
$cgmapT :: (forall b. Data b => b -> b) -> ParseMode -> ParseMode
gmapT :: (forall b. Data b => b -> b) -> ParseMode -> ParseMode
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParseMode -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParseMode -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParseMode -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParseMode -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ParseMode -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ParseMode -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ParseMode -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ParseMode -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ParseMode -> m ParseMode
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ParseMode -> m ParseMode
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParseMode -> m ParseMode
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParseMode -> m ParseMode
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParseMode -> m ParseMode
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParseMode -> m ParseMode
Data, (forall x. ParseMode -> Rep ParseMode x)
-> (forall x. Rep ParseMode x -> ParseMode) -> Generic ParseMode
forall x. Rep ParseMode x -> ParseMode
forall x. ParseMode -> Rep ParseMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ParseMode -> Rep ParseMode x
from :: forall x. ParseMode -> Rep ParseMode x
$cto :: forall x. Rep ParseMode x -> ParseMode
to :: forall x. Rep ParseMode x -> ParseMode
Generic)
deriving anyclass (ParseMode -> ()
(ParseMode -> ()) -> NFData ParseMode
forall a. (a -> ()) -> NFData a
$crnf :: ParseMode -> ()
rnf :: ParseMode -> ()
NFData)
parseNumber
:: ParseMode
-> Maybe Region
-> ByteString
-> Either ErrorType PhoneNumber
parseNumber :: ParseMode
-> Maybe Region -> ByteString -> Either ErrorType PhoneNumber
parseNumber ParseMode
mode Maybe Region
mRegion ByteString
number = case ErrorType
err of
ErrorType
I.NoParsingError -> PhoneNumber -> Either ErrorType PhoneNumber
forall a b. b -> Either a b
Right PhoneNumber
pn
ErrorType
I.InvalidCountryCodeError -> ErrorType -> Either ErrorType PhoneNumber
forall a b. a -> Either a b
Left ErrorType
InvalidCountryCodeError
ErrorType
I.NotANumber -> ErrorType -> Either ErrorType PhoneNumber
forall a b. a -> Either a b
Left ErrorType
NotANumber
ErrorType
I.TooShortAfterIdd -> ErrorType -> Either ErrorType PhoneNumber
forall a b. a -> Either a b
Left ErrorType
TooShortAfterIdd
ErrorType
I.TooShortNsn -> ErrorType -> Either ErrorType PhoneNumber
forall a b. a -> Either a b
Left ErrorType
TooShortNsn
ErrorType
I.TooLongNsn -> ErrorType -> Either ErrorType PhoneNumber
forall a b. a -> Either a b
Left ErrorType
TooLongNsn
where
region :: ByteString
region = case Maybe Region
mRegion of
Maybe Region
Nothing -> ByteString
"ZZ"
Just (Region ByteString
reg) -> ByteString
reg
(ErrorType
err, PhoneNumber
pn) = case ParseMode
mode of
ParseMode
Canonicalize -> IO (ErrorType, PhoneNumber) -> (ErrorType, PhoneNumber)
forall a. IO a -> a
unsafeDupablePerformIO (IO (ErrorType, PhoneNumber) -> (ErrorType, PhoneNumber))
-> IO (ErrorType, PhoneNumber) -> (ErrorType, PhoneNumber)
forall a b. (a -> b) -> a -> b
$ IO (ErrorType, PhoneNumber) -> IO (ErrorType, PhoneNumber)
forall a. IO a -> IO a
mask_ (IO (ErrorType, PhoneNumber) -> IO (ErrorType, PhoneNumber))
-> IO (ErrorType, PhoneNumber) -> IO (ErrorType, PhoneNumber)
forall a b. (a -> b) -> a -> b
$
ByteString -> ByteString -> IO (ErrorType, PhoneNumber)
c_phone_number_util_parse ByteString
number ByteString
region
ParseMode
KeepRawInput -> IO (ErrorType, PhoneNumber) -> (ErrorType, PhoneNumber)
forall a. IO a -> a
unsafeDupablePerformIO (IO (ErrorType, PhoneNumber) -> (ErrorType, PhoneNumber))
-> IO (ErrorType, PhoneNumber) -> (ErrorType, PhoneNumber)
forall a b. (a -> b) -> a -> b
$ IO (ErrorType, PhoneNumber) -> IO (ErrorType, PhoneNumber)
forall a. IO a -> IO a
mask_ (IO (ErrorType, PhoneNumber) -> IO (ErrorType, PhoneNumber))
-> IO (ErrorType, PhoneNumber) -> IO (ErrorType, PhoneNumber)
forall a b. (a -> b) -> a -> b
$
ByteString -> ByteString -> IO (ErrorType, PhoneNumber)
c_phone_number_util_parse_and_keep_raw_input ByteString
number ByteString
region
matchNumbers :: Either ByteString PhoneNumber -> Either ByteString PhoneNumber -> MatchType
matchNumbers :: Either ByteString PhoneNumber
-> Either ByteString PhoneNumber -> MatchType
matchNumbers (Left ByteString
pn1) (Left ByteString
pn2) = IO MatchType -> MatchType
forall a. IO a -> a
unsafeDupablePerformIO (IO MatchType -> MatchType) -> IO MatchType -> MatchType
forall a b. (a -> b) -> a -> b
$
ByteString -> ByteString -> IO MatchType
c_phone_number_util_is_number_match_with_two_strings ByteString
pn1 ByteString
pn2
matchNumbers (Left ByteString
pn1) (Right PhoneNumber
pn2) = IO MatchType -> MatchType
forall a. IO a -> a
unsafeDupablePerformIO (IO MatchType -> MatchType) -> IO MatchType -> MatchType
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> ByteString -> IO MatchType
c_phone_number_util_is_number_match_with_one_string PhoneNumber
pn2 ByteString
pn1
matchNumbers (Right PhoneNumber
pn1) (Left ByteString
pn2) = IO MatchType -> MatchType
forall a. IO a -> a
unsafeDupablePerformIO (IO MatchType -> MatchType) -> IO MatchType -> MatchType
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> ByteString -> IO MatchType
c_phone_number_util_is_number_match_with_one_string PhoneNumber
pn1 ByteString
pn2
matchNumbers (Right PhoneNumber
pn1) (Right PhoneNumber
pn2) = IO MatchType -> MatchType
forall a. IO a -> a
unsafeDupablePerformIO (IO MatchType -> MatchType) -> IO MatchType -> MatchType
forall a b. (a -> b) -> a -> b
$
PhoneNumber -> PhoneNumber -> IO MatchType
c_phone_number_util_is_number_match PhoneNumber
pn1 PhoneNumber
pn2