data-basic-0.3.0.0: A database library with a focus on ease of use, type safety and useful error messages

Safe HaskellNone
LanguageHaskell2010

Internal.Data.Basic.Lens

Synopsis

Documentation

type PolyOptic fun inType outType inVal outVal = (inVal -> fun outVal) -> inType -> fun outType Source #

type Getter' s a = PolyOptic (Const a) s s a a Source #

fieldOpticVarExp :: forall name t anyCtx proxy. TableField t name => proxy name -> PolyOptic (Const (DbExp FieldExp (TableFieldType t name))) (Var anyCtx t) (Var anyCtx t) (DbExp FieldExp (TableFieldType t name)) (DbExp FieldExp (TableFieldType t name)) Source #

type GettableField entKind field = FieldIsGettable field (MissingFields entKind) Source #

fieldOpticEntityGet :: forall name t entKind proxy. (TableField t name, GettableField entKind name) => proxy name -> PolyOptic (Const (TableFieldType t name)) (Entity entKind t) (Entity entKind t) (TableFieldType t name) (TableFieldType t name) Source #

class SupportedModifyAccess isSet outVal where Source #

Minimal complete definition

transformModifyFunction

Associated Types

type ExistingValue isSet outVal :: * Source #

Methods

transformModifyFunction :: (ExistingValue isSet outVal -> f outVal) -> outVal -> f outVal Source #

Instances

SupportedModifyAccess Bool False outVal Source # 

Associated Types

type ExistingValue False (outVal :: False) outVal :: * Source #

Methods

transformModifyFunction :: (ExistingValue False outVal outVal -> f outVal) -> outVal -> f outVal Source #

SupportedModifyAccess Bool True outVal Source # 

Associated Types

type ExistingValue True (outVal :: True) outVal :: * Source #

Methods

transformModifyFunction :: (ExistingValue True outVal outVal -> f outVal) -> outVal -> f outVal Source #

type ModifyableField table entKind field = SupportedModifyAccess (FieldIsGettableBool field (MissingFields entKind)) (TableFieldType table field) Source #

A field that's settable, but also potentially gettable (if it's already set). If it is gettable then you can modify it, otherwise you can just set it.

type SettableField table entKind field = ModifyableField table entKind field Source #

A synonym for ModifyableField. It still checks if the field is already set.

fieldOpticEntityModify :: forall name t entKind proxy. (TableField t name, ModifyableField t entKind name) => proxy name -> PolyOptic Identity (Entity entKind t) (Entity (WithFieldSet name entKind) t) (ExistingValue (FieldIsGettableBool name (MissingFields entKind)) (TableFieldType t name)) (TableFieldType t name) Source #

fieldOpticUpdateVarSet :: forall name t val proxy. (ValueAsDbExp val (TableFieldType t name), TableField t name) => proxy name -> PolyOptic Identity (Var Updating t) (UpdateExp '[name] t) (DbExp FieldExp (TableFieldType t name)) val Source #

fieldOpticUpdatedSet :: forall name t fields val proxy. (TableField t name, FieldIsNotSet name fields, ValueAsDbExp val (TableFieldType t name)) => proxy name -> PolyOptic Identity (UpdateExp fields t) (UpdateExp (name ': fields) t) (DbExp FieldExp (TableFieldType t name)) val Source #

class FieldOpticProxy t where Source #

Minimal complete definition

fieldOpticProxy

Instances

(TableField t name, EqualOrError Bool (Not (Elem Symbol name fields)) True ((:<>:) ((:<>:) (Text "Cannot update the field ") (ShowType Symbol name)) (Text " because it's already updated in this expression")), ValueAsDbExp val (TableFieldType t name), (~) * t5 (Identity (UpdateExp ((:) Symbol name fields) t)), (~) * t4 t, (~) [Symbol] t3 fields, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name) -> Identity val)), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (UpdateExp t3 t4) t5))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (UpdateExp t3 t4) t5)) Source #

(ValueAsDbExp val (TableFieldType t name), TableField t name, (~) * t7 (Identity (UpdateExp ((:) Symbol name ([] Symbol)) t)), (~) * t6 t, (~) VarContext t5 Updating, (~) (* -> * -> *) t4 ((->) LiftedRep LiftedRep), (~) * t3 val, (~) (* -> *) t2 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name))), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Identity t3)) (t4 (Var t5 t6) t7))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Identity t3)) (t4 (Var t5 t6) t7)) Source #

(ValueAsDbExp val (TableFieldType t name), TableField t name, (~) * t5 (UpdateExp ((:) Symbol name ([] Symbol)) t), (~) * t4 t, (~) VarContext t3 Updating, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name) -> Identity val)), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Var t3 t4) (Identity t5)))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Var t3 t4) (Identity t5))) Source #

(ValueAsDbExp val (TableFieldType t name), TableField t name, (~) * t7 t, (~) [Symbol] t6 ((:) Symbol name ([] Symbol)), (~) (* -> *) t5 Identity, (~) * t4 t, (~) VarContext t3 Updating, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name) -> Identity val)), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Var t3 t4) (t5 (UpdateExp t6 t7))))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Var t3 t4) (t5 (UpdateExp t6 t7)))) Source #

(TableField t name, SupportedModifyAccess Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name), (~) * t7 (Identity (Entity (WithFieldSet name entKind) t)), (~) * t6 t, (~) EntityKind t5 entKind, (~) (* -> * -> *) t4 ((->) LiftedRep LiftedRep), (~) * t3 (TableFieldType t name), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (ExistingValue Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name))), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Identity t3)) (t4 (Entity t5 t6) t7))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Identity t3)) (t4 (Entity t5 t6) t7)) Source #

