glazier-react-widget-0.6.0.0: Generic widget library using glazier-react

Safe HaskellNone
LanguageHaskell2010

Glazier.React.Widgets.List

Documentation

data Command k itemWidget Source #

Constructors

RenderCommand (Gizmo (Model k itemWidget) Plan) [Property] JSVal 
DisposeCommand SomeDisposable 
MakerCommand (F (Maker (Action k itemWidget)) (Action k itemWidget)) 
ItemCommand k (CommandOf itemWidget) 

data Action k itemWidget Source #

Constructors

ComponentRefAction JSVal 
RenderAction 
ComponentDidUpdateAction 
DestroyItemAction k 
MakeItemAction (k -> k) (k -> F (Maker (ActionOf itemWidget)) (ModelOf itemWidget)) 
AddItemAction k (GizmoOf itemWidget) 
ItemAction k (ActionOf itemWidget) 
SetFilterAction (OutlineOf itemWidget -> Bool) 

Instances

AsAction (Action k0 itemWidget0) k0 itemWidget0 Source # 

Methods

_Action :: Prism' (Action k0 itemWidget0) (Action k0 itemWidget0) Source #

_ComponentRefAction :: Prism' (Action k0 itemWidget0) JSVal Source #

_RenderAction :: Prism' (Action k0 itemWidget0) () Source #

_ComponentDidUpdateAction :: Prism' (Action k0 itemWidget0) () Source #

_DestroyItemAction :: Prism' (Action k0 itemWidget0) k0 Source #

_MakeItemAction :: Prism' (Action k0 itemWidget0) (k0 -> k0, k0 -> F (Maker (ActionOf itemWidget0)) (ModelOf itemWidget0)) Source #

_AddItemAction :: Prism' (Action k0 itemWidget0) (k0, GizmoOf itemWidget0) Source #

_ItemAction :: Prism' (Action k0 itemWidget0) (k0, ActionOf itemWidget0) Source #

_SetFilterAction :: Prism' (Action k0 itemWidget0) (OutlineOf itemWidget0 -> Bool) Source #

class AsAction r k itemWidget | r -> k itemWidget where Source #

Instances

AsAction (Action k0 itemWidget0) k0 itemWidget0 Source # 

Methods

_Action :: Prism' (Action k0 itemWidget0) (Action k0 itemWidget0) Source #

_ComponentRefAction :: Prism' (Action k0 itemWidget0) JSVal Source #

_RenderAction :: Prism' (Action k0 itemWidget0) () Source #

_ComponentDidUpdateAction :: Prism' (Action k0 itemWidget0) () Source #

_DestroyItemAction :: Prism' (Action k0 itemWidget0) k0 Source #

_MakeItemAction :: Prism' (Action k0 itemWidget0) (k0 -> k0, k0 -> F (Maker (ActionOf itemWidget0)) (ModelOf itemWidget0)) Source #

_AddItemAction :: Prism' (Action k0 itemWidget0) (k0, GizmoOf itemWidget0) Source #

_ItemAction :: Prism' (Action k0 itemWidget0) (k0, ActionOf itemWidget0) Source #

_SetFilterAction :: Prism' (Action k0 itemWidget0) (OutlineOf itemWidget0 -> Bool) Source #

data Schema k itemWidget t Source #

Constructors

Schema JSString k (Map k (SchemaType t itemWidget)) (OutlineOf itemWidget -> Bool) 

Instances

Disposing (GizmoOf itemWidget) => Disposing (Model k itemWidget) Source #

Undecidable instances because itemWidget appears more often in the constraint but this is safe because R.GizmoOf itemWidget is smaller than Model k itemWidget

Methods

disposing :: Model k itemWidget -> SomeDisposable #

HasPlan (Scene (Model k itemWidget) Plan) Source # 
HasPlan (Gizmo (Model k itemWidget) Plan) Source # 
HasSchema (Scene (Model k itemWidget) Plan) k itemWidget WithGizmo Source # 

Methods

schema :: Lens' (Scene (Model k itemWidget) Plan) (Schema k itemWidget WithGizmo) Source #

className :: Lens' (Scene (Model k itemWidget) Plan) JSString Source #

idx :: Lens' (Scene (Model k itemWidget) Plan) k Source #

items :: Lens' (Scene (Model k itemWidget) Plan) (Map k (SchemaType WithGizmo itemWidget)) Source #

itemsFilter :: Lens' (Scene (Model k itemWidget) Plan) (OutlineOf itemWidget -> Bool) Source #

HasSchema (Gizmo (Model k itemWidget) Plan) k itemWidget WithGizmo Source # 

Methods

schema :: Lens' (Gizmo (Model k itemWidget) Plan) (Schema k itemWidget WithGizmo) Source #

className :: Lens' (Gizmo (Model k itemWidget) Plan) JSString Source #

idx :: Lens' (Gizmo (Model k itemWidget) Plan) k Source #

items :: Lens' (Gizmo (Model k itemWidget) Plan) (Map k (SchemaType WithGizmo itemWidget)) Source #

itemsFilter :: Lens' (Gizmo (Model k itemWidget) Plan) (OutlineOf itemWidget -> Bool) Source #

IsWidget itemWidget => ToOutline (Model k itemWidget) (Outline k itemWidget) Source # 

Methods

outline :: Model k itemWidget -> Outline k itemWidget #

HasSchema (Schema k0 itemWidget0 t0) k0 itemWidget0 t0 Source # 

