persistent-2.13.1.1: Type-safe, multi-backend data serialization.
Safe HaskellNone
LanguageHaskell2010

Database.Persist.Class.PersistField

Synopsis

Documentation

class PersistField a where Source #

This class teaches Persistent how to take a custom type and marshal it to and from a PersistValue, allowing it to be stored in a database.

Examples

Expand
Simple Newtype

You can use newtype to add more type safety/readability to a basis type like ByteString. In these cases, just derive PersistField and PersistFieldSql:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

newtype HashedPassword = HashedPassword ByteString
  deriving (Eq, Show, PersistField, PersistFieldSql)
Smart Constructor Newtype

In this example, we create a PersistField instance for a newtype following the "Smart Constructor" pattern.

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import qualified Data.Text as T
import qualified Data.Char as C

-- | An American Social Security Number
newtype SSN = SSN Text
 deriving (Eq, Show, PersistFieldSql)

mkSSN :: Text -> Either Text SSN
mkSSN t = if (T.length t == 9) && (T.all C.isDigit t)
 then Right $ SSN t
 else Left $ "Invalid SSN: " <> t

instance PersistField SSN where
  toPersistValue (SSN t) = PersistText t
  fromPersistValue (PersistText t) = mkSSN t
  -- Handle cases where the database does not give us PersistText
  fromPersistValue x = Left $ "File.hs: When trying to deserialize an SSN: expected PersistText, received: " <> T.pack (show x)

Tips:

  • This file contain dozens of PersistField instances you can look at for examples.
  • Typically custom PersistField instances will only accept a single PersistValue constructor in fromPersistValue.
  • Internal PersistField instances accept a wide variety of PersistValues to accomodate e.g. storing booleans as integers, booleans or strings.
  • If you're making a custom instance and using a SQL database, you'll also need PersistFieldSql to specify the type of the database column.

Instances

Instances details
PersistField Bool Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Double Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Int Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Int8 Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Int16 Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Int32 Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Int64 Source # 
Instance details

Defined in Database.Persist.Class.PersistField

(TypeError ((((('Text "The instance of PersistField for the Natural type was removed." :$$: 'Text "Please see the documentation for OverflowNatural if you want to ") :$$: 'Text "continue using the old behavior or want to see documentation on ") :$$: 'Text "why the instance was removed.") :$$: 'Text "") :$$: 'Text "This error instance will be removed in a future release.") :: Constraint) => PersistField Natural Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Rational Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word8 Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word16 Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word32 Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Word64 Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField ByteString Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Text Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField UTCTime Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Text Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Html Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField TimeOfDay Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Day Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField PersistValue Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField Checkmark Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField SomePersistField Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField OverflowNatural Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField [Char] Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField a => PersistField [a] Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField a => PersistField (Maybe a) Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField v => PersistField (IntMap v) Source # 
Instance details

Defined in Database.Persist.Class.PersistField

(Ord a, PersistField a) => PersistField (Set a) Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField a => PersistField (Vector a) Source # 
Instance details

Defined in Database.Persist.Class.PersistField

(PersistEntity record, PersistField record, PersistField (Key record)) => PersistField (Entity record) Source # 
Instance details

Defined in Database.Persist.Class.PersistEntity

PersistField (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

PersistField (BackendKey SqlWriteBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

PersistField (BackendKey SqlReadBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

(BackendCompatible b s, PersistField (BackendKey b)) => PersistField (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(PersistField a, PersistField b) => PersistField (a, b) Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField v => PersistField (Map Text v) Source # 
Instance details

Defined in Database.Persist.Class.PersistField

HasResolution a => PersistField (Fixed a) Source # 
Instance details

Defined in Database.Persist.Class.PersistField

getPersistMap :: PersistValue -> Either Text [(Text, PersistValue)] Source #

FIXME Add documentation to that.

newtype OverflowNatural Source #

Prior to persistent-2.11.0, we provided an instance of PersistField for the Natural type. This was in error, because Natural represents an infinite value, and databases don't have reasonable types for this.

The instance for Natural used the Int64 underlying type, which will cause underflow and overflow errors. This type has the exact same code in the instances, and will work seamlessly.

A more appropriate type for this is the Word series of types from Data.Word. These have a bounded size, are guaranteed to be non-negative, and are quite efficient for the database to store.

Since: 2.11.0

Constructors

OverflowNatural 

Instances

Instances details
Eq OverflowNatural Source # 
Instance details

Defined in Database.Persist.Class.PersistField

Ord OverflowNatural Source # 
Instance details

Defined in Database.Persist.Class.PersistField

Show OverflowNatural Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField OverflowNatural Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistFieldSql OverflowNatural Source #

This type uses the SqlInt64 version, which will exhibit overflow and underflow behavior. Additionally, it permits negative values in the database, which isn't ideal.

Since: 2.11.0

Instance details

Defined in Database.Persist.Sql.Class