Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

How to let default values come from the database?

Tags:

haskell

yesod

Why does the user object still have Nothing for createdAt and updatedAt? Why are those fields not getting assigned by the database?

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
User
  email String
  createdAt UTCTime Maybe default=CURRENT_TIME
  updatedAt UTCTime Maybe default=CURRENT_TIME
  deriving Show
|]

main = runSqlite ":memory:" $ do
  runMigration migrateAll
  userId <- insert $ User "[email protected]" Nothing Nothing
  liftIO $ print userId
  user <- get userId
  case user of
    Nothing -> liftIO $ putStrLn ("coulnt find userId=" ++ (show userId))
    Just u -> liftIO $ putStrLn ("user=" ++ (show user))

Output:

UserKey {unUserKey = SqlBackendKey {unSqlBackendKey = 1}}
user=Just (User {userEmail = "[email protected]", userCreatedAt = Nothing, userUpdatedAt = Nothing})
like image 857
Saurabh Nanda Avatar asked Feb 05 '16 19:02

Saurabh Nanda


2 Answers

(Edit: see solution below using triggers)

The problem: Default values don't override explicitly setting a column to NULL

Per the SQLite docs:

The DEFAULT clause specifies a default value to use for the column if no value is explicitly provided by the user when doing an INSERT.

The issue is that when Persistent is doing the insert, it's specifying the createdAt and updatedAt columns as NULL:

