opaleye-0.6.7005.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.Field

Description

Functions for working directly with Field_s.

Please note that numeric Field_ types are instances of Num, so you can use *, /, +, - on them.

Synopsis

Documentation

type family Field_ (a :: Nullability) b Source #

The name Column will be replaced by Field in version 0.7. The Field_, Field and FieldNullable types exist to help smooth the transition. We recommend that you use Field_, Field or FieldNullable instead of Column everywhere that it is sufficient.

Instances
type Field_ NonNullable a Source # 
Instance details

Defined in Opaleye.Field

type Field_ Nullable a Source # 
Instance details

Defined in Opaleye.Field

data Nullability Source #

Constructors

NonNullable 
Nullable 
Instances
type A (H HT :: Arr Type (C k2) k2) (C ((,,) h o NN) :: C k2) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H HT :: Arr Type (C k2) k2) (C ((,,) h o NN) :: C k2) = h
type A (H NullsT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H NullsT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) = A (H NullsT :: Arr Type (C a) k2) (C t)
type A (H WT :: Arr Type (TC a) k2) (TC ((,) t Req) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H WT :: Arr Type (TC a) k2) (TC ((,) t Req) :: TC a) = A (H OT :: Arr Type (C a) k2) (C t)
type A (H OT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H OT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) = A (H OT :: Arr Type (C a) k2) (C t)
type A (H HT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H HT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) = A (H HT :: Arr Type (C a) k2) (C t)
type A (H WT :: Arr Type (TC a) Type) (TC ((,) t Opt) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H WT :: Arr Type (TC a) Type) (TC ((,) t Opt) :: TC a) = Maybe (A (H OT :: Arr Type (C a) Type) (C t))
type A (H NullsT :: Arr Type (C Type) Type) (C ((,,) h o n) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H NullsT :: Arr Type (C Type) Type) (C ((,,) h o n) :: C Type) = Column (Nullable o)
type A (H OT :: Arr Type (C Type) Type) (C ((,,) h o N) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H OT :: Arr Type (C Type) Type) (C ((,,) h o N) :: C Type) = Column (Nullable o)
type A (H OT :: Arr Type (C Type) Type) (C ((,,) h o NN) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H OT :: Arr Type (C Type) Type) (C ((,,) h o NN) :: C Type) = Column o
type A (H HT :: Arr Type (C Type) Type) (C ((,,) h o N) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H HT :: Arr Type (C Type) Type) (C ((,,) h o N) :: C Type) = Maybe h

null :: FieldNullable a Source #

A NULL of any type

isNull :: FieldNullable a -> Field PGBool Source #

TRUE if the value of the field is NULL, FALSE otherwise.

matchNullable Source #

If the Field 'Nullable a is NULL then return the Field 'NonNullable b otherwise map the underlying Field 'Nullable a using the provided function.

The Opaleye equivalent of maybe.

Will be generalized to Field_ n b in a later version.

fromNullable Source #

Arguments

:: Field_ NonNullable a 
-> Field_ Nullable a 
-> Field_ NonNullable a 

If the Field 'Nullable a is NULL then return the provided Field 'NonNullable a otherwise return the underlying Field 'NonNullable a.

The Opaleye equivalent of fromMaybe and very similar to PostgreSQL's COALESCE.

Will be generalized to Field_ n a in a later version.

toNullable :: Field_ NonNullable a -> Field_ Nullable a Source #

Treat a field as though it were nullable. This is always safe.

The Opaleye equivalent of Just.

Will be generalized to Field_ n a in a later version.

maybeToNullable :: Maybe (Field_ NonNullable a) -> Field_ Nullable a Source #

If the argument is Nothing return NULL otherwise return the provided value coerced to a nullable type.

Will be generalized to Maybe (Field_ n a) in a later version.