{-# LANGUAGE DeriveAnyClass #-}
module SnelstartImport.N26
( readN26,
readN26BS,
N26 (..),
TransactionType(..),
Date(..)
)
where
import SnelstartImport.Currency
import Data.Text
import Data.Text.Encoding
import Data.Csv
import Data.Time
import GHC.Generics
import qualified Data.ByteString.Lazy as BS
import Data.Vector
data MutatieSoort = Overschijving | Diversen | Incasso
deriving Int -> MutatieSoort -> ShowS
[MutatieSoort] -> ShowS
MutatieSoort -> String
(Int -> MutatieSoort -> ShowS)
-> (MutatieSoort -> String)
-> ([MutatieSoort] -> ShowS)
-> Show MutatieSoort
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MutatieSoort -> ShowS
showsPrec :: Int -> MutatieSoort -> ShowS
$cshow :: MutatieSoort -> String
show :: MutatieSoort -> String
$cshowList :: [MutatieSoort] -> ShowS
showList :: [MutatieSoort] -> ShowS
Show
data BijAf = Bij | Af
deriving Int -> BijAf -> ShowS
[BijAf] -> ShowS
BijAf -> String
(Int -> BijAf -> ShowS)
-> (BijAf -> String) -> ([BijAf] -> ShowS) -> Show BijAf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BijAf -> ShowS
showsPrec :: Int -> BijAf -> ShowS
$cshow :: BijAf -> String
show :: BijAf -> String
$cshowList :: [BijAf] -> ShowS
showList :: [BijAf] -> ShowS
Show
data TransactionType = MastercardPayment | OutgoingTransfer | Income | N26Referal | DirectDebit
deriving stock (Int -> TransactionType -> ShowS
[TransactionType] -> ShowS
TransactionType -> String
(Int -> TransactionType -> ShowS)
-> (TransactionType -> String)
-> ([TransactionType] -> ShowS)
-> Show TransactionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TransactionType -> ShowS
showsPrec :: Int -> TransactionType -> ShowS
$cshow :: TransactionType -> String
show :: TransactionType -> String
$cshowList :: [TransactionType] -> ShowS
showList :: [TransactionType] -> ShowS
Show, TransactionType -> TransactionType -> Bool
(TransactionType -> TransactionType -> Bool)
-> (TransactionType -> TransactionType -> Bool)
-> Eq TransactionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TransactionType -> TransactionType -> Bool
== :: TransactionType -> TransactionType -> Bool
$c/= :: TransactionType -> TransactionType -> Bool
/= :: TransactionType -> TransactionType -> Bool
Eq)
instance FromField TransactionType where
parseField :: Field -> Parser TransactionType
parseField Field
field = case Field -> Text
decodeUtf8 Field
field of
Text
"Presentment" -> TransactionType -> Parser TransactionType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TransactionType
MastercardPayment
Text
"Debit Transfer" -> TransactionType -> Parser TransactionType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TransactionType
OutgoingTransfer
Text
"Income" -> TransactionType -> Parser TransactionType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TransactionType
Income
Text
"Credit Transfer" -> TransactionType -> Parser TransactionType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TransactionType
Income
Text
"Presentment Refund" -> TransactionType -> Parser TransactionType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TransactionType
Income
Text
"Reward" -> TransactionType -> Parser TransactionType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TransactionType
N26Referal
Text
"Direct Debit" -> TransactionType -> Parser TransactionType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TransactionType
DirectDebit
Text
other -> String -> Parser TransactionType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser TransactionType)
-> String -> Parser TransactionType
forall a b. (a -> b) -> a -> b
$ String
"TransactionType unkown" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
unpack Text
other
newtype Date = Date { Date -> UTCTime
unDate :: UTCTime }
deriving newtype (Int -> Date -> ShowS
[Date] -> ShowS
Date -> String
(Int -> Date -> ShowS)
-> (Date -> String) -> ([Date] -> ShowS) -> Show Date
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Date -> ShowS
showsPrec :: Int -> Date -> ShowS
$cshow :: Date -> String
show :: Date -> String
$cshowList :: [Date] -> ShowS
showList :: [Date] -> ShowS
Show, Date -> Date -> Bool
(Date -> Date -> Bool) -> (Date -> Date -> Bool) -> Eq Date
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Date -> Date -> Bool
== :: Date -> Date -> Bool
$c/= :: Date -> Date -> Bool
/= :: Date -> Date -> Bool
Eq, ReadPrec [Date]
ReadPrec Date
Int -> ReadS Date
ReadS [Date]
(Int -> ReadS Date)
-> ReadS [Date] -> ReadPrec Date -> ReadPrec [Date] -> Read Date
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Date
readsPrec :: Int -> ReadS Date
$creadList :: ReadS [Date]
readList :: ReadS [Date]
$creadPrec :: ReadPrec Date
readPrec :: ReadPrec Date
$creadListPrec :: ReadPrec [Date]
readListPrec :: ReadPrec [Date]
Read)
instance FromField Date where
parseField :: Field -> Parser Date
parseField Field
field =
(UTCTime -> Date) -> Parser UTCTime -> Parser Date
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap UTCTime -> Date
Date (Parser UTCTime -> Parser Date) -> Parser UTCTime -> Parser Date
forall a b. (a -> b) -> a -> b
$ Bool -> TimeLocale -> String -> String -> Parser UTCTime
forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> String -> String -> m t
parseTimeM Bool
True TimeLocale
defaultTimeLocale String
"%Y-%m-%d" (String -> Parser UTCTime) -> String -> Parser UTCTime
forall a b. (a -> b) -> a -> b
$ Text -> String
unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Field -> Text
decodeUtf8 Field
field
data N26 = N26 {
N26 -> Date
date :: Date,
N26 -> Date
valueDate :: Date,
N26 -> Text
payee :: Text,
N26 -> Text
accountNumber :: Text,
N26 -> TransactionType
transactionType :: TransactionType,
N26 -> Text
paymentReference :: Text,
N26 -> Text
accountName :: Text,
N26 -> Currency
amountEur :: Currency ,
N26 -> Maybe Currency
amountForegin :: Maybe Currency ,
N26 -> Text
typeForeign :: Text,
N26 -> Text
exchangeRate :: Text
}
deriving stock ((forall x. N26 -> Rep N26 x)
-> (forall x. Rep N26 x -> N26) -> Generic N26
forall x. Rep N26 x -> N26
forall x. N26 -> Rep N26 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. N26 -> Rep N26 x
from :: forall x. N26 -> Rep N26 x
$cto :: forall x. Rep N26 x -> N26
to :: forall x. Rep N26 x -> N26
Generic, Int -> N26 -> ShowS
[N26] -> ShowS
N26 -> String
(Int -> N26 -> ShowS)
-> (N26 -> String) -> ([N26] -> ShowS) -> Show N26
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> N26 -> ShowS
showsPrec :: Int -> N26 -> ShowS
$cshow :: N26 -> String
show :: N26 -> String
$cshowList :: [N26] -> ShowS
showList :: [N26] -> ShowS
Show, N26 -> N26 -> Bool
(N26 -> N26 -> Bool) -> (N26 -> N26 -> Bool) -> Eq N26
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: N26 -> N26 -> Bool
== :: N26 -> N26 -> Bool
$c/= :: N26 -> N26 -> Bool
/= :: N26 -> N26 -> Bool
Eq)
deriving anyclass Record -> Parser N26
(Record -> Parser N26) -> FromRecord N26
forall a. (Record -> Parser a) -> FromRecord a
$cparseRecord :: Record -> Parser N26
parseRecord :: Record -> Parser N26
FromRecord
readN26 :: FilePath -> IO (Either String (Vector N26))
readN26 :: String -> IO (Either String (Vector N26))
readN26 String
path = do
ByteString
lines' <- String -> IO ByteString
BS.readFile String
path
Either String (Vector N26) -> IO (Either String (Vector N26))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String (Vector N26) -> IO (Either String (Vector N26)))
-> Either String (Vector N26) -> IO (Either String (Vector N26))
forall a b. (a -> b) -> a -> b
$ ByteString -> Either String (Vector N26)
readN26BS ByteString
lines'
readN26BS :: BS.ByteString -> Either String (Vector N26)
readN26BS :: ByteString -> Either String (Vector N26)
readN26BS = HasHeader -> ByteString -> Either String (Vector N26)
forall a.
FromRecord a =>
HasHeader -> ByteString -> Either String (Vector a)
decode HasHeader
HasHeader