ofx-0.4.4.0: Parser for OFX data

Safe HaskellSafe
LanguageHaskell2010

Data.OFX

Contents

Description

Parser for downloaded OFX files.

This parser was written based on the OFX version 1.03 specification, which is available at

http://www.ofx.net

It will probably work on earlier versions of OFX without incident. However, it may or may not not work on newer versions of OFX, which are XML based (this version of OFX is SGML based.)

It will also parse QFX files, which are OFX files with minor proprietary additions by Intuit, the maker of Quicken.

An OFX file consists of three parts: the HTTP headers (which this parser does NOT handle because typically they will not show up in files downloaded to disk), the OFX headers, and the OFX data. This parser handles the OFX headers and the OFX data.

The parser in this module simply parses the tags and data into a tree, which you can manipulate with other functions. Some functions are provided to find the transactions in the tree and place them into a Transaction type, which is the data you are most likely interested in. If you are interested in other data you can query the Tag tree for what you need.

The ofx package includes two executable files that you can use at the command line to test the library and see how it works. The renderTransactions executable reads an OFX file on standard input, runs it through the prettyRenderTransactions function, and prints the result to standard output. The renderOfx executable reads an OFX file on standard input, runs it through the prettyRenderOfxFile function, and prints the result to standard output.

Synopsis

Error handling

type Err = Either String Source #

Error handling. Errors are indicated with a Left String; successes with a Right.

The OFX data tree

type HeaderTag = String Source #

Headers consists of simple tag:value pairs; this represents the tag.

type HeaderValue = String Source #

The value in an OFX header.

data OFXHeader Source #

An OFX file starts with a number of headers, which take the form tag:value followed by a newline. These are followed by a blank line.

Instances
Eq OFXHeader Source # 
Instance details

Defined in Data.OFX

Data OFXHeader Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: OFXHeader -> Constr #

dataTypeOf :: OFXHeader -> DataType #

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

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

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

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

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

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

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

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

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

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

Read OFXHeader Source # 
Instance details

Defined in Data.OFX

Show OFXHeader Source # 
Instance details

Defined in Data.OFX

Generic OFXHeader Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep OFXHeader :: Type -> Type #

type Rep OFXHeader Source # 
Instance details

Defined in Data.OFX

type TagName = String Source #

The name of an OFX tag

type TagData = String Source #

The data accompanying an OFX tag.

data Tag Source #

The main OFX data consists of a series of tags. OFX 1.03 is SGML, not XML. This means that opening tags need not have closing tags. In OFX, a tag either has data and no child elements, or it has no data and it has child elements.

Constructors

Tag TagName (Either TagData [Tag]) 
Instances
Eq Tag Source # 
Instance details

Defined in Data.OFX

Methods

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

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

Data Tag Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Tag Source # 
Instance details

Defined in Data.OFX

Show Tag Source # 
Instance details

Defined in Data.OFX

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

type Rep Tag Source # 
Instance details

Defined in Data.OFX

data OFXFile Source #

All the data from an OFX file.

Constructors

OFXFile 

Fields

Instances
Eq OFXFile Source # 
Instance details

Defined in Data.OFX

Methods

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

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

Data OFXFile Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: OFXFile -> Constr #

dataTypeOf :: OFXFile -> DataType #

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

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

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

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

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

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

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

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

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

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

Read OFXFile Source # 
Instance details

Defined in Data.OFX

Show OFXFile Source # 
Instance details

Defined in Data.OFX

Generic OFXFile Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep OFXFile :: Type -> Type #

Methods

from :: OFXFile -> Rep OFXFile x #

to :: Rep OFXFile x -> OFXFile #

type Rep OFXFile Source # 
Instance details

Defined in Data.OFX

type Rep OFXFile = D1 (MetaData "OFXFile" "Data.OFX" "ofx-0.4.4.0-4RaBzGShUblBGqFbadwzIr" False) (C1 (MetaCons "OFXFile" PrefixI True) (S1 (MetaSel (Just "fHeader") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [OFXHeader]) :*: S1 (MetaSel (Just "fTag") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tag)))

