belgian-structured-communication-0.1.0.0: parsing, rendering and manipulating the structured communication of Belgian financial transactions.
Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageHaskell2010

Finance.Belgium.StructuredCommunication

Description

Belgian companies often make use of structured communication with a checksum. This package aims to provide a toolkit to parse, render and manipulate StructuredCommunication.

Synopsis

Constructing StructuredCommunication

data StructuredCommunication Source #

A data type that stores three numbers: one with three digits (000–999), four digits (0000–9999) and five digits (00001–99997). The data constructor itself is not accessible, since the StructuredCommunication could produce objects that are out of the given ranges, or where the checksum is not valid. The module thus aims to prevent parsing, changing, etc. StructuredCommunication objects into an invalid state.

Instances

Instances details
Arbitrary StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Data StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Methods

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

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

toConstr :: StructuredCommunication -> Constr #

dataTypeOf :: StructuredCommunication -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Enum StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Generic StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Associated Types

type Rep StructuredCommunication :: Type -> Type #

Num StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Read StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Integral StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Real StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Show StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Binary StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Eq StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Ord StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Hashable StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Validity StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

Lift StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

type Rep StructuredCommunication Source # 
Instance details

Defined in Finance.Belgium.StructuredCommunication

type Rep StructuredCommunication = D1 ('MetaData "StructuredCommunication" "Finance.Belgium.StructuredCommunication" "belgian-structured-communication-0.1.0.0-74zNtxkWSKb2Ahh9MdkGWp" 'False) (C1 ('MetaCons "StructuredCommunication" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32))))

structuredCommunication Source #

Arguments

:: (Integral i, Integral j, Integral k) 
=> i

The first number, should be between 000 and 999.

-> j

The second number, should be between 0000 and 9999.

-> k

The third number, should be between 00001 and 99997.

-> Maybe StructuredCommunication

The StructuredCommunication wrapped in a Just of the three numbers are in range, and the checksum matches, otherwise Nothing.

Construct a StructuredCommunication object for the given three integral values that form the three sequences of digits.

determining the checksum

checksum Source #

Arguments

:: StructuredCommunication

The StructuredCommunication for which we determine the checkum.

-> Word32

The last two digits of the StructuredCommunication object. The checksum is not per se valid.

Determining the checksum-part for the given StructuredCommunication. This thus takes the last two digits, or the third number modulo one hundred.

determineChecksum Source #

Arguments

:: StructuredCommunication

The StructuredCommunication to determine the checksum from.

-> Word32

The checksum determined by the first ten digits, not per se the real checksum of the StructuredCommunication.

Determine the checksum based on the first ten digits. If the StructuredCommunication is not valid, its checksum will not match the result of the determineChecksum.

validChecksum Source #

Arguments

:: StructuredCommunication

The StructuredCommunication for which we check the checksum.

-> Bool

True if the checksum is valid; False otherwise.

Check if the checksum matches for the given StructuredCommunication.

fixChecksum Source #

Arguments

:: StructuredCommunication

The given StructuredCommunication to fix.

-> StructuredCommunication

A variant of the given StructuredCommunication where only the last two digits are changed to have a valid checksum.

Convert the given StructuredCommunication to one where the checksum is valid. If the checksum was already valid, it returns an equivalent StructuredCommunication, this operation is thus idempotent.

Converting to text

communicationToString Source #

Arguments

:: StructuredCommunication

The given StructuredCommunication to convert to a String.

-> String

The corresponding String, of the form +++000/0000/00097+++.

Convert the given StructuredCommunication to a String that looks like a structured communication, so +++000/0000/00097+++.

communicationToText Source #

Arguments

:: StructuredCommunication

The given StructuredCommunication to convert to a Text.

-> Text

The corresponding Text, of the form +++000/0000/00097+++.

Convert the given StructuredCommunication to a Text that looks like a structured communication, so +++000/0000/00097+++.

Parsing from text

communicationParser Source #

Arguments

:: Stream s m Char 
=> ParsecT s u m StructuredCommunication

The ParsecT object that parses the structured communication of the form +++000/0000/00097+++.

A ParsecT that parses a string into a StructuredCommunication, the StructuredCommunication is checked for its validity (checksum). The parser does not (per se) ends with an eof.

communicationParser' Source #

Arguments

:: Stream s m Char 
=> ParsecT s u m StructuredCommunication

The ParsecT object that parses the structured communication of the form +++000/0000/00097+++.

A ParsecT that parses a string into a StructuredCommunication, the StructuredCommunication can be invalid. The parser also does not (per se) ends with an eof.

communicationEParser Source #

Arguments

:: Stream s m Char 
=> ParsecT s u m StructuredCommunication

The ParsecT object that parses the structured communication of the form +++000/0000/00097+++.

A ParsecT that parses a string into a StructuredCommunication, the StructuredCommunication is checked for its validity (checksum). The parser also checks that this is the end of the stream.

communicationEParser' Source #

Arguments

:: Stream s m Char 
=> ParsecT s u m StructuredCommunication

The ParsecT object that parses the structured communication of the form +++000/0000/00097+++.

A ParsecT that parses a string into a StructuredCommunication, the StructuredCommunication can be invalid. The parser also checks if this is the end of the stream.

parseCommunication Source #

Arguments

:: Stream s Identity Char 
=> s

The stream that is parsed into a StructuredCommunication

-> Either ParseError StructuredCommunication

The result of parsing, either a StructuredCommunication wrapped in a Right or a parsing error wrapped in a Left.

Parsing a stream into a StructuredCommunication that also validates the checksum of the communication. The stream does not per se needs to end with structured communcation.

parseCommunication' Source #

Arguments

:: Stream s Identity Char 
=> s

The stream that is parsed into a StructuredCommunication

-> Either ParseError StructuredCommunication

The result of parsing, either a StructuredCommunication wrapped in a Right or a parsing error wrapped in a Left.

Parsing a stream into a StructuredCommunication that does noet validate the checksum of the communication. The stream does not per se needs to end with structured communcation.

parseCommunicationE Source #

Arguments

:: Stream s Identity Char 
=> s

The stream that is parsed into a StructuredCommunication

-> Either ParseError StructuredCommunication

The result of parsing, either a StructuredCommunication wrapped in a Right or a parsing error wrapped in a Left.

Parsing a stream into a StructuredCommunication that also validates the checksum of the communication. After the structured communication, the stream needs to end.

parseCommunicationE' Source #

Arguments

:: Stream s Identity Char 
=> s

The stream that is parsed into a StructuredCommunication

-> Either ParseError StructuredCommunication

The result of parsing, either a StructuredCommunication wrapped in a Right or a parsing error wrapped in a Left.

Parsing a stream into a StructuredCommunication that does noet validate the checksum of the communication. After the structured communication, the stream needs to end.

Quasi quotation

beCommunication Source #

Arguments

:: QuasiQuoter

A QuasiQuoter to parse to a StructuredCommunication.

A QuasiQuoter that can parse a string into an expression or pattern. It will thus convert +++000/000/00097+++ into a StructuredCommunication as expression or pattern.