Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class PersistField a where
- toPersistValue :: a -> PersistValue
- fromPersistValue :: PersistValue -> Either Text a
- data SomePersistField = forall a.PersistField a => SomePersistField a
- getPersistMap :: PersistValue -> Either Text [(Text, PersistValue)]
- newtype OverflowNatural = OverflowNatural {}
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
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 = HashedPasswordByteString
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 = SSNText
deriving (Eq, Show, PersistFieldSql) mkSSN ::Text
->Either
Text
SSN mkSSN t = if (T.length t == 9) && (T.all C.isDigit t) thenRight
$ SSN t elseLeft
$ "Invalid SSN: " <> t instancePersistField
SSN wheretoPersistValue
(SSN t) =PersistText
tfromPersistValue
(PersistText
t) = mkSSN t -- Handle cases where the database does not give us PersistTextfromPersistValue
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 singlePersistValue
constructor infromPersistValue
. - Internal
PersistField
instances accept a wide variety ofPersistValue
s 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.
toPersistValue :: a -> PersistValue Source #
fromPersistValue :: PersistValue -> Either Text a Source #
Instances
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