Manipulating the OFX tag tree

find :: TagName -> Tag -> [Tag] Source #

Finds child tags with the given name. When a tag is found, that tag is not searched for further children with the same name.

findPath :: [TagName] -> Tag -> Maybe Tag Source #

Descends through a tree of tags to find a tag at a specific location in the tree. Fails if any part of the search fails. For example, to find the financial institution ORG tag, where t is the root OFX tag:

findPath ["SIGNONMSGSRSV1", "SONRS", "FI", "ORG"] t

tagData :: Tag -> Maybe TagData Source #

Gets the data from a tag, if it is a tag with data.

pathData :: [TagName] -> OFXFile -> Maybe TagData Source #

Goes to a certain path in the tag hierarchy and pulls the requested data, if the tag is present and it is a data tag. For example, to get the name of the financial institution:

pathData ["SIGNONMSGSRSV1", "SONRS", "FI", "ORG"] f

findData :: TagName -> Tag -> Maybe TagData Source #

Finds the first tag (either this tag or any children) that has the given name and that is a data tag (not an aggregate tag.) If no data tag with the given name is found, returns Nothing.

Extracting specific data

fiName :: OFXFile -> Maybe TagData Source #

Gets the name of the financial institution from the FI tag, if available. The OFX spec does not require this tag to be present.

creditCardNumber :: OFXFile -> Maybe TagData Source #

Gets the credit card number, if available. The OFX spec does not require this tag to be present.

bankAccountNumber :: OFXFile -> Maybe TagData Source #

Gets the bank account number, if available. The OFX spec does not require this tag to be present.

accountNumber :: OFXFile -> Maybe TagData Source #

Gets either the credit card or bank account number, if available.

Types to represent specific OFX data

data Transaction Source #

A single STMTTRN, see OFX spec section 11.4.2.3.1. This is most likely what you are interested in after downloading a statement from a bank.

Constructors

Transaction 

Fields

  • txTRNTYPE :: TrnType

    Transaction type

  • txDTPOSTED :: ZonedTime

    Date transaction was posted to account

  • txDTUSER :: Maybe ZonedTime

    Date user initiated transaction, if known

  • txDTAVAIL :: Maybe ZonedTime

    Date funds are available

  • txTRNAMT :: String

    Amount of transaction. This is left as the string that was originally in the download. That means the transaction may include a plus or minus sign (no sign is the same as a plus sign.) According to section 3.2.9.2, amounts are always signed from the perspective of the customer.

    Typically negative amounts:

    • Investment buy amount, investment sell quantity
    • Bank statement debit amounts, checks, fees
    • Credit card purchases
    • Margin balance (unless the institution owes the client money)

    Typically positive amounts:

    • Investment sell amount, investment buy quantity
    • Bank statement credits
    • Credit card payments
    • Ledger balance (unless the account is overdrawn)

    Formats for amounts are described in 3.2.9.1. If there is no decimal point, there is an implied decimal point at the end of the value. Trailing and leading spaces "should" be stripped. Positive or minus is indicated with a leading sign; a plus sign is assumed if there is no sign.

    An amount has a maximum of 32 alphanumeric characters, including digits and punctuation.

    The radix point is indicated with either a period or a comma. Amounts "should" not include any digit grouping characters.

  • txFITID :: String

    Transaction ID issued by financial institution. Used to detect duplicate downloads.

  • txCORRECTFITID :: Maybe String

    If present, this indicates the FITID of a previously sent transaction that is corrected by this record. This transaction replaces or deletes the transaction that it corrects, based on the value of CORRECTACTION below.

  • txCORRECTACTION :: Maybe CorrectAction
  • txSRVRTID :: Maybe String

    Server assigned transaction ID; used for transactions initiated by client, such as payment or funds transfer

  • txCHECKNUM :: Maybe String

    Check or other reference number

  • txREFNUM :: Maybe String

    Reference number that uniquely identifies the transaction. Can be used in addition to or instead of a CHECKNUM.

  • txSIC :: Maybe String

    Standard Industrial Code

  • txPAYEEID :: Maybe String

    Payee identifier if available

  • txPayeeInfo :: Maybe (Either String Payee)

    Information on the payee. The OFX spec seems to be saying that every transaction must have either NAME, wich is "name of payee or description of transaction", or the Payee aggregate. The former is indicated with a Left, the latter with a Right.

  • txAccountTo :: Maybe (Either BankAcctTo CCAcctTo)

    Information on a transfer. If this transaction wa sa transfer, this may contain information about the account being transferred to.

  • txMEMO :: Maybe String

    Extra information not in NAME

  • txCurrency :: Maybe (Either Currency OrigCurrency)

    Currency option. OFX spec says to choose either CURRENCY or ORIGCURRENCY.

