Support /login
Support basic authentication. Note the TODOs that this commit introduces to track some of the remaining work.
This commit is contained in:
parent
b170be9375
commit
b355664858
2 changed files with 30 additions and 3 deletions
|
@ -37,3 +37,8 @@ type API =
|
||||||
-- trips: List
|
-- trips: List
|
||||||
:<|> "trips"
|
:<|> "trips"
|
||||||
:> Get '[JSON] [T.Trip]
|
:> Get '[JSON] [T.Trip]
|
||||||
|
|
||||||
|
-- Miscellaneous
|
||||||
|
:<|> "login"
|
||||||
|
:> ReqBody '[JSON] T.AccountCredentials
|
||||||
|
:> Post '[JSON] (Maybe T.Session)
|
||||||
|
|
28
src/App.hs
28
src/App.hs
|
@ -1,18 +1,22 @@
|
||||||
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
module App where
|
module App where
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
import Control.Exception (throwIO)
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
import Control.Monad.Logger (runStderrLoggingT)
|
|
||||||
import Data.Function ((&))
|
import Data.Function ((&))
|
||||||
import Data.String.Conversions (cs)
|
import Data.String.Conversions (cs)
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Database.SQLite.Simple
|
import Database.SQLite.Simple
|
||||||
import Network.Wai.Handler.Warp as Warp
|
import Network.Wai.Handler.Warp as Warp
|
||||||
import Servant
|
import Servant
|
||||||
|
|
||||||
import API
|
import API
|
||||||
|
|
||||||
|
import qualified Crypto.KDF.BCrypt as BC
|
||||||
|
import qualified Data.Text.Encoding as TE
|
||||||
import qualified Types as T
|
import qualified Types as T
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
|
@ -23,14 +27,15 @@ server dbFile = createAccountH
|
||||||
:<|> createTripH
|
:<|> createTripH
|
||||||
:<|> deleteTripH
|
:<|> deleteTripH
|
||||||
:<|> listTripsH
|
:<|> listTripsH
|
||||||
|
:<|> loginH
|
||||||
where
|
where
|
||||||
createAccountH newUser = liftIO $ createAccount newUser
|
createAccountH newUser = liftIO $ createAccount newUser
|
||||||
deleteAccountH username = liftIO $ deleteAccount username
|
deleteAccountH username = liftIO $ deleteAccount username
|
||||||
listAccountsH = liftIO $ listAccounts
|
listAccountsH = liftIO $ listAccounts
|
||||||
|
|
||||||
createTripH trip = liftIO $ createTrip trip
|
createTripH trip = liftIO $ createTrip trip
|
||||||
deleteTripH tripPK = liftIO $ deleteTrip tripPK
|
deleteTripH tripPK = liftIO $ deleteTrip tripPK
|
||||||
listTripsH = liftIO $ listTrips
|
listTripsH = liftIO $ listTrips
|
||||||
|
loginH creds = liftIO $ login creds
|
||||||
|
|
||||||
-- TODO(wpcarro): Handle failed CONSTRAINTs instead of sending 500s
|
-- TODO(wpcarro): Handle failed CONSTRAINTs instead of sending 500s
|
||||||
createAccount :: T.CreateAccountRequest -> IO NoContent
|
createAccount :: T.CreateAccountRequest -> IO NoContent
|
||||||
|
@ -73,6 +78,23 @@ server dbFile = createAccountH
|
||||||
(tripPK & T.tripPKFields)
|
(tripPK & T.tripPKFields)
|
||||||
pure NoContent
|
pure NoContent
|
||||||
|
|
||||||
|
-- TODO(wpcarro): Create and store a session token
|
||||||
|
login :: T.AccountCredentials -> IO (Maybe T.Session)
|
||||||
|
login (T.AccountCredentials username password) =
|
||||||
|
withConnection dbFile $ \conn -> do
|
||||||
|
res <- query conn "SELECT * FROM Accounts WHERE username = ?"
|
||||||
|
(Only username)
|
||||||
|
case res of
|
||||||
|
[T.Account{T.accountUsername,T.accountPassword,T.accountRole}] ->
|
||||||
|
if T.passwordsMatch password accountPassword then
|
||||||
|
pure $ Just (T.Session accountUsername accountRole)
|
||||||
|
else
|
||||||
|
-- TODO(wpcarro): Catch and return errors over HTTP
|
||||||
|
throwIO $ err401 { errBody = "Your credentials are invalid" }
|
||||||
|
|
||||||
|
-- In this branch, the user didn't supply a known username.
|
||||||
|
_ -> throwIO $ err401 { errBody = "Your credentials are invalid" }
|
||||||
|
|
||||||
mkApp :: FilePath -> IO Application
|
mkApp :: FilePath -> IO Application
|
||||||
mkApp dbFile = do
|
mkApp dbFile = do
|
||||||
pure $ serve (Proxy @ API) $ server dbFile
|
pure $ serve (Proxy @ API) $ server dbFile
|
||||||
|
|
Loading…
Reference in a new issue