extensible-0.4.7.2: Extensible, efficient, optics-friendly data types and effects

Copyright(c) Fumiaki Kinoshita 2017
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Extensible.Nullable

Description

 

Synopsis

Documentation

vacancy :: Generate xs => Nullable h :* xs Source #

A product filled with Nullable Nothing

coinclusion :: (Include ys xs, Generate ys) => Nullable (Membership xs) :* ys Source #

The inverse of inclusion.

wrench :: (Generate ys, xs ys) => (h :* xs) -> Nullable h :* ys Source #

Extend a product and fill missing fields by Null.

retrench :: (Generate ys, xs ys) => (h :| ys) -> Nullable ((:|) h) xs Source #

Narrow the range of the sum, if possible.

newtype Nullable h x Source #

Wrapped Maybe

Constructors

Nullable 

Fields

Instances

Wrapper k h => Wrapper k (Nullable k h) Source # 

Associated Types

type Repr (Nullable k h) (h :: Nullable k h -> *) (v :: Nullable k h) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr (Nullable k h) h v) Source #

Eq (h x) => Eq (Nullable k h x) Source # 

Methods

(==) :: Nullable k h x -> Nullable k h x -> Bool #

(/=) :: Nullable k h x -> Nullable k h x -> Bool #

Ord (h x) => Ord (Nullable k h x) Source # 

Methods

compare :: Nullable k h x -> Nullable k h x -> Ordering #

(<) :: Nullable k h x -> Nullable k h x -> Bool #

(<=) :: Nullable k h x -> Nullable k h x -> Bool #

(>) :: Nullable k h x -> Nullable k h x -> Bool #

(>=) :: Nullable k h x -> Nullable k h x -> Bool #

max :: Nullable k h x -> Nullable k h x -> Nullable k h x #

min :: Nullable k h x -> Nullable k h x -> Nullable k h x #

Show (h x) => Show (Nullable k h x) Source # 

Methods

showsPrec :: Int -> Nullable k h x -> ShowS #

show :: Nullable k h x -> String #

showList :: [Nullable k h x] -> ShowS #

Generic (Nullable k h x) Source # 

Associated Types

type Rep (Nullable k h x) :: * -> * #

Methods

from :: Nullable k h x -> Rep (Nullable k h x) x #

to :: Rep (Nullable k h x) x -> Nullable k h x #

Semigroup (h x) => Semigroup (Nullable k h x) Source # 

Methods

(<>) :: Nullable k h x -> Nullable k h x -> Nullable k h x #

sconcat :: NonEmpty (Nullable k h x) -> Nullable k h x #

stimes :: Integral b => b -> Nullable k h x -> Nullable k h x #

Semigroup (h x) => Monoid (Nullable k h x) Source # 

Methods

mempty :: Nullable k h x #

mappend :: Nullable k h x -> Nullable k h x -> Nullable k h x #

mconcat :: [Nullable k h x] -> Nullable k h x #

Arbitrary (h x) => Arbitrary (Nullable k h x) Source # 

Methods

arbitrary :: Gen (Nullable k h x) #

shrink :: Nullable k h x -> [Nullable k h x] #

Hashable (h x) => Hashable (Nullable k h x) Source # 

Methods

hashWithSalt :: Int -> Nullable k h x -> Int #

hash :: Nullable k h x -> Int #

NFData (h x) => NFData (Nullable k h x) Source # 

Methods

rnf :: Nullable k h x -> () #

type Repr k (Nullable k h) x Source # 
type Repr k (Nullable k h) x = Maybe (Repr k h x)
type Rep (Nullable k h x) Source # 
type Rep (Nullable k h x) = D1 * (MetaData "Nullable" "Data.Extensible.Nullable" "extensible-0.4.7.2-7kfLsNOFubHGh4xGyZYKUH" True) (C1 * (MetaCons "Nullable" PrefixI True) (S1 * (MetaSel (Just Symbol "getNullable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (h x)))))

mapNullable :: (g x -> h y) -> Nullable g x -> Nullable h y Source #

Apply a function to its content.