hasql-interpolate-0.1.0.0: QuasiQuoter that supports expression interpolation for hasql
Safe HaskellNone
LanguageHaskell2010

Hasql.Interpolate.Internal.Decoder

Synopsis

Decoding type classes

class DecodeValue a where Source #

This type class determines which decoder we will apply to a query field by the type of the result.

Example

Expand
data ThreatLevel = None | Midnight

instance DecodeValue ThreatLevel where
  decodeValue = enum \case
    "none"     -> Just None
    "midnight" -> Just Midnight
    _          -> Nothing

Instances

Instances details
DecodeValue Bool Source #

Parse a postgres bool using bool

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Char Source #

Parse a postgres char using char

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Double Source #

Parse a postgres float8 using float8

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Float Source #

Parse a postgres float4 using float4

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Int16 Source #

Parse a postgres int2 using int2

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Int32 Source #

Parse a postgres int4 using int4

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Int64 Source #

Parse a postgres int8 using int8

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Scientific Source #

Parse a postgres numeric using numeric

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Text Source #

Parse a postgres text using text

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue UTCTime Source #

Parse a postgres timestamptz using timestamptz

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue UUID Source #

Parse a postgres uuid using uuid

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Day Source #

Parse a postgres date using date

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue DiffTime Source #

Parse a postgres interval using interval

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue LocalTime Source #

Parse a postgres timestamp using timestamp

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue Json Source #

Parse a postgres json using json

Instance details

Defined in Hasql.Interpolate.Internal.Json

DecodeValue Jsonb Source #

Parse a postgres jsonb using jsonb

Instance details

Defined in Hasql.Interpolate.Internal.Json

DecodeField a => DecodeValue [a] Source #

Parse a postgres array using listArray

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeValue :: Value [a] Source #

DecodeField a => DecodeValue (Vector a) Source #

Parse a postgres array using vectorArray

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

(Generic a, GToComposite (Rep a)) => DecodeValue (CompositeValue a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.CompositeValue

FromJSON a => DecodeValue (AsJsonb a) Source #

Parse a postgres jsonb to anything that is an instance of FromJSON

Instance details

Defined in Hasql.Interpolate.Internal.Json

FromJSON a => DecodeValue (AsJson a) Source #

Parse a postgres json to anything that is an instance of FromJSON

Instance details

Defined in Hasql.Interpolate.Internal.Json

class DecodeField a where Source #

You do not need to define instances for this class; The two instances exported here cover all uses. The class only exists to lift Value to hasql's NullableOrNot GADT.

Instances

Instances details
DecodeValue a => DecodeField a Source #

Overlappable instance for parsing non-nullable values

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeValue a => DecodeField (Maybe a) Source #

Instance for parsing nullable values

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

class DecodeRow a where Source #

Determine a row decoder from a Haskell type. Derivable with generics for any product type.

Examples

Expand

A manual instance:

data T = T Int64 Bool Text

instance DecodeRow T where
  decodeRow = T
    $ column decodeField
    * column decodeField
    * column decodeField

A generic instance:

data T
 = T Int64 Bool Text
 deriving stock (Generic)
 deriving anyclass (DecodeRow)

Minimal complete definition

Nothing

Methods

decodeRow :: Row a Source #

default decodeRow :: (Generic a, GDecodeRow (Rep a)) => Row a Source #

Instances

Instances details
DecodeField a => DecodeRow (OneColumn a) Source #

Parse a single column row

Instance details

Defined in Hasql.Interpolate.Internal.OneColumn

(DecodeField x1, DecodeField x2) => DecodeRow (x1, x2) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2) Source #

(DecodeField x1, DecodeField x2, DecodeField x3) => DecodeRow (x1, x2, x3) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3) Source #

(DecodeField x1, DecodeField x2, DecodeField x3, DecodeField x4) => DecodeRow (x1, x2, x3, x4) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3, x4) Source #

(DecodeField x1, DecodeField x2, DecodeField x3, DecodeField x4, DecodeField x5) => DecodeRow (x1, x2, x3, x4, x5) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3, x4, x5) Source #

(DecodeField x1, DecodeField x2, DecodeField x3, DecodeField x4, DecodeField x5, DecodeField x6) => DecodeRow (x1, x2, x3, x4, x5, x6) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3, x4, x5, x6) Source #

(DecodeField x1, DecodeField x2, DecodeField x3, DecodeField x4, DecodeField x5, DecodeField x6, DecodeField x7) => DecodeRow (x1, x2, x3, x4, x5, x6, x7) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3, x4, x5, x6, x7) Source #

(DecodeField x1, DecodeField x2, DecodeField x3, DecodeField x4, DecodeField x5, DecodeField x6, DecodeField x7, DecodeField x8) => DecodeRow (x1, x2, x3, x4, x5, x6, x7, x8) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeRow :: Row (x1, x2, x3, x4, x5, x6, x7, x8) Source #

class DecodeResult a where Source #

Determine a result decoder from a Haskell type.

Instances

Instances details
DecodeResult Int64 Source #

Parse the rows affected from the query result, as in an insert, update, or delete statement without a returning clause. (rowsAffected)

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeResult () Source #

Ignore the query response (noResult)

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeRow a => DecodeResult [a] Source #

Parse any number of rows into a list (rowList)

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

decodeResult :: Result [a] Source #

DecodeRow a => DecodeResult (Maybe a) Source #

Parse zero or one rows, throw UnexpectedAmountOfRows otherwise. (rowMaybe)

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeRow a => DecodeResult (Vector a) Source #

Parse any number of rows into a Vector (rowVector)

Instance details

Defined in Hasql.Interpolate.Internal.Decoder

DecodeRow a => DecodeResult (OneRow a) Source #

Parse a single row result, throw UnexpectedAmountOfRows otherwise. (singleRow)

Instance details

Defined in Hasql.Interpolate.Internal.OneRow

Generics

class GDecodeRow a where Source #

Methods

gdecodeRow :: Row (a p) Source #

Instances

Instances details
DecodeField a => GDecodeRow (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

gdecodeRow :: Row (K1 i a p) Source #

(GDecodeRow a, GDecodeRow b) => GDecodeRow (a :*: b) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

gdecodeRow :: Row ((a :*: b) p) Source #

GDecodeRow a => GDecodeRow (M1 t i a) Source # 
Instance details

Defined in Hasql.Interpolate.Internal.Decoder

Methods

gdecodeRow :: Row (M1 t i a p) Source #