extensible-0.8.2: Extensible, efficient, optics-friendly data types and effects
Copyright(c) Fumiaki Kinoshita 2018
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Extensible.Nullable

Description

 
Synopsis

Documentation

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

A product filled with Nullable Nothing

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

The inverse of inclusion.

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

Extend a product and fill missing fields by Null.

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

Narrow the range of the sum, if possible.

newtype Nullable h x Source #

Wrapped Maybe

Constructors

Nullable 

Fields

Instances

Instances details
Wrapper h => Wrapper (Nullable h :: k -> Type) Source # 
Instance details

Defined in Data.Extensible.Nullable

Associated Types

type Repr (Nullable h) v Source #

Methods

_Wrapper :: forall f p (v :: k0). (Functor f, Profunctor p) => Optic' p f (Nullable h v) (Repr (Nullable h) v) Source #

wrap :: forall (v :: k0). Repr (Nullable h) v -> Nullable h v Source #

unwrap :: forall (v :: k0). Nullable h v -> Repr (Nullable h) v Source #

Lift (h a) => Lift (Nullable h a :: Type) Source # 
Instance details

Defined in Data.Extensible.Nullable

Methods

lift :: Nullable h a -> Q Exp #

liftTyped :: Nullable h a -> Q (TExp (Nullable h a)) #

Eq (h x) => Eq (Nullable h x) Source # 
Instance details

Defined in Data.Extensible.Nullable

Methods

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

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

Ord (h x) => Ord (Nullable h x) Source # 
Instance details

Defined in Data.Extensible.Nullable

Methods

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

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

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

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

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

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

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

Show (h x) => Show (Nullable h x) Source # 
Instance details

Defined in Data.Extensible.Nullable

Methods

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

show :: Nullable h x -> String #

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

Generic (Nullable h x) Source # 
Instance details

Defined in Data.Extensible.Nullable

Associated Types

type Rep (Nullable h x) :: Type -> Type #

Methods

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

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

Semigroup (h x) => Semigroup (Nullable h x) Source # 
Instance details

Defined in Data.Extensible.Nullable

Methods

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

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

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

Semigroup (h x) => Monoid (Nullable h x) Source # 
Instance details

Defined in Data.Extensible.Nullable

Methods

mempty :: Nullable h x #

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

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

Arbitrary (h x) => Arbitrary (Nullable h x) Source # 
Instance details

Defined in Data.Extensible.Nullable

Methods

arbitrary :: Gen (Nullable h x) #

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

Hashable (h x) => Hashable (Nullable h x) Source # 
Instance details

Defined in Data.Extensible.Nullable

Methods

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

hash :: Nullable h x -> Int #

Forall (KeyTargetAre KnownSymbol (Instance1 ToJSON h)) xs => ToJSON (xs :& Nullable (Field h :: Assoc Symbol v -> Type)) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

toJSON :: (xs :& Nullable (Field h)) -> Value #

toEncoding :: (xs :& Nullable (Field h)) -> Encoding #

toJSONList :: [xs :& Nullable (Field h)] -> Value #

toEncodingList :: [xs :& Nullable (Field h)] -> Encoding #

Forall (KeyTargetAre KnownSymbol (Instance1 FromJSON h)) xs => FromJSON (xs :& Nullable (Field h :: Assoc Symbol v -> Type)) Source # 
Instance details

Defined in Data.Extensible.Dictionary

NFData (h x) => NFData (Nullable h x) Source # 
Instance details

Defined in Data.Extensible.Nullable

Methods

rnf :: Nullable h x -> () #

type Repr (Nullable h :: k -> Type) (x :: k) Source # 
Instance details

Defined in Data.Extensible.Nullable

type Repr (Nullable h :: k -> Type) (x :: k) = Maybe (Repr h x)
type Rep (Nullable h x) Source # 
Instance details

Defined in Data.Extensible.Nullable

type Rep (Nullable h x) = D1 ('MetaData "Nullable" "Data.Extensible.Nullable" "extensible-0.8.2-1gOJ4bcwk2I57PbXgExUYC" 'True) (C1 ('MetaCons "Nullable" 'PrefixI 'True) (S1 ('MetaSel ('Just "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.

fromNullable :: h x -> Nullable h x -> h x Source #