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

Safe HaskellNone
LanguageHaskell2010

Internal.Data.Basic.Lens

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 #

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

class SupportedModifyAccess isSet existingValue outVal | isSet outVal -> existingValue where Source #

Minimal complete definition

transformModifyFunction

Methods

transformModifyFunction :: (existingValue -> f outVal) -> outVal -> f outVal Source #

Instances

SupportedModifyAccess Bool False () outVal Source # 

Methods

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

SupportedModifyAccess Bool True outVal outVal Source # 

Methods

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

fieldOpticEntityModify :: forall name t entKind existingValue proxy. (TableField t name, SupportedModifyAccess (FieldIsGettableBool name (MissingFields entKind)) existingValue (TableFieldType t name)) => proxy name -> PolyOptic Identity (Entity entKind t) (Entity (WithFieldSet name entKind) t) existingValue (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 t0 name0, EqualOrError Bool (Not (Elem Symbol name0 fields0)) True ((:<>:) ((:<>:) (Text "Cannot update the field ") (ShowType Symbol name0)) (Text " because it's already updated in this expression")), ValueAsDbExp val0 (TableFieldType t0 name0), (~) * t5 (Identity (UpdateExp ((:) Symbol name0