Instances
Data Transaction Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: Transaction -> Constr #

dataTypeOf :: Transaction -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Transaction Source # 
Instance details

Defined in Data.OFX

Show Transaction Source # 
Instance details

Defined in Data.OFX

Generic Transaction Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep Transaction :: Type -> Type #

type Rep Transaction Source # 
Instance details

Defined in Data.OFX

type Rep Transaction = D1 (MetaData "Transaction" "Data.OFX" "ofx-0.4.4.0-4RaBzGShUblBGqFbadwzIr" False) (C1 (MetaCons "Transaction" PrefixI True) ((((S1 (MetaSel (Just "txTRNTYPE") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TrnType) :*: S1 (MetaSel (Just "txDTPOSTED") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ZonedTime)) :*: (S1 (MetaSel (Just "txDTUSER") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ZonedTime)) :*: S1 (MetaSel (Just "txDTAVAIL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ZonedTime)))) :*: ((S1 (MetaSel (Just "txTRNAMT") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "txFITID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "txCORRECTFITID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)) :*: S1 (MetaSel (Just "txCORRECTACTION") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CorrectAction))))) :*: (((S1 (MetaSel (Just "txSRVRTID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)) :*: S1 (MetaSel (Just "txCHECKNUM") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) :*: (S1 (MetaSel (Just "txREFNUM") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)) :*: S1 (MetaSel (Just "txSIC") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)))) :*: ((S1 (MetaSel (Just "txPAYEEID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)) :*: S1 (MetaSel (Just "txPayeeInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Either String Payee)))) :*: (S1 (MetaSel (Just "txAccountTo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Either BankAcctTo CCAcctTo))) :*: (S1 (MetaSel (Just "txMEMO") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)) :*: S1 (MetaSel (Just "txCurrency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Either Currency OrigCurrency)))))))))

transaction :: Tag -> Err Transaction Source #

Gets a single Transaction from a tag. The tag should be the one named STMTTRN. Fails with an error message if any required field was not present.

transactions :: OFXFile -> Err [Transaction] Source #

Pulls all Transactions from a file. Might fail if the OFX file does not conform to the specification (or if there are bugs in this library.) In case of the former, you can manually parse the transaction information yourself using functions like pathData. In case of the latter, please send bugreports :-)

data TrnType Source #

OFX transaction types. These are used in STMTTRN aggregates, see OFX spec section 11.4.2.3.1.1.

Constructors

TCREDIT 
TDEBIT 
TINT

Interest earned or paid (which it is depends on sign of amount)

TDIV

Dividend

TFEE 
TSRVCHG 
TDEP

Deposit

TATM

ATM debit or credit (which it is depends on sign of amount)

TPOS

Point of sale debit or credit (which it is depends on sign of amount)

TXFER

Transfer

TCHECK 
TPAYMENT

Electronic payment

TCASH

Cash withdrawal

TDIRECTDEP

Direct deposit

TDIRECTDEBIT

Merchant initiated debit

TREPEATPMT

Repeating payment / standing order

TOTHER 
Instances
Eq TrnType Source # 
Instance details

Defined in Data.OFX

