Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class HasRow a where
- class HasDField a where
- class HasDValue a where
- mkRow :: HasRow a => Row a
- mkDField :: HasDField a => Row a
- mkDValue :: HasDValue a => Value a
- gRow :: (Generic a, Code a ~ '[xs], All HasDField xs) => Row a
- gDEnumValue :: (Generic a, All (Equal '[]) (Code a)) => NP (K Text) (Code a) -> Value a
Documentation
A type that can be decoded from a database row, using Hasql's Row
decoder.
Your data type needs to derive GHC Generic
, and using this derive
an instance of SOP Generic
. From here you can derive an instance
of HasRow
. This gives you access to a value mkRow
, which you can use
to get a value of type Row
.
{-# DeriveGeneric #-}
import Data.Text (Text)
import Data.UUID (UUID)
import qualified GHC.Generics as GHC
import Generics.SOP
import Hasql.Query (statement)
import Hasql.Session (Session, query)
import qualified Hasql.Decoders as HD
import qualified Hasql.Encoders as HE
data Person = Person
{ personId :: UUID
, personName :: Text
, personAge :: Int
} deriving (GHC.Generic)
instance Generic Person
instance HasRow Person
-- Search for a Person
with a matching UUID
findPerson :: UUID -> Session (Maybe Person)
findPerson pid =
query pid preparedStatement
where
preparedStatement = statement sql encoder decoder True
sql = "SELECT id, name, age FROM people WHERE id=$1"
encoder = HE.value HE.uuid
decoder = HD.maybeRow mkRow
HasRow () Source # | |
All * HasDField ((:) * a ((:) * b ([] *))) => HasRow (a, b) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ([] *)))) => HasRow (a, b, c) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ([] *))))) => HasRow (a, b, c, d) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ([] *)))))) => HasRow (a, b, c, d, e) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ([] *))))))) => HasRow (a, b, c, d, e, f) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ([] *)))))))) => HasRow (a, b, c, d, e, f, g) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ([] *))))))))) => HasRow (a, b, c, d, e, f, g, h) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ([] *)))))))))) => HasRow (a, b, c, d, e, f, g, h, i) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ([] *))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ([] *)))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ([] *))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ([] *)))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ([] *))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ([] *)))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ((:) * p ([] *))))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ((:) * p ((:) * q ([] *)))))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ((:) * p ((:) * q ((:) * r ([] *))))))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ((:) * p ((:) * q ((:) * r ((:) * s ([] *)))))))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ((:) * p ((:) * q ((:) * r ((:) * s ((:) * t ([] *))))))))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ((:) * p ((:) * q ((:) * r ((:) * s ((:) * t ((:) * u ([] *)))))))))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ((:) * p ((:) * q ((:) * r ((:) * s ((:) * t ((:) * u ((:) * v ([] *))))))))))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ((:) * p ((:) * q ((:) * r ((:) * s ((:) * t ((:) * u ((:) * v ((:) * w ([] *)))))))))))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ((:) * p ((:) * q ((:) * r ((:) * s ((:) * t ((:) * u ((:) * v ((:) * w ((:) * x ([] *))))))))))))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ((:) * p ((:) * q ((:) * r ((:) * s ((:) * t ((:) * u ((:) * v ((:) * w ((:) * x ((:) * y ([] *)))))))))))))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # | |
All * HasDField ((:) * a ((:) * b ((:) * c ((:) * d ((:) * e ((:) * f ((:) * g ((:) * h ((:) * i ((:) * j ((:) * k ((:) * l ((:) * m ((:) * n ((:) * o ((:) * p ((:) * q ((:) * r ((:) * s ((:) * t ((:) * u ((:) * v ((:) * w ((:) * x ((:) * y ((:) * z ([] *))))))))))))))))))))))))))) => HasRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) Source # | |
class HasDField a where Source #
A type representing a value decoder lifted into a compasable Row
. Instances
are defined that will lift HasDValue
types into the common wrappers like
vectors, lists, and maybe.
HasDField Int Source # | |
HasDValue a => HasDField a Source # | |
HasDValue a => HasDField [Maybe a] Source # | |
HasDValue a => HasDField [a] Source # | |
HasDField (Maybe Int) Source # | |
HasDValue a => HasDField (Maybe a) Source # | |
HasDValue a => HasDField (Vector (Maybe a)) Source # | |
HasDValue a => HasDField (Vector a) Source # | |
class HasDValue a where Source #
A type representing an individual value decoder. These should be defined manually for each type.