Prefer SQLite.Simple to Persistent

In the spirit of walking crawling before I walk, I'm preferring the less
powerful SQLite.Simple library to the more powerful (but mystifying) Persistent
library.
This commit is contained in:
William Carroll 2020-07-27 15:22:22 +01:00
parent c38814d7a1
commit 475f62fb16
3 changed files with 128 additions and 68 deletions

View file

@ -5,12 +5,10 @@ module App where
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Control.Monad.Logger (runStderrLoggingT) import Control.Monad.Logger (runStderrLoggingT)
import Database.Persist.Sqlite ( ConnectionPool, createSqlitePool import Data.Function ((&))
, runSqlPool, runSqlPersistMPool
, runMigration, selectFirst, (==.)
, insert, entityVal)
import Data.String.Conversions (cs) import Data.String.Conversions (cs)
import Data.Text (Text) import Data.Text (Text)
import Database.SQLite.Simple
import Network.Wai.Handler.Warp as Warp import Network.Wai.Handler.Warp as Warp
import Servant import Servant
@ -18,40 +16,33 @@ import API
import qualified Types as T import qualified Types as T
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
server :: ConnectionPool -> Server API server :: FilePath -> Server API
server pool = server dbFile =
userAddH :<|> userGetH userAddH :<|> userGetH
where where
userAddH newUser = liftIO $ userAdd newUser userAddH newUser = liftIO $ userAdd newUser
userGetH name = liftIO $ userGet name userGetH name = liftIO $ userGet name
-- TODO(wpcarro): Handle failed CONSTRAINTs instead of sending 500s
userAdd :: T.Account -> IO (Maybe T.Session) userAdd :: T.Account -> IO (Maybe T.Session)
userAdd newUser = flip runSqlPersistMPool pool $ do userAdd account = withConnection dbFile $ \conn -> do
exists <- selectFirst [T.AccountUsername ==. (T.accountUsername newUser)] [] execute conn "INSERT INTO Accounts (username,password,email,role,profilePicture) VALUES (?,?,?,?,?)"
case exists of (account & T.accountFields)
Nothing -> do T.Session{ T.username = T.accountUsername account
insert newUser , T.password = T.accountPassword account
pure $ Just (T.Session { T.username = T.Username "wpcarro" , T.role = T.accountRole account
, T.password = T.Password "testing" } & Just & pure
, T.role = T.RegularUser
})
Just _ -> pure Nothing
userGet :: Text -> IO (Maybe T.Account) userGet :: Text -> IO (Maybe T.Account)
userGet name = flip runSqlPersistMPool pool $ do userGet name = withConnection dbFile $ \conn -> do
mUser <- selectFirst [T.AccountUsername ==. name] [] res <- query conn "SELECT * FROM Accounts WHERE username = ?" (Only name)
pure $ entityVal <$> mUser case res of
[x] -> pure (Just x)
app :: ConnectionPool -> Application _ -> pure Nothing
app pool = serve (Proxy @ API) $ server pool
mkApp :: FilePath -> IO Application mkApp :: FilePath -> IO Application
mkApp sqliteFile = do mkApp dbFile = do
pool <- runStderrLoggingT $ do pure $ serve (Proxy @ API) $ server dbFile
createSqlitePool (cs sqliteFile) 5
runSqlPool (runMigration T.migrateAll) pool
pure $ app pool
run :: FilePath -> IO () run :: FilePath -> IO ()
run sqliteFile = run sqliteFile =

View file

@ -4,4 +4,4 @@ import qualified App
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
main :: IO () main :: IO ()
main = App.run "sqlite.db" main = App.run "../db.sqlite3"

View file