[Debug#SQL] INSERT INTO "user"("email","created_at","updated_at") VALUES(?,?,?); [PersistText "[email protected]",PersistNull,PersistNull]

To reach this conclusion, I modified your snippet to add SQL logging (I just copied the source of runSqlite and changed it to log to STDOUT). I used a file instead of in-memory database just so I could open the database in a SQLite editor and verify that the default values were being set.

-- Pragmas and imports are taken from a snippet in the Yesod book. Some of them may be superfluous.
{-# LANGUAGE EmptyDataDecls             #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE GADTs                      #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE QuasiQuotes                #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE TypeFamilies               #-}
import Database.Persist
import Database.Persist.Sqlite
import Database.Persist.TH
import Control.Monad.IO.Class (liftIO)
import Data.Time
import Control.Monad.Trans.Resource
import Control.Monad.Logger
import Control.Monad.IO.Class
import Data.Text

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
User
  email String
  createdAt UTCTime Maybe default=CURRENT_TIME
  updatedAt UTCTime Maybe default=CURRENT_TIME
  deriving Show
|]

runSqlite2 :: (MonadBaseControl IO m, MonadIO m)
          => Text -- ^ connection string
          -> SqlPersistT (LoggingT (ResourceT m)) a -- ^ database action
          -> m a
runSqlite2 connstr = runResourceT
                  . runStdoutLoggingT
                  . withSqliteConn connstr
                  . runSqlConn

main = runSqlite2 "bar.db" $ do
  runMigration migrateAll
  userId <- insert $ User "[email protected]" Nothing Nothing
  liftIO $ print userId
  user <- get userId
  case user of
    Nothing -> liftIO $ putStrLn ("coulnt find userId=" ++ (show userId))
    Just u -> liftIO $ putStrLn ("user=" ++ (show user))

Here's the output I get:

Max@maximilians-mbp /tmp> stack runghc sqlite.hs
Run from outside a project, using implicit global project config
Using resolver: lts-3.10 from implicit global project's config file: /Users/Max/.stack/global/stack.yaml
Migrating: CREATE TABLE "user"("id" INTEGER PRIMARY KEY,"email" VARCHAR NOT NULL,"created_at" TIMESTAMP NULL DEFAULT CURRENT_TIME,"updated_at" TIMESTAMP NULL DEFAULT CURRENT_TIME)
[Debug#SQL] CREATE TABLE "user"("id" INTEGER PRIMARY KEY,"email" VARCHAR NOT NULL,"created_at" TIMESTAMP NULL DEFAULT CURRENT_TIME,"updated_at" TIMESTAMP NULL DEFAULT CURRENT_TIME); []
[Debug#SQL] INSERT INTO "user"("email","created_at","updated_at") VALUES(?,?,?); [PersistText "[email protected]",PersistNull,PersistNull]
[Debug#SQL] SELECT "id" FROM "user" WHERE _ROWID_=last_insert_rowid(); []
UserKey {unUserKey = SqlBackendKey {unSqlBackendKey = 1}}
[Debug#SQL] SELECT "email","created_at","updated_at" FROM "user" WHERE "id"=? ; [PersistInt64 1]
user=Just (User {userEmail = "[email protected]", userCreatedAt = Nothing, userUpdatedAt = Nothing})

Edit: Solution using triggers:

You can implement created_at and updated_at columns with triggers. This approach has some nice advantages. Basically there's no way for updated_at to be enforced by a DEFAULT value anyway, so you need a trigger for that if you want the database (and not the application) to manage it. Triggers also solve for updated_at being set when executing raw SQL queries or batch updates. Here's what this solution looks like:

CREATE TRIGGER set_created_and_updated_at AFTER INSERT ON user
BEGIN
UPDATE user SET created_at=CURRENT_TIMESTAMP, updated_at=CURRENT_TIMESTAMP WHERE user.id = NEW.id;
END

CREATE TRIGGER set_updated_at AFTER UPDATE ON user
BEGIN
UPDATE user SET updated_at=CURRENT_TIMESTAMP WHERE user.id = NEW.id;
END

Now the output is as expected:

[Debug#SQL] INSERT INTO "user"("email","created_at","updated_at") VALUES(?,?,?); [PersistText "[email protected]",PersistNull,PersistNull]
[Debug#SQL] SELECT "id" FROM "user" WHERE _ROWID_=last_insert_rowid(); []
UserKey {unUserKey = SqlBackendKey {unSqlBackendKey = 1}}
[Debug#SQL] SELECT "email","created_at","updated_at" FROM "user" WHERE "id"=? ; [PersistInt64 1]
user=Just (User {userEmail = "[email protected]", userCreatedAt = Just 2016-02-12 16:41:43 UTC, userUpdatedAt = Just 2016-02-12 16:41:43 UTC})

The main downside to the trigger solution is that it's a slight hassle to set up the triggers.

Edit 2: Avoiding Maybe and Postgres support

If you'd like to avoid having Maybe values for createdAt and updatedAt, you can set them on the server to some dummy value like so:

-- | Use 'zeroTime' to get a 'UTCTime' without doing any IO.
-- The main use case of this is providing a dummy-value for createdAt and updatedAt fields on our models. Those values are set by database triggers anyway.
zeroTime :: UTCTime
zeroTime = UTCTime (fromGregorian 1 0 0) (secondsToDiffTime 0)

And then let the server set the values through triggers. Slightly hacky, but in practice works great.

Postgresql triggers

The OP asked for SQLite but I'm sure people are reading this for other databases as well. Here's the Postgresql version:

CREATE OR REPLACE FUNCTION create_timestamps()   
        RETURNS TRIGGER AS $$
        BEGIN
            NEW.created_at = now();
            NEW.updated_at = now();
            RETURN NEW;   
        END;
        $$ language 'plpgsql';

CREATE OR REPLACE FUNCTION update_timestamps()   
        RETURNS TRIGGER AS $$
        BEGIN
            NEW.updated_at = now();
            RETURN NEW;   
        END;
        $$ language 'plpgsql';

CREATE TRIGGER users_insert BEFORE INSERT ON users FOR EACH ROW EXECUTE PROCEDURE create_timestamps();
CREATE TRIGGER users_update BEFORE UPDATE ON users FOR EACH ROW EXECUTE PROCEDURE update_timestamps();
like image 144
MaxGabriel Avatar answered Oct 21 '22 02:10

MaxGabriel


According to http://www.yesodweb.com/book/persistent

The default attribute has absolutely no impact on the Haskell code itself; you still need to fill in all values. This will only affect the database schema and automatic migrations.

do
  time <- liftIO getCurrentTime
  insert $ User "[email protected]" time time
like image 43
Daishi Nakajima Avatar answered Oct 21 '22 01:10

Daishi Nakajima