Support reading / writing cookies in API

Update my API type and handler types to reflect which handlers read and write
cookies.

TODO:
- Actually read from and write to Set-Cookie header
- Returning `pure NoContent` breaks my types, so I'm returning `undefined` now
This commit is contained in:
William Carroll 2020-07-29 14:14:47 +01:00
parent 9f70cb2c61
commit c4a090e558
3 changed files with 59 additions and 28 deletions

View file

@ -5,10 +5,14 @@ module API where
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Data.Text import Data.Text
import Servant.API import Servant.API
import Web.Cookie
import qualified Types as T import qualified Types as T
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Once authenticated, users receive a SessionCookie.
type SessionCookie = Header' '[Required] "Set-Cookie" T.SessionCookie
type API = type API =
-- accounts: Create -- accounts: Create
"accounts" "accounts"
@ -18,20 +22,24 @@ type API =
-- accounts: Update -- accounts: Update
-- accounts: Delete -- accounts: Delete
:<|> "accounts" :<|> "accounts"
:> SessionCookie
:> QueryParam' '[Required] "username" Text :> QueryParam' '[Required] "username" Text
:> Delete '[JSON] NoContent :> Delete '[JSON] NoContent
-- accounts: List -- accounts: List
:<|> "accounts" :<|> "accounts"
:> SessionCookie
:> Get '[JSON] [T.User] :> Get '[JSON] [T.User]
-- trips: Create -- trips: Create
:<|> "trips" :<|> "trips"
:> SessionCookie
:> ReqBody '[JSON] T.Trip :> ReqBody '[JSON] T.Trip
:> Post '[JSON] NoContent :> Post '[JSON] NoContent
-- trips: Read -- trips: Read
-- trips: Update -- trips: Update
-- trips: Delete -- trips: Delete
:<|> "trips" :<|> "trips"
:> SessionCookie
:> ReqBody '[JSON] T.TripPK :> ReqBody '[JSON] T.TripPK
:> Delete '[JSON] NoContent :> Delete '[JSON] NoContent
-- trips: List -- trips: List
@ -41,4 +49,7 @@ type API =
-- Miscellaneous -- Miscellaneous
:<|> "login" :<|> "login"
:> ReqBody '[JSON] T.AccountCredentials :> ReqBody '[JSON] T.AccountCredentials
:> Post '[JSON] NoContent :> Post '[JSON] (Headers '[Header "Set-Cookie" SetCookie] NoContent)
:<|> "logout"
:> SessionCookie
:> Get '[JSON] (Headers '[Header "Set-Cookie" SetCookie] NoContent)

View file