(TableField t name, SupportedModifyAccess Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name), (~) * t7 t, (~) EntityKind t6 (WithFieldSet name entKind), (~) (* -> *) t5 Identity, (~) (* -> *) t4 ((->) LiftedRep LiftedRep (Entity entKind t)), (~) * t3 (TableFieldType t name), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (ExistingValue Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name))), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Identity t3)) (t4 (t5 (Entity t6 t7))))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Identity t3)) (t4 (t5 (Entity t6 t7)))) Source #

(TableField t name, SupportedModifyAccess Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name), (~) * t5 (Entity (WithFieldSet name entKind) t), (~) * t4 t, (~) EntityKind t3 entKind, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (ExistingValue Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name) -> Identity (TableFieldType t name))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Entity t3 t4) (Identity t5)))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Entity t3 t4) (Identity t5))) Source #

(TableField t name, SupportedModifyAccess Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name), (~) * t4 t, (~) EntityKind t3 (WithFieldSet name entKind), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (Entity entKind t)), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (ExistingValue Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name) -> Identity (TableFieldType t name))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Identity (Entity t3 t4))))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Identity (Entity t3 t4)))) Source #

(TableField t name, EqualOrError Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) True ((:<>:) ((:<>:) (Text "Field ") (ShowType Symbol name)) (Text " is not set")), (~) * t9 (Const * (TableFieldType t name) (Entity entKind t)), (~) * t8 t, (~) EntityKind t7 entKind, (~) (* -> * -> *) t6 ((->) LiftedRep LiftedRep), (~) * t5 (TableFieldType t name), (~) * t4 (TableFieldType t name), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (TableFieldType t name)), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (t3 t4 t5)) (t6 (Entity t7 t8) t9))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (t3 t4 t5)) (t6 (Entity t7 t8) t9)) Source #

(TableField t name, EqualOrError Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) True ((:<>:) ((:<>:) (Text "Field ") (ShowType Symbol name)) (Text " is not set")), (~) * t7 (Entity entKind t), (~) * t6 (TableFieldType t name), (~) (* -> * -> *) t5 (Const *), (~) * t4 t, (~) EntityKind t3 entKind, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (TableFieldType t name -> Const * (TableFieldType t name) (TableFieldType t name))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Entity t3 t4) (t5 t6 t7)))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Entity t3 t4) (t5 t6 t7))) Source #

(TableField t name, EqualOrError Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) True ((:<>:) ((:<>:) (Text "Field ") (ShowType Symbol name)) (Text " is not set")), (~) * t9 t, (~) EntityKind t8 entKind, (~) (* -> *) t7 (Const * (TableFieldType t name)), (~) (* -> *) t6 ((->) LiftedRep LiftedRep (Entity entKind t)), (~) * t5 (TableFieldType t name), (~) * t4 (TableFieldType t name), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (TableFieldType t name)), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (t3 t4 t5)) (t6 (t7 (Entity t8 t9))))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (t3 t4 t5)) (t6 (t7 (Entity t8 t9)))) Source #

(TableField t name, EqualOrError Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) True ((:<>:) ((:<>:) (Text "Field ") (ShowType Symbol name)) (Text " is not set")), (~) * t6 t, (~) EntityKind t5 entKind, (~) * t4 (TableFieldType t name), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (Entity entKind t)), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (TableFieldType t name -> Const * (TableFieldType t name) (TableFieldType t name))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (t3 t4 (Entity t5 t6))))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (t3 t4 (Entity t5 t6)))) Source #

(TableField t name, (~) * t9 (Const * (DbExp FieldExp (TableFieldType t name)) (Var anyCtx t)), (~) * t8 t, (~) VarContext t7 anyCtx, (~) (* -> * -> *) t6 ((->) LiftedRep LiftedRep), (~) * t5 (DbExp FieldExp (TableFieldType t name)), (~) * t4 (DbExp FieldExp (TableFieldType t name)), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name))), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (t3 t4 t5)) (t6 (Var t7 t8) t9))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (t3 t4 t5)) (t6 (Var t7 t8) t9)) Source #

(TableField t name, (~) * t7 (Var anyCtx t), (~) * t6 (DbExp FieldExp (TableFieldType t name)), (~) (* -> * -> *) t5 (Const *), (~) * t4 t, (~) VarContext t3 anyCtx, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name) -> Const * (DbExp FieldExp (TableFieldType t name)) (DbExp FieldExp (TableFieldType t name)))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Var t3 t4) (t5 t6 t7)))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Var t3 t4) (t5 t6 t7))) Source #

(TableField t name, (~) * t5 t, (~) VarContext t4 anyCtx, (~) (* -> *) t3 (Const * (DbExp FieldExp (TableFieldType t name))), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (Var anyCtx t)), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name) -> Const * (DbExp FieldExp (TableFieldType t name)) (DbExp FieldExp (TableFieldType t name)))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (t3 (Var t4 t5))))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (t3 (Var t4 t5)))) Source #

fieldOptic :: forall name o. FieldOpticProxy (Proxy name -> o) => o Source #

fieldOpticEntitySet :: forall name t missing. TableField t name => PolyOptic Identity (Entity missing t) (Entity (WithFieldSet name missing) t) () (TableFieldType t name) Source #