Methods

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

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

Data TrnType Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: TrnType -> Constr #

dataTypeOf :: TrnType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TrnType Source # 
Instance details

Defined in Data.OFX

Read TrnType Source # 
Instance details

Defined in Data.OFX

Show TrnType Source # 
Instance details

Defined in Data.OFX

Generic TrnType Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep TrnType :: Type -> Type #

Methods

from :: TrnType -> Rep TrnType x #

to :: Rep TrnType x -> TrnType #

type Rep TrnType Source # 
Instance details

Defined in Data.OFX

type Rep TrnType = D1 (MetaData "TrnType" "Data.OFX" "ofx-0.4.4.0-4RaBzGShUblBGqFbadwzIr" False) ((((C1 (MetaCons "TCREDIT" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TDEBIT" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TINT" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TDIV" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "TFEE" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TSRVCHG" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TDEP" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TATM" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "TPOS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TXFER" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TCHECK" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TPAYMENT" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "TCASH" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TDIRECTDEP" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TDIRECTDEBIT" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TREPEATPMT" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TOTHER" PrefixI False) (U1 :: Type -> Type))))))

data Payee Source #

Instances
Eq Payee Source # 
Instance details

Defined in Data.OFX

Methods

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

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

Data Payee Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: Payee -> Constr #

dataTypeOf :: Payee -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Payee Source # 
Instance details

Defined in Data.OFX

Show Payee Source # 
Instance details

Defined in Data.OFX

Methods

showsPrec :: Int -> Payee -> ShowS #

show :: Payee -> String #

showList :: [Payee] -> ShowS #

Generic Payee Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep Payee :: Type -> Type #

Methods

from :: Payee -> Rep Payee x #

to :: Rep Payee x -> Payee #

type Rep Payee Source # 
Instance details

Defined in Data.OFX

payee Source #

Arguments

:: Tag

The tag which contains the PAYEE tag, if there is one. This would typically be a STMTTRN tag.

-> Maybe (Err Payee)

Nothing if there is no PAYEE tag. Just if a PAYEE tag is found, with a Left if the tag is lacking a required element, or a Right if the tag is successfully parsed.

If there is more than one PAYEE tag, only the first one is considered.

Parses a Payee record from its parent tag.

data CorrectAction Source #

Can be either REPLACE or DELETE.

Constructors

REPLACE

Replaces the transaction referenced by the CORRECTFITID

DELETE

Deletes the transaction referenced by the CORRECTFITID

Instances
Eq CorrectAction Source # 
Instance details

Defined in Data.OFX

Data CorrectAction Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: CorrectAction -> Constr #

dataTypeOf :: CorrectAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CorrectAction Source # 
Instance details

Defined in Data.OFX

Show CorrectAction Source # 
Instance details

Defined in Data.OFX

Generic CorrectAction Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep CorrectAction :: Type -> Type #

type Rep CorrectAction Source # 
Instance details

Defined in Data.OFX