@ -1,3 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
@ -14,6 +15,7 @@ import Network.Wai.Handler.Warp as Warp
import Servant import Servant
import API import API
import Utils import Utils
import Web.Cookie
import qualified Crypto.KDF.BCrypt as BC import qualified Crypto.KDF.BCrypt as BC
import qualified Data.Text.Encoding as TE import qualified Data.Text.Encoding as TE
@ -32,14 +34,16 @@ server dbFile = createAccountH
:<|> deleteTripH :<|> deleteTripH
:<|> listTripsH :<|> listTripsH
:<|> loginH :<|> loginH
:<|> logoutH
where where
createAccountH newUser = liftIO $ createAccount newUser createAccountH newUser = liftIO $ createAccount newUser
deleteAccountH username = liftIO $ deleteAccount username deleteAccountH cookie username = liftIO $ deleteAccount cookie username
listAccountsH = liftIO $ listAccounts listAccountsH cookie = liftIO $ listAccounts cookie
createTripH trip = liftIO $ createTrip trip createTripH cookie trip = liftIO $ createTrip cookie trip
deleteTripH tripPK = liftIO $ deleteTrip tripPK deleteTripH cookie tripPK = liftIO $ deleteTrip cookie tripPK
listTripsH = liftIO $ listTrips listTripsH = liftIO $ listTrips
loginH creds = liftIO $ login creds loginH creds = liftIO $ login creds
logoutH cookie = liftIO $ logout cookie
-- 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
@ -51,30 +55,30 @@ server dbFile = createAccountH
(T.createAccountRequestRole request) (T.createAccountRequestRole request)
pure NoContent pure NoContent
deleteAccount :: Text -> IO NoContent deleteAccount :: T.SessionCookie -> Text -> IO NoContent
deleteAccount username = do deleteAccount cookie username = do
Accounts.delete dbFile (T.Username username) Accounts.delete dbFile (T.Username username)
pure NoContent pure NoContent
listAccounts :: IO [T.User] listAccounts :: T.SessionCookie -> IO [T.User]
listAccounts = Accounts.list dbFile listAccounts cookie = Accounts.list dbFile
createTrip :: T.Trip -> IO NoContent createTrip :: T.SessionCookie -> T.Trip -> IO NoContent
createTrip trip = do createTrip cookie trip = do
Trips.create dbFile trip Trips.create dbFile trip
pure NoContent pure NoContent
-- TODO(wpcarro): Validate incoming data like startDate.
deleteTrip :: T.SessionCookie -> T.TripPK -> IO NoContent
deleteTrip cookie tripPK = do
Trips.delete dbFile tripPK
pure NoContent
listTrips :: IO [T.Trip] listTrips :: IO [T.Trip]
listTrips = Trips.list dbFile listTrips = Trips.list dbFile
-- TODO(wpcarro): Validate incoming data like startDate. login :: T.AccountCredentials
deleteTrip :: T.TripPK -> IO NoContent -> IO (Headers '[Header "Set-Cookie" SetCookie] NoContent)
deleteTrip tripPK = do
Trips.delete dbFile tripPK
pure NoContent
-- TODO(wpcarro): Create and store a session token
login :: T.AccountCredentials -> IO NoContent
login (T.AccountCredentials username password) = do login (T.AccountCredentials username password) = do
mAccount <- Accounts.lookup dbFile username mAccount <- Accounts.lookup dbFile username
case mAccount of case mAccount of
@ -85,25 +89,31 @@ server dbFile = createAccountH
if T.passwordsMatch password accountPassword then do if T.passwordsMatch password accountPassword then do
session <- Sessions.findOrCreate dbFile account session <- Sessions.findOrCreate dbFile account
-- set cookie -- set cookie
pure NoContent undefined
else do else do
LoginAttempts.increment dbFile username LoginAttempts.increment dbFile username
throwIO $ err401 { errBody = "Your credentials are invalid" } throwIO err401 { errBody = "Your credentials are invalid" }
Just attempts -> Just attempts ->
if attempts > 3 then if attempts > 3 then
-- TODO(wpcarro): Prefer 429 error code -- TODO(wpcarro): Prefer 429 error code
throwIO $ err401 { errBody = "Too many failed login attempts" } throwIO err401 { errBody = "Too many failed login attempts" }
else if T.passwordsMatch password accountPassword then do else if T.passwordsMatch password accountPassword then do
session <- Sessions.findOrCreate dbFile account session <- Sessions.findOrCreate dbFile account
-- set cookie -- set cookie
pure NoContent undefined
else do else do
LoginAttempts.increment dbFile username LoginAttempts.increment dbFile username
-- TODO(wpcarro): Catch and return errors over HTTP -- TODO(wpcarro): Catch and return errors over HTTP
throwIO $ err401 { errBody = "Your credentials are invalid" } throwIO err401 { errBody = "Your credentials are invalid" }
-- In this branch, the user didn't supply a known username. -- In this branch, the user didn't supply a known username.
Nothing -> throwIO $ err401 { errBody = "Your credentials are invalid" } Nothing -> throwIO err401 { errBody = "Your credentials are invalid" }
logout :: T.SessionCookie
-> IO (Headers '[Header "Set-Cookie" SetCookie] NoContent)
logout cookie = undefined
-- pull off SessionUUID from the request headers
-- delete the SessionUUID from the Sessions table.
mkApp :: FilePath -> IO Application mkApp :: FilePath -> IO Application
mkApp dbFile = do mkApp dbFile = do

View file

@ -14,6 +14,8 @@ import Database.SQLite.Simple.Ok
import Database.SQLite.Simple.FromField import Database.SQLite.Simple.FromField
import Database.SQLite.Simple.ToField import Database.SQLite.Simple.ToField
import GHC.Generics import GHC.Generics
import Web.Cookie
import Servant.API
import Crypto.Random.Types (MonadRandom) import Crypto.Random.Types (MonadRandom)
import qualified Crypto.KDF.BCrypt as BC import qualified Crypto.KDF.BCrypt as BC
@ -382,3 +384,11 @@ data LoginAttempt = LoginAttempt
instance FromRow LoginAttempt where instance FromRow LoginAttempt where
fromRow = LoginAttempt <$> field <*> field fromRow = LoginAttempt <$> field <*> field
newtype SessionCookie = SessionCookie Cookies
instance FromHttpApiData SessionCookie where
parseHeader x =
x |> parseCookies |> SessionCookie |> pure
parseQueryParam x =
x |> TE.encodeUtf8 |> parseCookies |> SessionCookie |> pure