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

Data.PhoneNumber.Util

Description

Utilities for international phone numbers

Synopsis

Parsing

parseNumber Source #

Arguments

:: ParseMode 
-> Maybe Region

Default region, the country that we are expecting the number to be dialed from, which affects national and international dialing prefixes. This is only used if the number being parsed is not written in international format. In such cases the countryCode of the number would be that of the default region supplied. If the number is guaranteed to start with a '+' followed by the country calling code, then this can be omitted.

-> ByteString

Input.

-> Either ErrorType PhoneNumber 

Parse a phone number.

The function is quite lenient and looks for a number in the input ByteString and does not check whether the string is definitely only a phone number. To do this, it ignores punctuation and white-space, as well as any text before the number (e.g. a leading "Tel: ") and trims the non-number bits. It will accept a number in any format (E164, national, international etc.), assuming it can be interpreted with the default Region supplied. It also attempts to convert any alpha characters into digits if it thinks this is a vanity number of the type "1800 MICROSOFT".

The input can contain formatting such as +, ( and -, as well as a phone number extension. It can also be provided in RFC3966 format.

Note that validation of whether the number is actually a valid number for a particular region is not performed. This can be done separately with isValidNumber.

Returns an error if the string is not considered to be a viable phone number (e.g. too few or too many digits) or if no Region was supplied and the number is not in international format (does not start with '+').

data ParseMode Source #

How much information to retain when parsing

Constructors

Canonicalize

Canonicalize the phone number such that different representations can be easily compared, no matter what form it was originally entered in (e.g. national, international)

KeepRawInput

Record context about the number being parsed, such as rawInput, countryCodeSource, and preferredDomesticCarrierCode

Instances

Instances details
Data ParseMode Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

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

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

toConstr :: ParseMode -> Constr #

dataTypeOf :: ParseMode -> DataType #

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

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

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

gmapQl :: (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 #

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

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

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

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

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

Generic ParseMode Source # 
Instance details

Defined in Data.PhoneNumber.Util

Associated Types

type Rep ParseMode :: Type -> Type #

Read ParseMode Source # 
Instance details

Defined in Data.PhoneNumber.Util

Show ParseMode Source # 
Instance details

Defined in Data.PhoneNumber.Util

NFData ParseMode Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

rnf :: ParseMode -> () #

Eq ParseMode Source # 
Instance details

Defined in Data.PhoneNumber.Util

Ord ParseMode Source # 
Instance details

Defined in Data.PhoneNumber.Util

type Rep ParseMode Source # 
Instance details

Defined in Data.PhoneNumber.Util

type Rep ParseMode = D1 ('MetaData "ParseMode" "Data.PhoneNumber.Util" "libphonenumber-0.1.2.0-inplace" 'False) (C1 ('MetaCons "Canonicalize" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeepRawInput" 'PrefixI 'False) (U1 :: Type -> Type))

data ErrorType Source #

Phone number parsing error

Constructors

InvalidCountryCodeError

The number did not contain a country code and there was no default region supplied, or the number contained an invalid country code

NotANumber

Does not look like a phone number

TooShortAfterIdd

Input starts with an International Direct Dialing prefix, but ends too shortly thereafter

TooShortNsn

The National Significant Number is too short

TooLongNsn

The National Significant Number is too long

Instances

Instances details
Data ErrorType Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

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

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

toConstr :: ErrorType -> Constr #

dataTypeOf :: ErrorType -> DataType #

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

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

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

gmapQl :: (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 #

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

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

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

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

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

Generic ErrorType Source # 
Instance details

Defined in Data.PhoneNumber.Util

Associated Types

type Rep ErrorType :: Type -> Type #

Read ErrorType Source # 
Instance details

Defined in Data.PhoneNumber.Util

Show ErrorType Source # 
Instance details

Defined in Data.PhoneNumber.Util

NFData ErrorType Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

rnf :: ErrorType -> () #

Eq ErrorType Source # 
Instance details

Defined in Data.PhoneNumber.Util

Ord ErrorType Source # 
Instance details

Defined in Data.PhoneNumber.Util

type Rep ErrorType Source # 
Instance details

Defined in Data.PhoneNumber.Util

type Rep ErrorType = D1 ('MetaData "ErrorType" "Data.PhoneNumber.Util" "libphonenumber-0.1.2.0-inplace" 'False) ((C1 ('MetaCons "InvalidCountryCodeError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotANumber" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TooShortAfterIdd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TooShortNsn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TooLongNsn" 'PrefixI 'False) (U1 :: Type -> Type))))

Formatting

formatNumber :: PhoneNumberFormat -> PhoneNumber -> ByteString Source #

Formats a phone number in the specified PhoneNumberFormat using default rules. Note that this does not promise to produce a phone number that the user can dial from where they are - as we do not currently support a more abbreviated format, such as for users in the same area who could potentially dial the number without area code.

data PhoneNumberFormat Source #

How formatNumber should format a phone number

Constructors

International

Consistent with the definition in ITU-T Recommendation E.123. However we follow local conventions such as using '-' instead of whitespace as separators. E.g. "+41 44 668 1800".

National

Consistent with E.123, and also following local conventions for separators. E.g. "044 668 1800".

E164

Same as International but with no formatting, e.g. "+41446681800". See https://en.wikipedia.org/wiki/E.164.

RFC3966

Same as International but with all separating symbols replaced with a hyphen, and with any phone number extension appended with ";ext=". It will also have a prefix of "tel:" added, e.g. "tel:+41-44-668-1800".

NationalWithCarrierCodeOverride ByteString

Same as National but for dialing using the specified domestic carrier code.

NationalWithCarrierCodeFallback ByteString

Same as National but use the phone number's preferredDomesticCarrierCode (which is only set if parsed with KeepRawInput). If a preferred carrier code is absent, the provided string is used as fallback.

ForMobileDialing

Format in such a way that it can be dialed from a mobile phone in a specific region. If the number cannot be reached from the region (e.g. some countries block toll-free numbers from being called outside of the country), will format to an empty string.

Fields

OutOfCountry

Format for out-of-country dialing purposes. This takes care of the case of calling inside of NANPA and between Russia and Kazakhstan (who share the same country calling code). In those cases, no international prefix is used. For regions which have multiple international prefixes, formats as International.

Fields

  • from :: Region
     
  • keepAlphaChars :: Bool

    Attempt to keep alpha chars and grouping information, if rawInput is available. Setting this to True comes with a number of caveats:

    1. This will not produce good results if the country calling code is both present in rawInput and is the start of the national number. This is not a problem in the regions which typically use alpha numbers.
    2. This will also not produce good results if rawInput has any grouping information within the first three digits of the national number, and if the function needs to strip preceding digits/words in rawInput before these digits. Normally people group the first three digits together so this is not a huge problem.
Original

Use rawInput verbatim if present, otherwise infer National, International, or OutOfCountry based on countryCodeSource.

Fields

Analysis

matchNumbers :: Either ByteString PhoneNumber -> Either ByteString PhoneNumber -> MatchType Source #

Compares two numbers for equality. A number can be provided as a string, in which case it is parsed without assuming its region.

Returns ExactMatch if the country calling code, National Significant Number (NSN), presence of a leading zero for Italian numbers and any extension present are the same.

Returns NsnMatch if either or both has no country calling code specified, and the NSNs and extensions are the same.

Returns ShortNsnMatch if either or both has no country calling code specified, or the country calling code specified is the same, and one NSN could be a shorter version of the other number. This includes the case where one has an extension specified, and the other does not.

Returns InvalidNumber if a number that was provided as a string could not be parsed.

Returns NoMatch otherwise.

For example, the numbers 1 345 657 1234 and 657 1234 are a ShortNsnMatch. The numbers 1 345 657 1234 and 345 657 are a NoMatch. Note that none of these numbers can be parsed by parseNumber without assuming a region.

data MatchType Source #

Types of phone number matches. See matchNumbers.

Instances

Instances details
Enum MatchType Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

Generic MatchType Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

Associated Types

type Rep MatchType :: Type -> Type #

Show MatchType Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

Eq MatchType Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

type Rep MatchType Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

type Rep MatchType = D1 ('MetaData "MatchType" "Data.PhoneNumber.Internal.Util" "libphonenumber-0.1.2.0-inplace" 'False) ((C1 ('MetaCons "InvalidNumber" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoMatch" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ShortNsnMatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NsnMatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExactMatch" 'PrefixI 'False) (U1 :: Type -> Type))))

regionForNumber :: PhoneNumber -> Maybe (Either NonGeoRegion Region) Source #

Returns the region where a phone number is from. This could be used for geocoding at the region level. Only guarantees correct results for valid, full numbers (not short-codes, or invalid numbers).

nationalSignificantNumber :: PhoneNumber -> ByteString Source #

Gets the National Significant Number (NSN) of a phone number. Note an NSN doesn't contain a national prefix or any formatting.

isValidNumber :: Maybe (Either NonGeoRegion Region) -> PhoneNumber -> Bool Source #

Tests whether a phone number is valid for a certain region (if unspecified, the region the number is from). Note this doesn't verify the number is actually in use, which is impossible to tell by just looking at a number itself.

If the country calling code is not the same as the country calling code for the provided region, this immediately returns False. After this, the specific number pattern rules for the region are examined.

Specifying a region may be useful for determining for example whether a particular number is valid for Canada, rather than just a valid NANPA number. On the other hand this may lead to undesirable results, for example numbers from British Crown dependencies such as the Isle of Man are considered invalid for the region "GB" (United Kingdom), since it has its own region code, "IM".

Note that it only verifies whether the parsed, canonicalised number is valid: not whether a particular series of digits entered by the user is dialable from the region provided when parsing. For example, the number +41 (0) 78 927 2696 can be parsed into a number with country code "41" and National Significant Number "789272696". This is valid, while the original string is not dialable.

numberType :: PhoneNumber -> PhoneNumberType Source #

Gets the phone number type. Returns Unknown if invalid.

data PhoneNumberType Source #

Type of a phone number.

FixedLineOrMobile designates cases where it is impossible to distinguish between fixed-line and mobile numbers by looking at the phone number itself (e.g. the USA).

TollFree designates freephone lines.

SharedCost designates numbers where the cost of the call is shared between the caller and the recipient, and is hence typically less than for PremiumRate. See http://en.wikipedia.org/wiki/Shared_Cost_Service for more information.

Voip designates Voice over IP numbers. This includes TSoIP (Telephony Service over IP).

Uan designates "Universal Access Numbers" or "Company Numbers". They may be further routed to specific offices, but allow one number to be used for a company.

Voicemail designates "Voice Mail Access Numbers".

Instances

Instances details
Enum PhoneNumberType Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

Generic PhoneNumberType Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

Associated Types

type Rep PhoneNumberType :: Type -> Type #

Show PhoneNumberType Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

Eq PhoneNumberType Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

Ord PhoneNumberType Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

type Rep PhoneNumberType Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

type Rep PhoneNumberType = D1 ('MetaData "PhoneNumberType" "Data.PhoneNumber.Internal.Util" "libphonenumber-0.1.2.0-inplace" 'False) (((C1 ('MetaCons "FixedLine" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mobile" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FixedLineOrMobile" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "TollFree" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PremiumRate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SharedCost" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Voip" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PersonalNumber" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pager" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Uan" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Voicemail" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unknown" 'PrefixI 'False) (U1 :: Type -> Type)))))

possibleNumber :: PhoneNumberType -> PhoneNumber -> ValidationResult Source #

Check whether a phone number is a possible number of a particular type. Pass the type Unknown to check whether a number is possible at all.

For more specific types that don't exist in a particular region, this will return a result that isn't so useful; it is recommended that you use supportedTypesForRegion or supportedTypesForNonGeoEntity respectively before calling this function to determine you should pass a more specific type instead of Unknown.

This function provides a more lenient check than isValidNumber in the following sense:

  1. It only checks the length of phone numbers. In particular, it doesn't check starting digits of the number.
  2. If Unknown is provided, it doesn't attempt to figure out the type of the number, but uses general rules which apply to all types of phone numbers in a region. Therefore, it is much faster than isValidNumber.
  3. For some numbers (particularly fixed-line), many regions have the concept of area code, which together with subscriber number constitute the National Significant Number. It is sometimes okay to dial only the subscriber number when dialing in the same area. This function will return IsPossibleLocalOnly if the subscriber-number-only version is passed in. On the other hand, because isValidNumber validates using information on both starting digits (for fixed line numbers, that would most likely be area codes) and length (obviously includes the length of area codes for fixed line numbers), it will return False for the subscriber-number-only version.

data ValidationResult Source #

Possible outcomes when testing if a PhoneNumber is possible.

IsPossible means the number length matches that of valid numbers for this region.

IsPossibleLocalOnly means the number length matches that of local numbers for this region only (i.e. numbers that may be able to be dialled within an area, but do not have all the information to be dialled from anywhere inside or outside the country).

InvalidCountryCode means the number has an invalid country calling code.

TooShort means the number is shorter than all valid numbers for this region.

TooLong means the number is longer than all valid numbers for this region.

InvalidLength means the number is longer than the shortest valid numbers for this region, shorter than the longest valid numbers for this region, and does not itself have a number length that matches valid numbers for this region. This can also be returned in the case when there are no numbers of a specific type at all for this region.

Instances

Instances details
Enum ValidationResult Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

Generic ValidationResult Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

Associated Types

type Rep ValidationResult :: Type -> Type #

Show ValidationResult Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

Eq ValidationResult Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

type Rep ValidationResult Source # 
Instance details

Defined in Data.PhoneNumber.Internal.Util

type Rep ValidationResult = D1 ('MetaData "ValidationResult" "Data.PhoneNumber.Internal.Util" "libphonenumber-0.1.2.0-inplace" 'False) ((C1 ('MetaCons "IsPossible" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IsPossibleLocalOnly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidCountryCode" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "TooShort" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InvalidLength" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TooLong" 'PrefixI 'False) (U1 :: Type -> Type))))

canBeInternationallyDialed :: PhoneNumber -> Bool Source #

Returns True if the number can be dialed from outside the region, or unknown. If the number can only be dialled from within the region, returns False. Does not check the number is a valid number. Note that, at the moment, this method does not handle short numbers (which are currently all presumed to not be diallable from outside their country).

isGeographicalNumber :: PhoneNumber -> Bool Source #

Tests whether a phone number has a geographical association. It checks if the number is associated with a certain region in the country to which it belongs. Note that this doesn't verify if the number is actually in use.

isGeographicalNumberType :: PhoneNumberType -> CountryCode -> Bool Source #

A less expensive version of isGeographicalNumber if we already know the PhoneNumberType

isAlphaNumber :: ByteString -> Bool Source #

Returns true if the number is a valid vanity (alpha) number such as "800 MICROSOFT". A valid vanity number will start with at least 3 digits and will have three or more alpha characters. This does not do region-specific checks - to work out if this number is actually valid for a region, you should use parseNumber and possibleNumber/isValidNumber.

Library Support

supportedRegions :: Set Region Source #

All geographical regions the library has metadata for

supportedGlobalNetworkCallingCodes :: Set CountryCode Source #

All global network calling codes (country calling codes for non-geographical entities) the library has metadata for

supportedCallingCodes :: Set CountryCode Source #

All country calling codes the library has metadata for, covering both non-geographical entities (global network calling codes) and those used for geographical entities. This could be used to populate a drop-down box of country calling codes for a phone-number widget, for instance.

supportedTypesForRegion :: Region -> Set PhoneNumberType Source #

Returns the types for a given region which the library has metadata for. Will not include FixedLineOrMobile (if numbers for this non-geographical entity could be classified as FixedLineOrMobile, both FixedLine and Mobile would be present) and Unknown.

No types will be returned for invalid or unknown region codes.

supportedTypesForNonGeoEntity :: CountryCode -> Set PhoneNumberType Source #

Returns the types for a country-code belonging to a non-geographical entity which the library has metadata for. Will not include FixedLineOrMobile (if numbers for this non-geographical entity could be classified as FixedLineOrMobile, both FixedLine and Mobile would be present) and Unknown.

No types will be returned for country calling codes that do not map to a known non-geographical entity.

Region/CountryCode Queries

newtype Region Source #

An ISO 3166-1 alpha-2 country code in upper case.

Constructors

Region ByteString 

Instances

Instances details
Data Region Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

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

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

toConstr :: Region -> Constr #

dataTypeOf :: Region -> DataType #

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

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

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

gmapQl :: (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 #

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

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

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

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

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

IsString Region Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

fromString :: String -> Region #

Generic Region Source # 
Instance details

Defined in Data.PhoneNumber.Util

Associated Types

type Rep Region :: Type -> Type #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

Read Region Source # 
Instance details

Defined in Data.PhoneNumber.Util

Show Region Source # 
Instance details

Defined in Data.PhoneNumber.Util

NFData Region Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

rnf :: Region -> () #

Eq Region Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

(==) :: Region -> Region -> Bool #

(/=) :: Region -> Region -> Bool #

Ord Region Source # 
Instance details

Defined in Data.PhoneNumber.Util

type Rep Region Source # 
Instance details

Defined in Data.PhoneNumber.Util

type Rep Region = D1 ('MetaData "Region" "Data.PhoneNumber.Util" "libphonenumber-0.1.2.0-inplace" 'True) (C1 ('MetaCons "Region" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data NonGeoRegion Source #

A "region" corresponding to non-geographical entities. The library internally uses the UN M.49 code "001" (meaning the world) for this.

Constructors

Region001 

Instances

Instances details
Data NonGeoRegion Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

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

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

toConstr :: NonGeoRegion -> Constr #

dataTypeOf :: NonGeoRegion -> DataType #

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

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

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

gmapQl :: (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 #

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

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

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

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

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

Generic NonGeoRegion Source # 
Instance details

Defined in Data.PhoneNumber.Util

Associated Types

type Rep NonGeoRegion :: Type -> Type #

Read NonGeoRegion Source # 
Instance details

Defined in Data.PhoneNumber.Util

Show NonGeoRegion Source # 
Instance details

Defined in Data.PhoneNumber.Util

NFData NonGeoRegion Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

rnf :: NonGeoRegion -> () #

Eq NonGeoRegion Source # 
Instance details

Defined in Data.PhoneNumber.Util

Ord NonGeoRegion Source # 
Instance details

Defined in Data.PhoneNumber.Util

type Rep NonGeoRegion Source # 
Instance details

Defined in Data.PhoneNumber.Util

type Rep NonGeoRegion = D1 ('MetaData "NonGeoRegion" "Data.PhoneNumber.Util" "libphonenumber-0.1.2.0-inplace" 'False) (C1 ('MetaCons "Region001" 'PrefixI 'False) (U1 :: Type -> Type))

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 

countryCodeForRegion :: Region -> Maybe CountryCode Source #

Returns the country calling code for a specific region. For example, this would be 1 for the United States, and 64 for New Zealand.

regionForCountryCode :: CountryCode -> Maybe (Either NonGeoRegion Region) Source #

Returns the region code that matches the specific country code. Note that it is possible that several regions share the same country calling code (e.g. US and Canada), and in that case, only one of the regions (normally the one with the largest population) is returned. If the country calling code entered is valid but doesn't match a specific region (such as in the case of non-geographical calling codes like 800) Region001 will be returned.

regionsForCountryCode :: CountryCode -> [Either NonGeoRegion Region] Source #

Returns a list of the region codes that match the specific country calling code. For non-geographical country calling codes, Region001 is returned. Also, in the case of no region code being found, the list is empty.

isNANPACountry :: Region -> Bool Source #

Checks if this is a region under the North American Numbering Plan Administration (NANPA).

countryMobileToken :: CountryCode -> ByteString Source #

Returns the mobile token for the provided country calling code if it has one, otherwise returns an empty string. A mobile token is a number inserted before the area code when dialing a mobile number from that country from abroad.

nddPrefixForRegion Source #

Arguments

:: Bool

Whether to strip non-digits like '~'

-> Region 
-> ByteString 

Returns the National Direct Dialling prefix (NDD prefix) for a specific region. For example, this would be "1" for the United States, and "0" for New Zealand. Note that this may contain symbols like '~' (which indicates a wait for a dialing tone). Returns an empty string if no national prefix is present.

Miscellaneous

truncateTooLongNumber :: PhoneNumber -> Maybe PhoneNumber Source #

Attempts to extract a valid number from a phone number that is too long to be valid. Returns Nothing if no valid number could be extracted.

convertAlphaNumber :: ByteString -> ByteString Source #

Converts all alpha characters in a number to their respective digits on a keypad, but retains existing formatting

normalizeNumber :: Normalize -> ByteString -> ByteString Source #

Normalizes a string of characters representing a phone number. See Normalize.

data Normalize Source #

How normalizeNumber should normalize a phone number

Constructors

Digits

Convert wide-ascii and arabic-indic numerals to European numerals, and strip punctuation and alpha characters

Dialable

Strip all characters which are not diallable on a mobile phone keypad (including all non-ASCII digits)

Instances

Instances details
Data Normalize Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

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

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

toConstr :: Normalize -> Constr #

dataTypeOf :: Normalize -> DataType #

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

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

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

gmapQl :: (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 #

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

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

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

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

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

Generic Normalize Source # 
Instance details

Defined in Data.PhoneNumber.Util

Associated Types

type Rep Normalize :: Type -> Type #

Read Normalize Source # 
Instance details

Defined in Data.PhoneNumber.Util

Show Normalize Source # 
Instance details

Defined in Data.PhoneNumber.Util

NFData Normalize Source # 
Instance details

Defined in Data.PhoneNumber.Util

Methods

rnf :: Normalize -> () #

Eq Normalize Source # 
Instance details

Defined in Data.PhoneNumber.Util

Ord Normalize Source # 
Instance details

Defined in Data.PhoneNumber.Util

type Rep Normalize Source # 
Instance details

Defined in Data.PhoneNumber.Util

type Rep Normalize = D1 ('MetaData "Normalize" "Data.PhoneNumber.Util" "libphonenumber-0.1.2.0-inplace" 'False) (C1 ('MetaCons "Digits" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Dialable" 'PrefixI 'False) (U1 :: Type -> Type))

Re-exports

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