gtin-0.1.0.0
Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Trade.GTIN

Description

The module exposes a GTIN data type that contains the number of digits as well.

Synopsis

GTIN and its aliasses.

newtype GTIN (n :: Natural) Source #

A datatype for Global Trade Item Numbers GTIN with arbitrary "width" (up to nineteen digits technically possible).

Constructors

GTIN Word64 

Instances

Instances details
Lift (GTIN n :: Type) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

lift :: Quote m => GTIN n -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => GTIN n -> Code m (GTIN n) #

(n <= 19, KnownNat n) => Arbitrary (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

arbitrary :: Gen (GTIN n) #

shrink :: GTIN n -> [GTIN n] #

KnownNat n => Data (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

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

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

toConstr :: GTIN n -> Constr #

dataTypeOf :: GTIN n -> DataType #

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

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

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

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

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

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

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

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

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

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

KnownNat n => Bounded (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

minBound :: GTIN n #

maxBound :: GTIN n #

KnownNat n => Enum (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

succ :: GTIN n -> GTIN n #

pred :: GTIN n -> GTIN n #

toEnum :: Int -> GTIN n #

fromEnum :: GTIN n -> Int #

enumFrom :: GTIN n -> [GTIN n] #

enumFromThen :: GTIN n -> GTIN n -> [GTIN n] #

enumFromTo :: GTIN n -> GTIN n -> [GTIN n] #

enumFromThenTo :: GTIN n -> GTIN n -> GTIN n -> [GTIN n] #

Generic (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Associated Types

type Rep (GTIN n) :: Type -> Type #

Methods

from :: GTIN n -> Rep (GTIN n) x #

to :: Rep (GTIN n) x -> GTIN n #

(n <= 19, KnownNat n) => Num (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

(+) :: GTIN n -> GTIN n -> GTIN n #

(-) :: GTIN n -> GTIN n -> GTIN n #

(*) :: GTIN n -> GTIN n -> GTIN n #

negate :: GTIN n -> GTIN n #

abs :: GTIN n -> GTIN n #

signum :: GTIN n -> GTIN n #

fromInteger :: Integer -> GTIN n #

Read (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

(n <= 19, KnownNat n) => Integral (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

quot :: GTIN n -> GTIN n -> GTIN n #

rem :: GTIN n -> GTIN n -> GTIN n #

div :: GTIN n -> GTIN n -> GTIN n #

mod :: GTIN n -> GTIN n -> GTIN n #

quotRem :: GTIN n -> GTIN n -> (GTIN n, GTIN n) #

divMod :: GTIN n -> GTIN n -> (GTIN n, GTIN n) #

toInteger :: GTIN n -> Integer #

(n <= 19, KnownNat n) => Real (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

toRational :: GTIN n -> Rational #

KnownNat n => Show (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

showsPrec :: Int -> GTIN n -> ShowS #

show :: GTIN n -> String #

showList :: [GTIN n] -> ShowS #

Binary (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

put :: GTIN n -> Put #

get :: Get (GTIN n) #

putList :: [GTIN n] -> Put #

Eq (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

(==) :: GTIN n -> GTIN n -> Bool #

(/=) :: GTIN n -> GTIN n -> Bool #

Ord (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

compare :: GTIN n -> GTIN n -> Ordering #

(<) :: GTIN n -> GTIN n -> Bool #

(<=) :: GTIN n -> GTIN n -> Bool #

(>) :: GTIN n -> GTIN n -> Bool #

(>=) :: GTIN n -> GTIN n -> Bool #

max :: GTIN n -> GTIN n -> GTIN n #

min :: GTIN n -> GTIN n -> GTIN n #

Hashable (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

hashWithSalt :: Int -> GTIN n -> Int #

hash :: GTIN n -> Int #

KnownNat n => Validity (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

Methods

validate :: GTIN n -> Validation #

type Rep (GTIN n) Source # 
Instance details

Defined in Data.Trade.GTIN

type Rep (GTIN n) = D1 ('MetaData "GTIN" "Data.Trade.GTIN" "gtin-0.1.0.0-2fmMDAPc4kE2eYOUPVUJV1" 'True) (C1 ('MetaCons "GTIN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

gtin Source #

Arguments

:: forall i n. ((<=) n 19, Integral i, KnownNat n) 
=> i

An Integral value for which we want to construct a GTIN number.

-> Maybe (GTIN n)

A GTIN number wrapped in a Just if the given value is within bounds and the checksum matches; Nothing otherwise.

Constructing a 'GTIN" with bound and checksum checks.

type GTIN14 = GTIN 14 Source #

A type alias for a GTIN number with fourteen numbers, with as range 00 0000 0000 000099 9999 9999 9997.

type GTIN13 = GTIN 13 Source #

A type alias for a GTIN number with thirteen numbers, with as range 0 0000 0000 00009 9999 9999 9994.

type GTIN12 = GTIN 12 Source #

A type alias for a GTIN number with twelve numbers, with as range 0000 0000 00009999 9999 9993.

type GTIN8 = GTIN 8 Source #

A type alias for a GTIN number with eight numbers, with as range 0000 00009999 9995.

type EANUCC14 = GTIN14 Source #

A type alias for a GTIN number with fourteen numbers, with as range 00 0000 0000 000099 9999 9999 9997.

type SCC14 = GTIN14 Source #

A type alias for a GTIN number with fourteen numbers, with as range 00 0000 0000 000099 9999 9999 9997.

type EAN = GTIN13 Source #

A type alias for a GTIN number with thirteen numbers, with as range 0 0000 0000 00009 9999 9999 9994.

type EANUCC13 = GTIN13 Source #

A type alias for a GTIN number with thirteen numbers, with as range 0 0000 0000 00009 9999 9999 9994.

type ISBN = GTIN13 Source #

A type alias for a GTIN with thirtheen numbers which is also an ISBN number, with as range 0 0000 0000 00009 9999 9999 9994.

type ISBN13 = GTIN13 Source #

A type alias for a GTIN with thirtheen numbers which is also an ISBN number, with as range 0 0000 0000 00009 9999 9999 9994.

type EANUCC8 = GTIN8 Source #

A type alias for a GTIN number with eight numbers, with as range 0000 00009999 9995.

type GSIN = GTIN 17 Source #

A type alias for a GTIN number with seventeen numbers, with as range 0 0000 0000 0000 00009 9999 9999 9999 9992.

type SSCC = GTIN 18 Source #

A type alias for a GTIN number with eighteen numbers, with as range 00 0000 0000 0000 000099 9999 9999 9999 9995.

Check if two GTINs are equivalent, even if the "width" of the GTINs are equivalent.

equivGTIN Source #

Arguments

:: GTIN m

The first GTIN to check.

-> GTIN n

The second GTIN to check.

-> Bool

True if the given GTIN values are equivalent; False otherwise.

Check if two GTIN numbers, possibly with a different "width" are equivalent.

upscaleGTIN Source #

Arguments

:: (<=) m n 
=> GTIN m

The original GTIN number to upscale.

-> GTIN n

A GTIN with the same number, but more (or the same) number of digits.

Convert one GTIN into a GTIN that has more digits. The new GTIN will have additional leading zeros.

Fix the checksum of a GTIN number

fixChecksum Source #

Arguments

:: GTIN n

The given GTIN number where we fix the checksum from.

-> GTIN n

A GTIN object that is the variant of the given GTIN number, with a valid checksum.

Fix the checksum of a given GTIN object. If the checksum is valid, then it will return the same GTIN, this operation is thus idempotent.

checkChecksum Source #

Arguments

:: GTIN n

The given GTIN number for which we check the checksum.

-> Bool

True if the given checksum matches; False otherwise.

Check if the given checksum matches.

Convert the GTINs to a readable format.

gtinToString Source #

Arguments

:: KnownNat n 
=> GTIN n

The given GTIN number to convert to a readable String.

-> String

A String that contains the GTIN number, in chucks of four digits.

Convert the given GTIN number to convert to a String that groups numbers into groups of four.

ISBN-10 to ISBN-13

fromISBN10' Source #

Arguments

:: Integral i 
=> i

An Integral number that contains an ISBN-10.

-> ISBN13

The equivalent ISBN-13 number, which is a GTIN number with the corresponding checksum algorithm.

Convert a given integral number that contains an ISBN-10 number into the ISBN13 equivalent. For example 8175257660 is converted to 9 7881 7525 7665. This will add a 978 prefix, and recalculate the checksum.

Parsing GTINs

gtinParser Source #

Arguments

:: forall s u m n. ((<=) 2 n, (<=) n 19, KnownNat n, Stream s m Char) 
=> ParsecT s u m (GTIN n)

A parser parsing a GTIN with an arbitrary number of digits that forces the stream to end, and does checks the checksum.

A parser for a gtin number with an arbitrary number of digits between two and nineteen. the parser forces the stream to end after the gtin, and validates if the gtin is indeed valid. The parser parses the number of digits with an arbitrary number of spaces between any two digits.

gtinParser_ Source #

Arguments

:: forall s u m n. ((<=) 2 n, (<=) n 19, KnownNat n, Stream s m Char) 
=> ParsecT s u m (GTIN n)

A parser parsing a GTIN with an arbitrary number of digits that does not force the stream to end, but checks the checksum.

A parser for a gtin number with an arbitrary number of digits between two and nineteen. the parser does not end after the gtin (so no eof is required). The GTIN is validated, so if the checksum does not match, the parser fails. The parser parses the number of digits with an arbitrary number of spaces between any two digits.

gtinParser' Source #

Arguments

:: forall s u m n. ((<=) 2 n, (<=) n 19, KnownNat n, Stream s m Char) 
=> ParsecT s u m (GTIN n)

A parser parsing a GTIN with an arbitrary number of digits thats force the stream to end, but does not check the checksum.

A parser for a gtin number with an arbitrary number of digits between two and nineteen. the parser forces the stream to end after the gtin, but does not validate if the gtin is indeed valid. The parser parses the number of digits with an arbitrary number of spaces between any two digits.

gtinParser_' Source #

Arguments

:: forall s u m n. ((<=) 2 n, (<=) n 19, KnownNat n, Stream s m Char) 
=> ParsecT s u m (GTIN n)

A parser parsing a GTIN with an arbitrary number of digits that does not force the stream to end, and does not check the checksum.

A parser for a gtin number with an arbitrary number of digits between two and nineteen. the parser does not end after the gtin (so no eof is required), and furthermore does not validate if the gtin is indeed valid. The parser parses the number of digits with an arbitrary number of spaces between any two digits.

parseGTIN Source #

Arguments

:: forall n s. ((<=) 2 n, (<=) n 19, KnownNat n, Stream s Identity Char) 
=> s

The stream to parse.

-> Either ParseError (GTIN n)

The result of the parser: Either a ParseError or the parsed GTIN.

Run the gtinParser_' parser and thus parses a GTIN with an arbitrary number of digits. The parser requires the stream to end after the GTIN, and validates the checksum.

parseGTIN_ Source #

Arguments

:: forall n s. ((<=) 2 n, (<=) n 19, KnownNat n, Stream s Identity Char) 
=> s

The stream to parse.

-> Either ParseError (GTIN n)

The result of the parser: Either a ParseError or the parsed GTIN.

Run the gtinParser_' parser and thus parses a GTIN with an arbitrary number of digits. The parser does not require the stream to end after the GTIN, but validates the checksum.

parseGTIN' Source #

Arguments

:: forall n s. ((<=) 2 n, (<=) n 19, KnownNat n, Stream s Identity Char) 
=> s

The stream to parse.

-> Either ParseError (GTIN n)

The result of the parser: Either a ParseError or the parsed GTIN.

Run the gtinParser_' parser and thus parses a GTIN with an arbitrary number of digits. The parser requires the stream to end after the GTIN, but does not validate the checksum.

parseGTIN_' Source #

Arguments

:: forall n s. ((<=) 2 n, (<=) n 19, KnownNat n, Stream s Identity Char) 
=> s

The stream to parse.

-> Either ParseError (GTIN n)

The result of the parser: Either a ParseError or the parsed GTIN.

Run the gtinParser_' parser and thus parses a GTIN with an arbitrary number of digits. The parser does not require the stream to end after the GTIN, and does not validate the checksum.

QuasiQuoters

gtinQ Source #

Arguments

:: forall n. ((<=) 2 n, (<=) n 19, KnownNat n) 
=> Proxy (GTIN n)

The Proxy object that is ignored, but used to determine the number of digits of the GTIN number.

-> QuasiQuoter

The corresponding QuasiQuoter that resolves to a GTIN expression or pattern.

A function that constructs a GTIN expression or pattern based on a given string. The Proxy parameter is used to specify the number of digits of the GTIN number.

gtin14Q Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an GTIN14 number.

gtin13Q Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an GTIN13 number.

gtin12Q Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an GTIN12 number.

gtin8Q Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an GTIN8 number.

eanucc8Q Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an EANUCC8 number.

eanucc14Q Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an EANUCC14 number.

scc14Q Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an SCC14 number.

eanQ Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an EAN number.

eanucc13Q Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an EANUCC13 number.

gsinQ Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for a GSIN number.

ssccQ Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an SSCC number.

isbnQ Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an ISBN number, only the thirteen digit number is supported.

isbn13Q Source #

Arguments

:: QuasiQuoter

The corresponding QuasiQuoter.

A QuasiQuoter for an ISBN13 number.