{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE QuasiQuotes #-}
module SnelstartImport.ING
( ING(..),
toCode,
writeCsv,
MutatieSoort (..),
BijAf(..)
)
where
import SnelstartImport.Currency
import Data.Text
import Data.Text.Encoding
import Data.Csv
import Data.Time
import GHC.Generics
import qualified Data.Vector as Vector
import NeatInterpolation(text)
import qualified Data.ByteString.Lazy as LBS
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
mutatieSoortToFIeld :: MutatieSoort -> Text
mutatieSoortToFIeld :: MutatieSoort -> Text
mutatieSoortToFIeld = \case
MutatieSoort
Overschijving -> Text
"Overschrijving"
MutatieSoort
Diversen -> Text
"Diversen"
MutatieSoort
Incasso -> Text
"Incasso"
toCode :: MutatieSoort -> Text
toCode :: MutatieSoort -> Text
toCode = \case
MutatieSoort
Overschijving -> Text
"OV"
MutatieSoort
Diversen -> Text
"DV"
MutatieSoort
Incasso -> Text
"IC"
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
bijAfToField :: BijAf -> Text
bijAfToField :: BijAf -> Text
bijAfToField = \case
BijAf
Bij -> Text
"Bij"
BijAf
Af -> Text
"Af"
data ING = ING {
ING -> UTCTime
datum :: UTCTime,
ING -> Text
naamBescrhijving :: Text,
ING -> Text
rekening :: Text,
ING -> Text
tegenRekening :: Text,
ING -> MutatieSoort
mutatieSoort :: MutatieSoort,
ING -> BijAf
bijAf :: BijAf,
ING -> Currency
bedragEur :: Currency ,
ING -> Text
mededeling :: Text
}
deriving stock ((forall x. ING -> Rep ING x)
-> (forall x. Rep ING x -> ING) -> Generic ING
forall x. Rep ING x -> ING
forall x. ING -> Rep ING x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ING -> Rep ING x
from :: forall x. ING -> Rep ING x
$cto :: forall x. Rep ING x -> ING
to :: forall x. Rep ING x -> ING
Generic, Int -> ING -> ShowS
[ING] -> ShowS
ING -> String
(Int -> ING -> ShowS)
-> (ING -> String) -> ([ING] -> ShowS) -> Show ING
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ING -> ShowS
showsPrec :: Int -> ING -> ShowS
$cshow :: ING -> String
show :: ING -> String
$cshowList :: [ING] -> ShowS
showList :: [ING] -> ShowS
Show)
instance ToRecord ING where
toRecord :: ING -> Record
toRecord (ING{Text
UTCTime
Currency
BijAf
MutatieSoort
datum :: ING -> UTCTime
naamBescrhijving :: ING -> Text
rekening :: ING -> Text
tegenRekening :: ING -> Text
mutatieSoort :: ING -> MutatieSoort
bijAf :: ING -> BijAf
bedragEur :: ING -> Currency
mededeling :: ING -> Text
datum :: UTCTime
naamBescrhijving :: Text
rekening :: Text
tegenRekening :: Text
mutatieSoort :: MutatieSoort
bijAf :: BijAf
bedragEur :: Currency
mededeling :: Text
..}) =
[Field] -> Record
forall a. [a] -> Vector a
Vector.fromList
[ String -> Field
forall a. ToField a => a -> Field
toField (String -> Field) -> String -> Field
forall a b. (a -> b) -> a -> b
$ TimeLocale -> String -> UTCTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%Y%m%d" UTCTime
datum
, Text -> Field
forall a. ToField a => a -> Field
toField Text
naamBescrhijving
, Text -> Field
forall a. ToField a => a -> Field
toField Text
rekening
, Text -> Field
forall a. ToField a => a -> Field
toField Text
tegenRekening
, Text -> Field
forall a. ToField a => a -> Field
toField (Text -> Field) -> Text -> Field
forall a b. (a -> b) -> a -> b
$ MutatieSoort -> Text
toCode MutatieSoort
mutatieSoort
, Text -> Field
forall a. ToField a => a -> Field
toField (Text -> Field) -> Text -> Field
forall a b. (a -> b) -> a -> b
$ BijAf -> Text
bijAfToField BijAf
bijAf
, String -> Field
forall a. ToField a => a -> Field
toField (String -> Field) -> String -> Field
forall a b. (a -> b) -> a -> b
$ Char -> Char
replaceDotWithComma (Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Currency -> String
forall a. Show a => a -> String
Prelude.show Currency
bedragEur
, Text -> Field
forall a. ToField a => a -> Field
toField (Text -> Field) -> Text -> Field
forall a b. (a -> b) -> a -> b
$ MutatieSoort -> Text
mutatieSoortToFIeld MutatieSoort
mutatieSoort
, Text -> Field
forall a. ToField a => a -> Field
toField Text
mededeling
]
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)
replaceDotWithComma :: Char -> Char
replaceDotWithComma :: Char -> Char
replaceDotWithComma Char
'.' = Char
','
replaceDotWithComma Char
other = Char
other
instance FromField TransactionType where
parseField :: Field -> Parser TransactionType
parseField Field
field = case Field -> Text
decodeUtf8 Field
field of
Text
"MasterCard Payment" -> TransactionType -> Parser TransactionType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TransactionType
MastercardPayment
Text
"Outgoing 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
"N26 Referral" -> 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 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
writeCsv :: [ING] -> LBS.ByteString
writeCsv :: [ING] -> ByteString
writeCsv [ING]
lines' = Field -> ByteString
LBS.fromStrict Field
header' ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
data'
where
data' :: LBS.ByteString
data' :: ByteString
data' = EncodeOptions -> [ING] -> ByteString
forall a. ToRecord a => EncodeOptions -> [a] -> ByteString
encodeWith EncodeOptions
opts [ING]
lines'
header' :: Field
header' = Text -> Field
encodeUtf8 (Text -> Field) -> Text -> Field
forall a b. (a -> b) -> a -> b
$ [text|"Datum","Naam / Omschrijving","Rekening","Tegenrekening","Code","Af Bij","Bedrag (EUR)","Mutatiesoort","Mededelingen"|] Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n"
opts :: EncodeOptions
opts :: EncodeOptions
opts = EncodeOptions
defaultEncodeOptions { encQuoting = QuoteAll}