libphonenumber-0.1.0.0: Parsing, formatting, and validating international phone numbers
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.PhoneNumber.Number

Description

Data fields of PhoneNumber objects.

Synopsis

Documentation

data PhoneNumber Source #

A decoded phone number. While internally it is a handle for the corresponding C++ object, for most intents and purposes it can be used as a record (using the PhoneNumber record pattern synonym) with the following structure:

PhoneNumber
{ extension :: !(Maybe ByteString)
, rawInput :: !(Maybe ByteString)
, preferredDomesticCarrierCode :: !(Maybe ByteString)
, nationalNumber :: !Word
, countryCode :: ! CountryCode
, italianLeadingZero :: !(Maybe Bool)
, countryCodeSource :: !(Maybe CountryCodeSource)
, numberOfLeadingZeros :: !(Maybe Int)
}

Instances

Instances details
Data PhoneNumber Source #

No internal structure

Instance details

Defined in Data.PhoneNumber.Internal.Number

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PhoneNumber -> c PhoneNumber #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PhoneNumber #

toConstr :: PhoneNumber -> Constr #

dataTypeOf :: PhoneNumber -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PhoneNumber) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PhoneNumber) #

gmapT :: (forall b. Data b => b -> b) -> PhoneNumber -> PhoneNumber #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PhoneNumber -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PhoneNumber -> r #

gmapQ :: (forall d. Data d => d -> u) -> PhoneNumber -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PhoneNumber -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PhoneNumber -> m PhoneNumber #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PhoneNumber -> m PhoneNumber #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PhoneNumber -> m PhoneNumber #

Read PhoneNumber Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

Show PhoneNumber Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

NFData PhoneNumber Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

Methods

rnf :: PhoneNumber -> () #

Eq PhoneNumber Source #

Compares all the data fields, consider matchNumbers instead

Instance details

Defined in Data.PhoneNumber.Internal.Number

Ord PhoneNumber Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

pattern PhoneNumber :: Maybe ByteString -> Maybe ByteString -> Maybe ByteString -> Word -> CountryCode -> Maybe Bool -> Maybe CountryCodeSource -> Maybe Int -> PhoneNumber Source #

Record pattern synonym for accessing data fields of the underlying C++ object. It can be used for record construction, record update, and record pattern match. See PhoneNumber.

extension :: PhoneNumber -> Maybe ByteString Source #

E.g.:

parseNumber Canonicalize Nothing "+1 800-234-5678 ext. 1234"
= Right PhoneNumber { extension = Just "1234", .. }

rawInput :: PhoneNumber -> Maybe ByteString Source #

E.g.:

parseNumber KeepRawInput Nothing " + 1(2-3~4*5.6 "
= Right PhoneNumber { rawInput = Just " + 1(2-3~4*5.6 ", .. }

nationalNumber :: PhoneNumber -> Word Source #

You probably want to use nationalSignificantNumber instead. E.g.:

parseNumber Canonicalize Nothing "+800 0001 2345"
= Right PhoneNumber { nationalNumber = 12345, numberOfLeadingZeros = Just 3, .. }

newtype CountryCode Source #

A country calling code (International Subscriber Dialing code, ISD code), e.g. 34 for Spain.

Contrary to the name, doesn't always correspond to a unique country (e.g. 7 could be either Russia or Kazakhstan), or a country at all, and instead a non-geographical entity (e.g. 800 is a Universal International Freephone Service dialing code).

Constructors

CountryCode Int 

data CountryCodeSource Source #

Indicates what information was used to fill the countryCode field of PhoneNumber.

Instances

Instances details
Data CountryCodeSource Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CountryCodeSource -> c CountryCodeSource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CountryCodeSource #

toConstr :: CountryCodeSource -> Constr #

dataTypeOf :: CountryCodeSource -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CountryCodeSource) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CountryCodeSource) #

gmapT :: (forall b. Data b => b -> b) -> CountryCodeSource -> CountryCodeSource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CountryCodeSource -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CountryCodeSource -> r #

gmapQ :: (forall d. Data d => d -> u) -> CountryCodeSource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CountryCodeSource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CountryCodeSource -> m CountryCodeSource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CountryCodeSource -> m CountryCodeSource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CountryCodeSource -> m CountryCodeSource #

Enum CountryCodeSource Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

Generic CountryCodeSource Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

Associated Types

type Rep CountryCodeSource :: Type -> Type #

Read CountryCodeSource Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

Show CountryCodeSource Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

NFData CountryCodeSource Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

Methods

rnf :: CountryCodeSource -> () #

Eq CountryCodeSource Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

Ord CountryCodeSource Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

type Rep CountryCodeSource Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Number

type Rep CountryCodeSource = D1 ('MetaData "CountryCodeSource" "Data.PhoneNumber.Internal.Number" "libphonenumber-0.1.0.0-inplace" 'False) ((C1 ('MetaCons "Unspecified" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FromNumberWithPlusSign" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FromNumberWithIdd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FromNumberWithoutPlusSign" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FromDefaultCountry" 'PrefixI 'False) (U1 :: Type -> Type))))