implement cash checks
This commit is contained in:
parent
bfd334871a
commit
142d5da6b2
4 changed files with 53 additions and 1 deletions
|
@ -179,6 +179,7 @@ app initState =
|
||||||
buy :<|>
|
buy :<|>
|
||||||
|
|
||||||
journalShow :<|>
|
journalShow :<|>
|
||||||
|
journalCheck :<|>
|
||||||
|
|
||||||
avatarGet :<|>
|
avatarGet :<|>
|
||||||
avatarInsert :<|>
|
avatarInsert :<|>
|
||||||
|
|
|
@ -55,7 +55,11 @@ type MateAPI =
|
||||||
:> Post '[JSON] PurchaseResult
|
:> Post '[JSON] PurchaseResult
|
||||||
|
|
||||||
:<|> "journal" :> AuthProtect "header-auth" :> QueryParam "limit" Int
|
:<|> "journal" :> AuthProtect "header-auth" :> QueryParam "limit" Int
|
||||||
:> QueryParam "offset" Int :> Get '[JSON] [JournalEntry]
|
:> QueryParam "offset" Int
|
||||||
|
:> Get '[JSON] [JournalEntry]
|
||||||
|
:<|> "journal" :> AuthProtect "header-auth"
|
||||||
|
:> ReqBody '[JSON] JournalCashCheck
|
||||||
|
:> Post '[JSON] ()
|
||||||
|
|
||||||
:<|> "avatar" :> Capture "id" Int :> RawM
|
:<|> "avatar" :> Capture "id" Int :> RawM
|
||||||
:<|> "avatar" :> AuthProtect "header-auth" :> ReqBody '[JSON] AvatarData
|
:<|> "avatar" :> AuthProtect "header-auth" :> ReqBody '[JSON] AvatarData
|
||||||
|
@ -90,6 +94,7 @@ productShortListLink :: Maybe ProductRefine -> Link
|
||||||
buyLink :: Link
|
buyLink :: Link
|
||||||
|
|
||||||
journalShowLink :: Maybe Int -> Maybe Int -> Link
|
journalShowLink :: Maybe Int -> Maybe Int -> Link
|
||||||
|
journalPostCheck :: Link
|
||||||
|
|
||||||
-- avatarGetLink :: Int -> Link
|
-- avatarGetLink :: Int -> Link
|
||||||
avaterInsertLink :: Link
|
avaterInsertLink :: Link
|
||||||
|
@ -121,6 +126,7 @@ avatarListLink :: Link
|
||||||
buyLink :<|>
|
buyLink :<|>
|
||||||
|
|
||||||
journalShowLink :<|>
|
journalShowLink :<|>
|
||||||
|
journalPostCheck :<|>
|
||||||
|
|
||||||
avatarGetLink :<|>
|
avatarGetLink :<|>
|
||||||
avaterInsertLink :<|>
|
avaterInsertLink :<|>
|
||||||
|
|
|
@ -3,6 +3,7 @@ module Control.Journal where
|
||||||
|
|
||||||
import Servant
|
import Servant
|
||||||
|
|
||||||
|
import Control.Monad (void)
|
||||||
import Control.Monad.Reader (asks)
|
import Control.Monad.Reader (asks)
|
||||||
|
|
||||||
-- internal imports
|
-- internal imports
|
||||||
|
@ -28,3 +29,21 @@ journalShow Nothing _ _ =
|
||||||
throwError $ err401
|
throwError $ err401
|
||||||
{ errBody = "No Authentication present"
|
{ errBody = "No Authentication present"
|
||||||
}
|
}
|
||||||
|
|
||||||
|
journalCheck
|
||||||
|
:: Maybe (Int, AuthMethod)
|
||||||
|
-> JournalCashCheck
|
||||||
|
-> MateHandler ()
|
||||||
|
journalCheck (Just (_, method)) check = do
|
||||||
|
if method `elem` [PrimaryPass, ChallengeResponse]
|
||||||
|
then do
|
||||||
|
conn <- asks rsConnection
|
||||||
|
void $ insertNewCashCheck check conn
|
||||||
|
else
|
||||||
|
throwError $ err401
|
||||||
|
{ errBody = "Wrong Authentication present"
|
||||||
|
}
|
||||||
|
journalCheck Nothing _ =
|
||||||
|
throwError $ err401
|
||||||
|
{ errBody = "No Authentication present"
|
||||||
|
}
|
||||||
|
|
|
@ -151,3 +151,29 @@ insertNewJournalEntry (JournalSubmit descr amount) conn = do
|
||||||
, iReturning = rReturning (\(id_, _, _, _, _) -> id_)
|
, iReturning = rReturning (\(id_, _, _, _, _) -> id_)
|
||||||
, iOnConflict = Nothing
|
, iOnConflict = Nothing
|
||||||
}
|
}
|
||||||
|
|
||||||
|
insertNewCashCheck
|
||||||
|
:: JournalCashCheck
|
||||||
|
-> PGS.Connection
|
||||||
|
-> MateHandler Int
|
||||||
|
insertNewCashCheck (JournalCashCheck amount) conn = do
|
||||||
|
-- lastTotal <- (\case
|
||||||
|
-- Just j -> journalEntryTotalAmount j
|
||||||
|
-- Nothing -> 0
|
||||||
|
-- ) <$> selectLatestJournalEntry conn
|
||||||
|
liftIO $ do
|
||||||
|
now <- getCurrentTime
|
||||||
|
fmap head $ runInsert_ conn $ Insert
|
||||||
|
{ iTable = journalTable
|
||||||
|
, iRows =
|
||||||
|
[
|
||||||
|
( C.constant (Nothing :: Maybe Int)
|
||||||
|
, C.constant now
|
||||||
|
, C.constant ("Cash check" :: String)
|
||||||
|
, C.constant amount
|
||||||
|
, C.constant True
|
||||||
|
)
|
||||||
|
]
|
||||||
|
, iReturning = rReturning (\(id_, _, _, _, _) -> id_)
|
||||||
|
, iOnConflict = Nothing
|
||||||
|
}
|
||||||
|
|
Loading…
Reference in a new issue