Copyright | (c) Ilya Portnov 2014 |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | portnov84@rambler.ru |
Stability | unstable |
Portability | not tested |
Safe Haskell | Safe |
Language | Haskell98 |
This module contains Get and Put method implementations for ISO 8583 style bitmaps, and also utility methods for getting/putting fields in formats commonly used in ISO 8583 specification.
- getBitmapFieldNumbers :: Get [Int]
- getBitmap :: (Int -> Maybe (Get f)) -> Get (Map Int f)
- mergeFieldNumbers :: [Int] -> ByteString
- putBitmap :: [(Int, Put)] -> Put
- putBitmap' :: [(Int, Maybe Put)] -> Put
- embeddedLen :: Int -> Int -> Get ByteString
- asciiNumber :: Int -> Get Int
- asciiNumberF :: Int -> Int -> Get Integer
- putAsciiNumber :: Int -> Integer -> Put
- putEmbeddedLen :: Int -> ByteString -> Put
- putByteStringPad :: Int -> ByteString -> Put
- putLazyByteStringPad :: Int64 -> ByteString -> Put
- toBS :: String -> ByteString
- fromBS :: ByteString -> String
Usage
Typical usage is:
data Message = Message {pan :: B.ByteString, stan :: Integer} deriving (Eq, Show)
data FieldValue = String B.ByteString | Int Integer deriving (Eq, Show)
getField :: Int -> Maybe (Get FieldValue) getField 2 = Just $ String `fmap` embeddedLen 2 getField 11 = Just $ Int `fmap` asciiNumberF 11 6 getField _ = Nothing
getMessage :: Get Message getMessage = do m <- getBitmap getField let Just (String pan) = M.lookup 2 m let Just (Int stan) = M.lookup 11 m return $ Message pan stan
putMessage :: Message -> Put putMessage (Message pan stan) = do putBitmap [(2, putEmbeddedLen 2 pan), (11, putAsciiNumber 6 stan)]
getBitmapFieldNumbers :: Get [Int] Source #
Parse bitmap. Return numbers of fields present. NB: only two bitmaps are supported as for now (Primary and Secondary bitmaps in ISO 8583 notation).
:: (Int -> Maybe (Get f)) | Parser for n'th field, or Nothing if field is not supported |
-> Get (Map Int f) |
Parse ISO 8583-style bitmap. Fails if unsupported field is present in message.
mergeFieldNumbers :: [Int] -> ByteString Source #
Merge numbers of fields present into ISO bitmap.
Put ISO 8583-style bitmap.
:: Int | Field number (to be used in error message) |
-> Int | Number of bytes used for length (2 for LLVAR, 3 for LLLVAR and so on) |
-> Get ByteString |
Parse string with embedded length (LLVAR/LLLVAR in ISO 8583 notation)
Parse number of given length in ASCII notation; Report bitmap field number in case of error.
Put number of given length in ASCII notation
:: Int | Number of bytes used for length (2 for LLVAR, 3 for LLLVAR and so on) |
-> ByteString | String to put |
-> Put |
Put string with embedded length (LLVAR/LLLVAR in ISO 8583 notation)
:: Int | Field length |
-> ByteString | String to put |
-> Put |
Put space-padded string of given length
:: Int64 | Field length |
-> ByteString | String to put |
-> Put |
Put space-padded string of given length
toBS :: String -> ByteString Source #
fromBS :: ByteString -> String Source #