type Rep CorrectAction = D1 (MetaData "CorrectAction" "Data.OFX" "ofx-0.4.4.0-4RaBzGShUblBGqFbadwzIr" False) (C1 (MetaCons "REPLACE" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DELETE" PrefixI False) (U1 :: Type -> Type))

data BankAcctTo Source #

Constructors

BankAcctTo 

Fields

Instances
Data BankAcctTo Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: BankAcctTo -> Constr #

dataTypeOf :: BankAcctTo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BankAcctTo Source # 
Instance details

Defined in Data.OFX

Show BankAcctTo Source # 
Instance details

Defined in Data.OFX

Generic BankAcctTo Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep BankAcctTo :: Type -> Type #

type Rep BankAcctTo Source # 
Instance details

Defined in Data.OFX

data CCAcctTo Source #

Constructors

CCAcctTo 

Fields

Instances
Eq CCAcctTo Source # 
Instance details

Defined in Data.OFX

Data CCAcctTo Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: CCAcctTo -> Constr #

dataTypeOf :: CCAcctTo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CCAcctTo Source # 
Instance details

Defined in Data.OFX

Show CCAcctTo Source # 
Instance details

Defined in Data.OFX

Generic CCAcctTo Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep CCAcctTo :: Type -> Type #

Methods

from :: CCAcctTo -> Rep CCAcctTo x #

to :: Rep CCAcctTo x -> CCAcctTo #

type Rep CCAcctTo Source # 
Instance details

Defined in Data.OFX

type Rep CCAcctTo = D1 (MetaData "CCAcctTo" "Data.OFX" "ofx-0.4.4.0-4RaBzGShUblBGqFbadwzIr" False) (C1 (MetaCons "CCAcctTo" PrefixI True) (S1 (MetaSel (Just "ctACCTID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "ctACCTKEY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))))

data AcctType Source #

Instances
Eq AcctType Source # 
Instance details

Defined in Data.OFX

Data AcctType Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: AcctType -> Constr #

dataTypeOf :: AcctType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AcctType Source # 
Instance details

Defined in Data.OFX

Read AcctType Source # 
Instance details

Defined in Data.OFX

Show AcctType Source # 
Instance details

Defined in Data.OFX

Generic AcctType Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep AcctType :: Type -> Type #

Methods

from :: AcctType -> Rep AcctType x #

to :: Rep AcctType x -> AcctType #

type Rep AcctType Source # 
Instance details

Defined in Data.OFX

type Rep AcctType = D1 (MetaData "AcctType" "Data.OFX" "ofx-0.4.4.0-4RaBzGShUblBGqFbadwzIr" False) ((C1 (MetaCons "ACHECKING" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ASAVINGS" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "AMONEYMRKT" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ACREDITLINE" PrefixI False) (U1 :: Type -> Type)))

data CurrencyData Source #

Holds all data both for CURRENCY and for ORIGCURRENCY.

Constructors

CurrencyData 

Fields

Instances
Eq CurrencyData Source # 
Instance details

Defined in Data.OFX

Data CurrencyData Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: CurrencyData -> Constr #

dataTypeOf :: CurrencyData -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CurrencyData Source # 
Instance details

Defined in Data.OFX

Show CurrencyData Source # 
Instance details

Defined in Data.OFX

Generic CurrencyData Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep CurrencyData :: Type -> Type #

type Rep CurrencyData Source # 
Instance details

Defined in Data.OFX

type Rep CurrencyData = D1 (MetaData "CurrencyData" "Data.OFX" "ofx-0.4.4.0-4RaBzGShUblBGqFbadwzIr" False) (C1 (MetaCons "CurrencyData" PrefixI True) (S1 (MetaSel (Just "cdCURRATE") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "cdCURSYM") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

currencyData Source #

Arguments

:: Tag

The tag that contains the data, e.g. CURRENCY or ORIGCURRENCY.

-> Err CurrencyData 

Parses currency data.

data Currency Source #

Constructors

Currency CurrencyData 
Instances
Eq Currency Source # 
Instance details

Defined in Data.OFX

Data Currency Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: Currency -> Constr #

dataTypeOf :: Currency -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Currency Source # 
Instance details

Defined in Data.OFX

Show Currency Source # 
Instance details

Defined in Data.OFX

Generic Currency Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep Currency :: Type -> Type #

Methods

from :: Currency -> Rep Currency x #

to :: Rep Currency x -> Currency #

type Rep Currency Source # 
Instance details

Defined in Data.OFX

type Rep Currency = D1 (MetaData "Currency" "Data.OFX" "ofx-0.4.4.0-4RaBzGShUblBGqFbadwzIr" False) (C1 (MetaCons "Currency" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CurrencyData)))

data OrigCurrency Source #

Instances
Eq OrigCurrency Source # 
Instance details

Defined in Data.OFX

Data OrigCurrency Source # 
Instance details

Defined in Data.OFX

Methods

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

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

toConstr :: OrigCurrency -> Constr #

dataTypeOf :: OrigCurrency -> DataType #

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

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

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

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

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

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

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

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

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

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

Read OrigCurrency Source # 
Instance details

Defined in Data.OFX

Show OrigCurrency Source # 
Instance details

Defined in Data.OFX

Generic OrigCurrency Source # 
Instance details

Defined in Data.OFX

Associated Types

type Rep OrigCurrency :: Type -> Type #

type Rep OrigCurrency Source # 
Instance details

Defined in Data.OFX

type Rep OrigCurrency = D1 (MetaData "OrigCurrency" "Data.OFX" "ofx-0.4.4.0-4RaBzGShUblBGqFbadwzIr" False) (C1 (MetaCons "OrigCurrency" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CurrencyData)))

Running parsers

parseOfxFile :: String -> Err OFXFile Source #

Parses an input file. Returns either an error message or the resulting OFXFile.

loadOfxFile :: FilePath -> IO OFXFile Source #

Loads an OFX file from disk, parses it, and returns the resulting OFXFile. Uses fail if the parse fails.

parseTransactions :: String -> Err [Transaction] Source #

Parses an OFX file and gets the list of Transaction.

loadTransactions :: FilePath -> IO [Transaction] Source #

Loads an OFX file from disk, parses it, and returns the resulting list of Transaction. Uses fail if the parse fails.

prettyRenderOfxFile Source #

Arguments

:: String

File contents to parse

-> String

Pretty printed result of rending the result of the parse, which is either an error message or an OFXFile.

Parses an input file to an OfxFile. Returns a pretty-printed string with the results of the parse.

prettyRenderTransactions Source #

Arguments

:: String

File contents to parse

-> String

Pretty printed result of rendering the result of the parse, which is either an error message or a list of Transaction.

Parses an input file to an OfxFile, and then to a list of Transaction. Returns a pretty-printed string with the results.

Parsec parsers

ofxFile :: Parser OFXFile Source #

Parses an entire OFX file, including headers.

newline :: Parser () Source #

Parses either a UNIX or an MS-DOS newline. According to 1.2.2, OFX does not contain any white space between tags. However, since I have seen OFX files that do have whitespace between tags, the parser makes allowance for this.

escChar :: Parser Char Source #

Parses a character, possibly with an escape sequence. The greater-than sign, less-than sign, and ampersand must be entered with escape sequences.

According to OFX spec section 2.3.2.1, ampersands, less-than signs, and greater-than signs must appear as entities. However some banks deliver broken OFX files that do not use entities for ampersands (and possibly for less-than or greater-than signs too, although I have not yet observed such behavior.) There is now an error message that reflects this problem. Client code can filter the OFX data for known offenders before passing it to this library.

openingTag :: Parser TagName Source #

Parses any opening tag. Returns the name of the tag.

closingTag :: TagName -> Parser () Source #

Parses a closing tag with the given name.

tag :: Parser Tag Source #

Parses any tag. The tag itself must be followed by at least one character: either the next tag if this is an aggregate tag, or the data if this is a data tag. OFX does not allow empty tags.

The OFX spec seems to say that OFX files do not include trailing newlines after tags or data, but I have seen these newlines in QFX files, so this parses optional trailing newlines and spaces.

date :: Parser ZonedTime Source #

Parses an OFX date. Fails if the date is not valid or if there is no date to be parsed.

time :: Parser (TimeOfDay, TimeZone) Source #

Parses an OFX time. Fails if the time is not valid or if there is no time to parse. Fails if there is no time to parse; however, if there is a time but no zone, returns the time and UTC for the zone.

tzOffset :: Parser TimeZone Source #

Parses a time zone offset. Fails if there is no time zone offset to parse.

Pretty printers

pEither :: (a -> Doc) -> (b -> Doc) -> Either a b -> Doc Source #

pMaybe :: (a -> Doc) -> Maybe a -> Doc Source #

pList :: [Doc] -> Doc Source #

pExceptional :: (e -> Doc) -> (a -> Doc) -> Either e a -> Doc Source #