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

Safe HaskellNone
LanguageHaskell2010

Glazier.React.Widgets.Collection.Dynamic

Synopsis

Documentation

data DynamicCollection ftr srt k a f Source #

Contains information on sorting and filtering the items in a collection differerently from the native data structure.

Constructors

DynamicCollection 

Fields

Instances
Generic (DynamicCollection ftr srt k a f) Source # 
Instance details

Defined in Glazier.React.Widgets.Collection.Dynamic

Associated Types

type Rep (DynamicCollection ftr srt k a f) :: * -> * #

Methods

from :: DynamicCollection ftr srt k a f -> Rep (DynamicCollection ftr srt k a f) x #

to :: Rep (DynamicCollection ftr srt k a f) x -> DynamicCollection ftr srt k a f #

type Rep (DynamicCollection ftr srt k a f) Source # 
Instance details

Defined in Glazier.React.Widgets.Collection.Dynamic

type Rep (DynamicCollection ftr srt k a f) = D1 (MetaData "DynamicCollection" "Glazier.React.Widgets.Collection.Dynamic" "glazier-react-widget-1.0.0.0-6HV9uwI557lI53FjkcrH3T" False) (C1 (MetaCons "DynamicCollection" PrefixI True) ((S1 (MetaSel (Just "filterCriteria") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ftr) :*: S1 (MetaSel (Just "sortCriteria") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 srt)) :*: (S1 (MetaSel (Just "visibleList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [HKD f a]) :*: S1 (MetaSel (Just "rawCollection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map k (HKD f a))))))

type HKDynamicCollection ftr srt k a f = DynamicCollection ftr srt k (a f) f Source #

_filterCriteria :: forall ftr srt k a f ftr. Lens (DynamicCollection ftr srt k a f) (DynamicCollection ftr srt k a f) ftr ftr Source #

_sortCriteria :: forall ftr srt k a f srt. Lens (DynamicCollection ftr srt k a f) (DynamicCollection ftr srt k a f) srt srt Source #

_visibleList :: forall ftr srt k a f. Lens' (DynamicCollection ftr srt k a f) [HKD f a] Source #

_rawCollection :: forall ftr srt k a f k. Lens (DynamicCollection ftr srt k a f) (DynamicCollection ftr srt k a f) (Map k (HKD f a)) (Map k (HKD f a)) Source #

updateVisibleList :: (ftr -> s -> ReadIORef Bool) -> (srt -> s -> s -> ReadIORef Ordering) -> ModelState (DynamicCollection ftr srt k s Subject) () Source #

deleteDynamicCollectionItem :: (MonadReactor p allS cmd m, Ord k) => k -> ModelState (DynamicCollection ftr srt k s Subject) (m ()) Source #

insertDynamicCollectionItem :: (MonadReactor p allS cmd m, Ord k) => k -> Subject s -> ModelState (DynamicCollection ftr srt k s Subject) (m ()) Source #