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

Safe HaskellNone
LanguageHaskell2010

Glazier.React.Widgets.Input

Synopsis

Documentation

data Command act Source #

Instances

Functor Command Source # 

Methods

fmap :: (a -> b) -> Command a -> Command b #

(<$) :: a -> Command b -> Command a #

data Gasket Source #

Constructors

Gasket 

Fields

Instances

Generic Gasket Source # 

Associated Types

type Rep Gasket :: * -> * #

Methods

from :: Gasket -> Rep Gasket x #

to :: Rep Gasket x -> Gasket #

Disposing Gasket Source # 
HasGasket Gasket Source # 
HasGasket (SuperModel Gasket Model) Source # 

Methods

gasket :: Lens' (SuperModel Gasket Model) Gasket Source #

component :: Lens' (SuperModel Gasket Model) ReactComponent Source #

onInputRef :: Lens' (SuperModel Gasket Model) (Callback (JSVal -> IO ())) Source #

onKeyDown :: Lens' (SuperModel Gasket Model) (Callback (JSVal -> IO ())) Source #

onRender :: Lens' (SuperModel Gasket Model) (Callback (JSVal -> IO JSVal)) Source #

HasGasket (GModel Gasket Model) Source # 

Methods

gasket :: Lens' (GModel Gasket Model) Gasket Source #

component :: Lens' (GModel Gasket Model) ReactComponent Source #

onInputRef :: Lens' (GModel Gasket Model) (Callback (JSVal -> IO ())) Source #

onKeyDown :: Lens' (GModel Gasket Model) (Callback (JSVal -> IO ())) Source #

onRender :: Lens' (GModel Gasket Model) (Callback (JSVal -> IO JSVal)) Source #

HasModel (SuperModel Gasket Model) Source # 
HasModel (GModel Gasket Model) Source # 
type Rep Gasket Source # 
type Rep Gasket = D1 (MetaData "Gasket" "Glazier.React.Widgets.Input" "glazier-react-widget-0.1.0.0-L7ptADVVxlGft9VBkyPbJ" False) (C1 (MetaCons "Gasket" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_component") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ReactComponent)) (S1 (MetaSel (Just Symbol "_onRender") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Callback (JSVal -> IO JSVal))))) ((:*:) (S1 (MetaSel (Just Symbol "_onInputRef") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Callback (JSVal -> IO ())))) (S1 (MetaSel (Just Symbol "_onKeyDown") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Callback (JSVal -> IO ())))))))

class HasGasket c where Source #

Minimal complete definition

gasket

mkGasket :: MModel Gasket Model -> F (Maker (Action act)) Gasket Source #

data Model Source #

Instances

Disposing Model Source # 
HasModel Model Source # 
HasGasket (SuperModel Gasket Model) Source # 

Methods

gasket :: Lens' (SuperModel Gasket Model) Gasket Source #

component :: Lens' (SuperModel Gasket Model) ReactComponent Source #

onInputRef :: Lens' (SuperModel Gasket Model) (Callback (JSVal -> IO ())) Source #

onKeyDown :: Lens' (SuperModel Gasket Model) (Callback (JSVal -> IO ())) Source #

onRender :: Lens' (SuperModel Gasket Model) (Callback (JSVal -> IO JSVal)) Source #

HasGasket (GModel Gasket Model) Source # 

Methods

gasket :: Lens' (GModel Gasket Model) Gasket Source #

component :: Lens' (GModel Gasket Model) ReactComponent Source #

onInputRef :: Lens' (GModel Gasket Model) (Callback (JSVal -> IO ())) Source #

onKeyDown :: Lens' (GModel Gasket Model) (Callback (JSVal -> IO ())) Source #

onRender :: Lens' (GModel Gasket Model) (Callback (JSVal -> IO JSVal)) Source #

HasModel (SuperModel Gasket Model) Source # 
HasModel (GModel Gasket Model) Source # 

mkSuperModel :: Model -> F (Maker (Action act)) (SuperModel act) Source #

data Widget act Source #

Instances

IsWidget (Widget act) Source # 

Associated Types

type WidgetAction (Widget act) :: *

type WidgetCommand (Widget act) :: *

type WidgetModel (Widget act) :: *

type WidgetGasket (Widget act) :: *

type WidgetModel (Widget act) Source # 
type WidgetModel (Widget act) = Model
type WidgetGasket (Widget act) Source # 
type WidgetGasket (Widget act) = Gasket
type WidgetCommand (Widget act) Source # 
type WidgetCommand (Widget act) = Command act
type WidgetAction (Widget act) Source # 
type WidgetAction (Widget act) = Action act

type GModel act = WidgetGModel (Widget act) Source #

type MModel act = WidgetMModel (Widget act) Source #

type SuperModel act = WidgetSuperModel (Widget act) Source #

window :: Monad m => WindowT (GModel act) (ReactMlT m) () Source #

This is used by parent components to render this component

gadget :: Monad m => GadgetT (Action act) (SuperModel act) m (DList (Command act)) Source #

State update logic. The best practice is to leave this in general Monad m (eg, not MonadIO). This allows gadget to use STM as the base monad which allows for combining concurrently with other stateful STM effects and still maintain a single source of truth.