| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Opaleye.MaybeFields
Contents
Description
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
- justFields :: a -> MaybeFields a
- fromMaybeFields :: Default IfPP b b => b -> MaybeFields b -> b
- maybeFields :: Default IfPP b b => b -> (a -> b) -> MaybeFields a -> b
- maybeFieldsToSelect :: SelectArr (MaybeFields a) a
- nothingFieldsOfTypeOf :: a -> MaybeFields a
- catMaybeFields :: SelectArr i (MaybeFields a) -> SelectArr i 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)
- data Nullspec fields fields'
- nullspecField :: IsSqlType b => Nullspec a (Column b)
- 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)
Documentation
data MaybeFields fields Source #
The Opaleye analogue of Maybe
Instances
nothingFields :: Default Nullspec a a => MaybeFields a Source #
The Opaleye analogue of Nothing.
justFields :: a -> MaybeFields a Source #
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
maybeFieldsToSelect :: SelectArr (MaybeFields a) a Source #
The Opaleye analogue of maybeToList
nothingFieldsOfTypeOf :: a -> MaybeFields a Source #
catMaybeFields :: SelectArr i (MaybeFields a) -> SelectArr i a Source #
The Opaleye analogue of catMaybes
Arguments
| :: 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" | 
NB Opaleye exports Opaleye.Table. from
 the top level.  If you want this optionaloptional you will have to import
 it from this module.
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 aoptional q
 :: SelectArr i (MaybeFields a)optional qq
 wrapped in "Just".  For example,
> let l1 = ["one", "two", "three"] :: [Field SqlText] >runSelectconn (optional(valuesSafel1)) :: IO [Maybe String] [Just "one", Just "two", Just "three"] > let l2 = [] :: [Field SqlText] >runSelectconn (optional(valuesSafel2)) :: IO [Maybe String] [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
Arguments
| :: (Default Unpackspec a a, Default Unpackspec b b) | |
| => SelectArr a b | |
| -> SelectArr (MaybeFields a) (MaybeFields b) | 
traverseMaybeFields is analogous to Haskell's
 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) 
Adaptors
data Nullspec fields fields' Source #
Instances
| Profunctor Nullspec Source # | |
| Defined in Opaleye.Internal.Values Methods 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 # | |
| ProductProfunctor Nullspec Source # | |
| IsSqlType b => Default Nullspec a (Column b) Source # | |
| Defined in Opaleye.Internal.Values | |
| Functor (Nullspec a) Source # | |
| Applicative (Nullspec a) Source # | |
| Defined in Opaleye.Internal.Values | |
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 #