McBear Holden
McBear Holden

Reputation: 5901

Yesod new data type definition and mapping

In Yesod, I want to define a new data type:

data Status = Read | Reviewed | Learned

I'm using the Scaffold example. So in the best practice where should I declare the above data? In the Foundation.hs or Application.hs or elsewhere?

I will then create a database table with one of the column as this Status type. How is this mapped to my Postgresql backend? Which sql data type should correspond to this Status type?

Upvotes: 1

Views: 110

Answers (1)

Sibi
Sibi

Reputation: 48664

So in the best practice where should I declare the above data? In the Foundation.hs or Application.hs or elsewhere?

I define it neither of the places. I usually create a new module for it and define the type there. But ultimately it boils down to personal taste. I don't recommend it doing it in Foundation.hs because that's a module where your master application type and it's instances for various Yesod related typeclasses reside on. Similary I would not add it in Application.hs because that's a module where your application's setting and the Wai Application related functions reside on. But that's just my taste. :-)

I will then create a database table with one of the column as this Status type. How is this mapped to my Postgresql backend? Which sql data type should correspond to this Status type?

You can use Status algebric type to be define as it is. An example:

#!/usr/bin/env stack
{- stack
     --resolver lts-6.19
     --install-ghc
     runghc
     --package persistent
     --package aeson
     --package persistent-postgresql
     --package text
     --package persistent-template
     --package time
     --package mtl
-}

{-# LANGUAGE EmptyDataDecls             #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE GADTs                      #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE QuasiQuotes                #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE FlexibleInstances#-}
{-# LANGUAGE TypeFamilies               #-}

import           Database.Persist
import           Database.Persist.Postgresql
import           Database.Persist.TH
import           Control.Monad.IO.Class  (liftIO)
import           Control.Monad.Logger    (runStderrLoggingT)
import Data.Time
import Data.Text
import Data.Aeson
import ModelSum

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
User
    name Text
    age Int
    status Status
    deriving Show
|]

connStr = "host=localhost dbname=test user=postgres password=postgres port=5432"

main :: IO ()
main = mockMigration migrateAll

And the ModelSum file:

{-# LANGUAGE TemplateHaskell #-}

module ModelSum where

import Database.Persist.TH

data Status
  = Read
  | Reviewed
  | Learned
  deriving (Show, Eq, Read)

derivePersistField "Status"

On executing it, you get:

$ ./script.hs
CREATe TABLE "user"("id" SERIAL8  PRIMARY KEY UNIQUE,"name" VARCHAR NOT NULL,"age" INT8 NOT NULL,"status" VARCHAR NOT NULL)

You can see that the status column is created as varchar. Internally it performs the conversion using the Show and Read instances.

Upvotes: 2

Related Questions