Methods

schema :: Lens' (Schema k0 itemWidget0 t0) (Schema k0 itemWidget0 t0) Source #

className :: Lens' (Schema k0 itemWidget0 t0) JSString Source #

idx :: Lens' (Schema k0 itemWidget0 t0) k0 Source #

items :: Lens' (Schema k0 itemWidget0 t0) (Map k0 (SchemaType t0 itemWidget0)) Source #

itemsFilter :: Lens' (Schema k0 itemWidget0 t0) (OutlineOf itemWidget0 -> Bool) Source #

class HasSchema c k itemWidget t | c -> k itemWidget t where Source #

Minimal complete definition

schema

Methods

schema :: Lens' c (Schema k itemWidget t) Source #

className :: Lens' c JSString Source #

idx :: Lens' c k Source #

items :: Lens' c (Map k (SchemaType t itemWidget)) Source #

itemsFilter :: Lens' c (OutlineOf itemWidget -> Bool) Source #

Instances

HasSchema (Scene (Model k itemWidget) Plan) k itemWidget WithGizmo Source # 

Methods

schema :: Lens' (Scene (Model k itemWidget) Plan) (Schema k itemWidget WithGizmo) Source #

className :: Lens' (Scene (Model k itemWidget) Plan) JSString Source #

idx :: Lens' (Scene (Model k itemWidget) Plan) k Source #

items :: Lens' (Scene (Model k itemWidget) Plan) (Map k (SchemaType WithGizmo itemWidget)) Source #

itemsFilter :: Lens' (Scene (Model k itemWidget) Plan) (OutlineOf itemWidget -> Bool) Source #

HasSchema (Gizmo (Model k itemWidget) Plan) k itemWidget WithGizmo Source # 

Methods

schema :: Lens' (Gizmo (Model k itemWidget) Plan) (Schema k itemWidget WithGizmo) Source #

className :: Lens' (Gizmo (Model k itemWidget) Plan) JSString Source #

idx :: Lens' (Gizmo (Model k itemWidget) Plan) k Source #

items :: Lens' (Gizmo (Model k itemWidget) Plan) (Map k (SchemaType WithGizmo itemWidget)) Source #

itemsFilter :: Lens' (Gizmo (Model k itemWidget) Plan) (OutlineOf itemWidget -> Bool) Source #

HasSchema (Schema k0 itemWidget0 t0) k0 itemWidget0 t0 Source # 

Methods

schema :: Lens' (Schema k0 itemWidget0 t0) (Schema k0 itemWidget0 t0) Source #

className :: Lens' (Schema k0 itemWidget0 t0) JSString Source #

idx :: Lens' (Schema k0 itemWidget0 t0) k0 Source #

items :: Lens' (Schema k0 itemWidget0 t0) (Map k0 (SchemaType t0 itemWidget0)) Source #

itemsFilter :: Lens' (Schema k0 itemWidget0 t0) (OutlineOf itemWidget0 -> Bool) Source #

data Plan Source #

Instances

Generic Plan Source # 

Associated Types

type Rep Plan :: * -> * #

Methods

from :: Plan -> Rep Plan x #

to :: Rep Plan x -> Plan #

Disposing Plan Source # 
HasPlan Plan Source # 
HasPlan (Scene (Model k itemWidget) Plan) Source # 
HasPlan (Gizmo (Model k itemWidget) Plan) Source # 
HasSchema (Scene (Model k itemWidget) Plan) k itemWidget WithGizmo Source # 

Methods

schema :: Lens' (Scene (Model k itemWidget) Plan) (Schema k itemWidget WithGizmo) Source #

className :: Lens' (Scene (Model k itemWidget) Plan) JSString Source #

idx :: Lens' (Scene (Model k itemWidget) Plan) k Source #

items :: Lens' (Scene (Model k itemWidget) Plan) (Map k (SchemaType WithGizmo itemWidget)) Source #

itemsFilter :: Lens' (Scene (Model k itemWidget) Plan) (OutlineOf itemWidget -> Bool) Source #

HasSchema (Gizmo (Model k itemWidget) Plan) k itemWidget WithGizmo Source # 

Methods

schema :: Lens' (Gizmo (Model k itemWidget) Plan) (Schema k itemWidget WithGizmo) Source #

className :: Lens' (Gizmo (Model k itemWidget) Plan) JSString Source #

idx :: Lens' (Gizmo (Model k itemWidget) Plan) k Source #

items :: Lens' (Gizmo (Model k itemWidget) Plan) (Map k (SchemaType WithGizmo itemWidget)) Source #

itemsFilter :: Lens' (Gizmo (Model k itemWidget) Plan) (OutlineOf itemWidget -> Bool) Source #

type Rep Plan Source # 

class HasPlan c where Source #

Minimal complete definition

plan

Instances

HasPlan Plan Source # 
HasPlan (Scene (Model k itemWidget) Plan) Source # 
HasPlan (Gizmo (Model k itemWidget) Plan) Source # 

type Outline k itemWidget = Schema k itemWidget WithOutline Source #

type Model k itemWidget = Schema k itemWidget WithGizmo Source #

type Widget k itemWidget = Widget (Command k itemWidget) (Action k itemWidget) (Outline k itemWidget) (Model k itemWidget) Plan Source #

widget :: (IsWidget itemWidget, Ord k) => ReactMlT Identity () -> itemWidget -> Widget k itemWidget Source #