Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
MaybeFields
is Opaleye's analogue to Maybe
. You
probably won't want to create values of type MaybeFields
directly; instead they will appear as the result of
left/right/outer join-like operations, such as
optionalRestrict
and optional
.
Synopsis
- data MaybeFields fields
- nothingFields :: Default Nullspec a a => MaybeFields a
- nothingFieldsOfTypeOf :: a -> MaybeFields a
- justFields :: a -> MaybeFields a
- nullableToMaybeFields :: FieldNullable a -> MaybeFields (Field a)
- matchMaybe :: Default IfPP b b => MaybeFields a -> (Maybe a -> b) -> b
- fromMaybeFields :: Default IfPP b b => b -> MaybeFields b -> b
- maybeFields :: Default IfPP b b => b -> (a -> b) -> MaybeFields a -> b
- maybeFieldsToNullable :: MaybeFields (Field a) -> FieldNullable a
- optional :: Default Unpackspec a a => SelectArr i a -> SelectArr i (MaybeFields a)
- traverseMaybeFields :: (Default Unpackspec a a, Default Unpackspec b b) => SelectArr a b -> SelectArr (MaybeFields a) (MaybeFields b)
- catMaybeFields :: SelectArr i (MaybeFields a) -> SelectArr i a
- maybeFieldsToSelect :: SelectArr (MaybeFields a) a
- data Nullspec fields fields'
- nullspecField :: forall a n sqlType. IsSqlType sqlType => Nullspec a (Field_ n sqlType)
- nullspecMaybeFields :: Nullspec a b -> Nullspec (MaybeFields a) (MaybeFields b)
- nullspecList :: Nullspec a [b]
- nullspecEitherLeft :: Nullspec a b -> Nullspec a (Either b b')
- nullspecEitherRight :: Nullspec a b' -> Nullspec a (Either b b')
- binaryspecMaybeFields :: WithNulls Binaryspec a b -> Binaryspec (MaybeFields a) (MaybeFields b)
- distinctspecMaybeFields :: WithNulls Distinctspec a b -> Distinctspec (MaybeFields a) (MaybeFields b)
- fromFieldsMaybeFields :: FromFields fields haskells -> FromFields (MaybeFields fields) (Maybe haskells)
- toFieldsMaybeFields :: Nullspec a b -> ToFields a b -> ToFields (Maybe a) (MaybeFields b)
- unpackspecMaybeFields :: Unpackspec a b -> Unpackspec (MaybeFields a) (MaybeFields b)
- valuesspecMaybeFields :: Valuesspec a b -> Valuesspec (MaybeFields a) (MaybeFields b)
- nothingFieldsExplicit :: Nullspec a b -> MaybeFields b
- fromMaybeFieldsExplicit :: IfPP b b -> b -> MaybeFields b -> b
- maybeFieldsExplicit :: IfPP b b' -> b -> (a -> b) -> MaybeFields a -> b'
- optionalExplicit :: Unpackspec a a -> SelectArr i a -> SelectArr i (MaybeFields a)
- traverseMaybeFieldsExplicit :: Unpackspec a a -> Unpackspec b b -> SelectArr a b -> SelectArr (MaybeFields a) (MaybeFields b)
MaybeFields
type
data MaybeFields fields Source #
The Opaleye analogue of Maybe
. A value of type
MaybeFields a
either contains a value of type a
, or it contains
nothing.
Instances
Creating a MaybeFields
nothingFields :: Default Nullspec a a => MaybeFields a Source #
The Opaleye analogue of Nothing
.
nothingFieldsOfTypeOf :: a -> MaybeFields a Source #
justFields :: a -> MaybeFields a Source #
nullableToMaybeFields :: FieldNullable a -> MaybeFields (Field a) Source #
Convert NULL
to nothingFields
and non-NULL
to a justFields
Using a MaybeFields
matchMaybe :: Default IfPP b b => MaybeFields a -> (Maybe a -> b) -> b Source #
Use a Haskell \case
expression to pattern match on a
MaybeFields
.
example :: MaybeFields (Field SqlInt4) -> Field SqlInt4 example mf = matchMaybe mf $ \case Nothing -> 0 Just x -> x * 100
fromMaybeFields :: Default IfPP b b => b -> MaybeFields b -> b Source #
The Opaleye analogue of fromMaybe
maybeFields :: Default IfPP b b => b -> (a -> b) -> MaybeFields a -> b Source #
The Opaleye analogue of maybe
maybeFieldsToNullable :: MaybeFields (Field a) -> FieldNullable a Source #
Convert nothingFields
to NULL
to a justFields
to non-NULL
Creating a Select
which returns MaybeFields
:: Default Unpackspec a a | |
=> SelectArr i a | Input query |
-> SelectArr i (MaybeFields a) | The rows of the input query wrapped in "Just", unless the input query has no rows in which case a single row of "Nothing" |
Convenient access to lateral left/right join
functionality. Performs a LATERAL LEFT JOIN
under the hood and
has behaviour equivalent to the following Haskell function:
optional :: [a] -> [Maybe a] optional q = case q of [] -> [Nothing] xs -> map Just xs
That is, if q ::
returns no rows, SelectArr
i a
returns exactly one "Nothing"
row. Otherwise, optional
q
:: SelectArr
i (MaybeFields
a)
returns exactly the rows of optional
qq
wrapped in "Just". For example,
> let l1 = ["one", "two", "three"] :: [Field SqlText] >runSelectI
conn (optional
(values
l1)) [Just "one", Just "two", Just "three"] > let l2 = [] :: [Field SqlText] >runSelectI
conn (optional
(values
l2)) [Nothing]
optionalRestrict
is a special case of optional
and could be
written in terms of optional
as follows (except that
optionalRestrict
doesn't use LATERAL
under the hood and
optional
does).
optionalRestrict q = optional $ proc cond -> do a <- q -< () restrict -< cond a returnA -< a
traverseMaybeFields :: (Default Unpackspec a a, Default Unpackspec b b) => SelectArr a b -> SelectArr (MaybeFields a) (MaybeFields b) Source #
traverseMaybeFields
is analogous to Haskell's
. In particular,
traverse
:: (a -> [b]) -> Maybe
a
-> [Maybe
b]traverse
has the following definition that
generalises to traverseMaybeFields
:
traverse _ Nothing = pure Nothing
traverse f (Just x) = fmap Just (f x)
Using a Select
which returns MaybeFields
catMaybeFields :: SelectArr i (MaybeFields a) -> SelectArr i a Source #
The Opaleye analogue of catMaybes
. Most commonly
you will want to use this at type
catMaybeFields :: Select (MaybeFields a) -> Select a
maybeFieldsToSelect :: SelectArr (MaybeFields a) a Source #
The Opaleye analogue of maybeToList
. Unless you are
using arrow notation you'll probably find catMaybeFields
easier
to use.
Adaptors
data Nullspec fields fields' Source #
Instances
ProductProfunctor Nullspec Source # | |
Profunctor Nullspec Source # | |
Defined in Opaleye.Internal.Values dimap :: (a -> b) -> (c -> d) -> Nullspec b c -> Nullspec a d # lmap :: (a -> b) -> Nullspec b c -> Nullspec a c # rmap :: (b -> c) -> Nullspec a b -> Nullspec a c # (#.) :: forall a b c q. Coercible c b => q b c -> Nullspec a b -> Nullspec a c # (.#) :: forall a b c q. Coercible b a => Nullspec b c -> q a b -> Nullspec a c # | |
IsSqlType b => Default Nullspec a (Field_ n b) Source # | |
Defined in Opaleye.Internal.Values | |
Applicative (Nullspec a) Source # | |
Defined in Opaleye.Internal.Values | |
Functor (Nullspec a) Source # | |
nullspecMaybeFields :: Nullspec a b -> Nullspec (MaybeFields a) (MaybeFields b) Source #
nullspecList :: Nullspec a [b] Source #
binaryspecMaybeFields :: WithNulls Binaryspec a b -> Binaryspec (MaybeFields a) (MaybeFields b) Source #
distinctspecMaybeFields :: WithNulls Distinctspec a b -> Distinctspec (MaybeFields a) (MaybeFields b) Source #
fromFieldsMaybeFields :: FromFields fields haskells -> FromFields (MaybeFields fields) (Maybe haskells) Source #
toFieldsMaybeFields :: Nullspec a b -> ToFields a b -> ToFields (Maybe a) (MaybeFields b) Source #
unpackspecMaybeFields :: Unpackspec a b -> Unpackspec (MaybeFields a) (MaybeFields b) Source #
valuesspecMaybeFields :: Valuesspec a b -> Valuesspec (MaybeFields a) (MaybeFields b) Source #
Explicit versions
nothingFieldsExplicit :: Nullspec a b -> MaybeFields b Source #
fromMaybeFieldsExplicit :: IfPP b b -> b -> MaybeFields b -> b Source #
maybeFieldsExplicit :: IfPP b b' -> b -> (a -> b) -> MaybeFields a -> b' Source #
optionalExplicit :: Unpackspec a a -> SelectArr i a -> SelectArr i (MaybeFields a) Source #
traverseMaybeFieldsExplicit :: Unpackspec a a -> Unpackspec b b -> SelectArr a b -> SelectArr (MaybeFields a) (MaybeFields b) Source #