@ -1,3 +1,4 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GADTs #-} {-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
@ -10,58 +11,126 @@
module Types where module Types where
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Data.Aeson import Data.Aeson
import Data.Function ((&))
import Data.Text import Data.Text
import Data.Typeable
import Database.Persist.TH import Database.Persist.TH
import Database.SQLite.Simple
import Database.SQLite.Simple.Ok
import Database.SQLite.Simple.FromField
import Database.SQLite.Simple.ToField
import GHC.Generics
import qualified Data.ByteString as BS
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| -- TODO(wpcarro): Properly handle NULL for columns like profilePicture.
Account forNewtype :: (Typeable b) => (Text -> b) -> FieldParser b
username Text forNewtype wrapper field =
password Text case fieldData field of
email Text (SQLText x) -> Ok (wrapper x)
role Text _ -> returnError ConversionFailed field ""
UniqueUsername username
UniqueEmail email
deriving Eq Read Show
|]
instance FromJSON Account where
parseJSON = withObject "Account" $ \ v ->
Account <$> v .: "username"
<*> v .: "password"
<*> v .: "email"
<*> v .: "role"
instance ToJSON Account where
toJSON (Account{ accountUsername
, accountPassword
, accountEmail
, accountRole }) =
object [ "username" .= accountUsername
, "password" .= accountPassword
, "email" .= accountEmail
, "role" .= accountRole
]
newtype Username = Username Text newtype Username = Username Text
deriving (Eq, Show) deriving (Eq, Show, Generic)
instance ToJSON Username where instance ToJSON Username
toJSON (Username x) = toJSON x instance FromJSON Username
instance ToField Username where
toField (Username x) = SQLText x
instance FromField Username where
fromField = forNewtype Username
newtype Password = Password Text newtype Password = Password Text
deriving (Eq, Show) deriving (Eq, Show, Generic)
instance ToJSON Password where instance ToJSON Password
toJSON (Password x) = toJSON x instance FromJSON Password
instance ToField Password where
toField (Password x) = SQLText x
instance FromField Password where
fromField = forNewtype Password
newtype Email = Email Text
deriving (Eq, Show, Generic)
instance ToJSON Email
instance FromJSON Email
instance ToField Email where
toField (Email x) = SQLText x
instance FromField Email where
fromField = forNewtype Email
data Role = RegularUser | Manager | Admin data Role = RegularUser | Manager | Admin
deriving (Eq, Show) deriving (Eq, Show, Generic)
instance ToJSON Role where instance ToJSON Role
toJSON RegularUser = "user" instance FromJSON Role
toJSON Manager = "manager"
toJSON Admin = "admin" instance ToField Role where
toField RegularUser = SQLText "user"
toField Manager = SQLText "manager"
toField Admin = SQLText "admin"
instance FromField Role where
fromField field =
case fieldData field of
(SQLText "user") -> Ok RegularUser
(SQLText "manager") -> Ok Manager
(SQLText "admin") -> Ok Admin
_ -> returnError ConversionFailed field ""
-- TODO(wpcarro): Prefer Data.ByteString instead of Text
newtype ProfilePicture = ProfilePicture Text
deriving (Eq, Show, Generic)
instance ToJSON ProfilePicture
instance FromJSON ProfilePicture
instance ToField ProfilePicture where
toField (ProfilePicture x) = SQLText x
instance FromField ProfilePicture where
fromField = forNewtype ProfilePicture
data Account = Account
{ accountUsername :: Username
, accountPassword :: Password
, accountEmail :: Email
, accountRole :: Role
, accountProfilePicture :: ProfilePicture
} deriving (Eq, Show, Generic)
instance FromJSON Account
instance ToJSON Account
-- | Return a tuple with all of the fields for an Account record to use for SQL.
accountFields :: Account -> (Username, Password, Email, Role, ProfilePicture)
accountFields (Account { accountUsername
, accountPassword
, accountEmail
, accountRole
, accountProfilePicture
})
= ( accountUsername
, accountPassword
, accountEmail
, accountRole
, accountProfilePicture
)
instance FromRow Account where
fromRow = Account <$> field
<*> field
<*> field
<*> field
<*> field
data Session = Session data Session = Session
{ username :: Username { username :: Username