| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GI.Gtk.Declarative
Description
The declarative layer on top of GTK+ lets you describe your user interface as a declarative hierarchy of objects, using data structures and pure functions. You can leverage the declarative event handling to build reusable widgets. The Patch typeclass, and the instances provided by this library, performs minimal updates to GTK+ widgets using the underlying imperative operations, so that your rendering can always be a pure function your state to a Widget.
Synopsis
- data EventHandler gtkEventHandler widget (purity :: Purity) event where- PureEventHandler :: EventHandlerReturn Identity ret e -> EventHandler (IO ret) w Pure e
- ImpureEventHandler :: (w -> EventHandlerReturn IO ret e) -> EventHandler (IO ret) w Impure e
- EventHandlerFunction :: (a -> EventHandler b w p e) -> EventHandler (a -> b) w p e
 
- type ClassSet = HashSet Text
- data Attribute widget event where- (:=) :: (AttrOpAllowed AttrConstruct info widget, AttrOpAllowed AttrSet info widget, AttrGetC info widget attr getValue, AttrSetTypeConstraint info setValue, KnownSymbol attr, Typeable attr, Eq setValue, Typeable setValue) => AttrLabelProxy (attr :: Symbol) -> setValue -> Attribute widget event
- Classes :: IsWidget widget => ClassSet -> Attribute widget event
- OnSignalPure :: (GObject widget, SignalInfo info, gtkCallback ~ HaskellCallbackType info, ToGtkCallback gtkCallback Pure) => SignalProxy widget info -> EventHandler gtkCallback widget Pure event -> Attribute widget event
- OnSignalImpure :: (GObject widget, SignalInfo info, gtkCallback ~ HaskellCallbackType info, ToGtkCallback gtkCallback Impure) => SignalProxy widget info -> EventHandler gtkCallback widget Impure event -> Attribute widget event
- AfterCreated :: (widget -> IO ()) -> Attribute widget event
 
- classes :: IsWidget widget => [Text] -> Attribute widget event
- on :: (GObject widget, SignalInfo info, gtkCallback ~ HaskellCallbackType info, ToGtkCallback gtkCallback Pure, ToEventHandler gtkCallback widget Pure, userEventHandler ~ UserEventHandler gtkCallback widget Pure event) => SignalProxy widget info -> userEventHandler -> Attribute widget event
- onM :: (GObject widget, SignalInfo info, gtkCallback ~ HaskellCallbackType info, ToGtkCallback gtkCallback Impure, ToEventHandler gtkCallback widget Impure, userEventHandler ~ UserEventHandler gtkCallback widget Impure event) => SignalProxy widget info -> userEventHandler -> Attribute widget event
- afterCreated :: (widget -> IO ()) -> Attribute widget event
- class Patchable widget where
- data Patch
- data CustomWidget widget params internalState event = CustomWidget {- customWidget :: ManagedPtr widget -> widget
- customCreate :: params -> IO (widget, internalState)
- customPatch :: params -> params -> internalState -> CustomPatch widget internalState
- customSubscribe :: params -> internalState -> widget -> (event -> IO ()) -> IO Subscription
- customAttributes :: Vector (Attribute widget event)
- customParams :: params
 
- data CustomPatch widget internalState- = CustomReplace
- | CustomModify (widget -> IO internalState)
- | CustomKeep
 
- class FromWidget widget target where- fromWidget :: widget event -> target event
 
- data Widget event where
- data SingleWidget widget event
- widget :: (Typeable widget, Typeable event, Functor (Attribute widget), IsWidget widget, FromWidget (SingleWidget widget) target) => (ManagedPtr widget -> widget) -> Vector (Attribute widget event) -> target event
- data BoxChildProperties = BoxChildProperties {}
- data BoxChild event = BoxChild {- properties :: BoxChildProperties
- child :: Widget event
 
- defaultBoxChildProperties :: BoxChildProperties
- data Container widget children event
- container :: (Patchable (Container widget (Children child)), Typeable widget, Typeable child, Typeable event, Functor child, IsWidget widget, IsContainer widget, FromWidget (Container widget (Children child)) target, ToChildren widget parent child) => (ManagedPtr widget -> widget) -> Vector (Attribute widget event) -> parent (child event) -> target event
- data PaneProperties = PaneProperties {}
- data Pane event
- defaultPaneProperties :: PaneProperties
- pane :: PaneProperties -> Widget event -> Pane event
- paned :: Typeable event => Vector (Attribute Paned event) -> Pane event -> Pane event -> Widget event
- data Bin widget event
- bin :: (Patchable (Bin widget), Typeable widget, Typeable event, IsContainer widget, IsBin widget, IsWidget widget, FromWidget (Bin widget) target) => (ManagedPtr widget -> widget) -> Vector (Attribute widget event) -> Widget event -> target event
- data MenuItem event
- menuItem :: (IsMenuItem item, Typeable event, Typeable item, IsContainer item, IsBin item, IsWidget item) => (ManagedPtr item -> item) -> Vector (Attribute item event) -> Widget event -> MenuItem event
- subMenu :: Typeable event => Text -> Vector (MenuItem event) -> MenuItem event
Documentation
data EventHandler gtkEventHandler widget (purity :: Purity) event where Source #
Encodes the user event handler in such a way that we can have
 a Functor instance for arity-polymorphic event handlers.
Constructors
| PureEventHandler :: EventHandlerReturn Identity ret e -> EventHandler (IO ret) w Pure e | |
| ImpureEventHandler :: (w -> EventHandlerReturn IO ret e) -> EventHandler (IO ret) w Impure e | |
| EventHandlerFunction :: (a -> EventHandler b w p e) -> EventHandler (a -> b) w p e | 
Instances
| Functor (EventHandler gtkEventHandler widget purity) Source # | |
| Defined in GI.Gtk.Declarative.Attributes.Internal.EventHandler Methods fmap :: (a -> b) -> EventHandler gtkEventHandler widget purity a -> EventHandler gtkEventHandler widget purity b # (<$) :: a -> EventHandler gtkEventHandler widget purity b -> EventHandler gtkEventHandler widget purity a # | |
data Attribute widget event where Source #
The attribute GADT represent a supported attribute for a declarative widget. This extends the regular notion of GTK+ attributes to also include event handling and CSS classes.
Constructors
| (:=) :: (AttrOpAllowed AttrConstruct info widget, AttrOpAllowed AttrSet info widget, AttrGetC info widget attr getValue, AttrSetTypeConstraint info setValue, KnownSymbol attr, Typeable attr, Eq setValue, Typeable setValue) => AttrLabelProxy (attr :: Symbol) -> setValue -> Attribute widget event | An attribute/value mapping for a declarative widget. The
  | 
| Classes :: IsWidget widget => ClassSet -> Attribute widget event | Defines a set of CSS classes for the underlying widget's style context.
 Use the  | 
| OnSignalPure :: (GObject widget, SignalInfo info, gtkCallback ~ HaskellCallbackType info, ToGtkCallback gtkCallback Pure) => SignalProxy widget info -> EventHandler gtkCallback widget Pure event -> Attribute widget event | Emit events using a pure event handler. Use the  | 
| OnSignalImpure :: (GObject widget, SignalInfo info, gtkCallback ~ HaskellCallbackType info, ToGtkCallback gtkCallback Impure) => SignalProxy widget info -> EventHandler gtkCallback widget Impure event -> Attribute widget event | Emit events using a pure event handler. Use the  | 
| AfterCreated :: (widget -> IO ()) -> Attribute widget event | Provide a callback to modify the widget after it's been created. | 
classes :: IsWidget widget => [Text] -> Attribute widget event Source #
Define the CSS classes for the underlying widget's style context. For these
 classes to have any effect, this requires a CssProvider with CSS files
 loaded, to be added to the GDK screen. You probably want to do this in your
 entry point when setting up GTK.
on :: (GObject widget, SignalInfo info, gtkCallback ~ HaskellCallbackType info, ToGtkCallback gtkCallback Pure, ToEventHandler gtkCallback widget Pure, userEventHandler ~ UserEventHandler gtkCallback widget Pure event) => SignalProxy widget info -> userEventHandler -> Attribute widget event Source #
Emit events, using a pure event handler, by subcribing to the specified signal.
onM :: (GObject widget, SignalInfo info, gtkCallback ~ HaskellCallbackType info, ToGtkCallback gtkCallback Impure, ToEventHandler gtkCallback widget Impure, userEventHandler ~ UserEventHandler gtkCallback widget Impure event) => SignalProxy widget info -> userEventHandler -> Attribute widget event Source #
Emit events, using an impure event handler receiving the widget and returning
 an IO action of event, by subcribing to the specified signal.
afterCreated :: (widget -> IO ()) -> Attribute widget event Source #
Provide a EventHandler to modify the widget after it's been created.
class Patchable widget where Source #
A patchable widget is one that can create an underlying GTK widget, or
 calculate a Patch to be applied to an existing GTK widget that was
 previously created.
Methods
create :: widget e -> IO SomeState Source #
Given a declarative widget that is Patchable, return an IO action that
 can create a new corresponding Widget. The created widget should be
 use in corresponding patch modifications, until it is replaced.
patch :: SomeState -> widget e1 -> widget e2 -> Patch Source #
Given two declarative widgets of the same widget type (but not
 necessarily of the same event types,) calculate a Patch.
Instances
| Patchable Widget Source # | 
 | 
| Patchable BoxChild Source # | |
| Patchable Pane Source # | |
| Patchable MenuItem Source # | |
| Patchable (SingleWidget widget) Source # | |
| Defined in GI.Gtk.Declarative.SingleWidget Methods create :: SingleWidget widget e -> IO SomeState Source # patch :: SomeState -> SingleWidget widget e1 -> SingleWidget widget e2 -> Patch Source # | |
| IsBin parent => Patchable (Bin parent) Source # | |
| (Patchable child, Typeable child, IsContainer container child) => Patchable (Container container (Children child)) Source # | |
| (Typeable widget, Typeable internalState, IsWidget widget) => Patchable (CustomWidget widget params internalState) Source # | |
| Defined in GI.Gtk.Declarative.CustomWidget Methods create :: CustomWidget widget params internalState e -> IO SomeState Source # patch :: SomeState -> CustomWidget widget params internalState e1 -> CustomWidget widget params internalState e2 -> Patch Source # | |
A possible action to take on an existing Widget, decided by the
 patch method when comparing declarative widgets.
Constructors
| Modify (IO SomeState) | An  | 
| Replace (IO SomeState) | Replace the current  | 
| Keep | Do nothing, i.e. keep the  | 
data CustomWidget widget params internalState event Source #
A custom widget specification, with all functions needed to
 instantiate Patchable and EventSource. A custom widget:
- is based on a top widget
- can use internalStateas a way of keeping an internal state value threaded through updates, which is often useful for passing references to child widgets used in a custom widget
- emits events of type event
Constructors
| CustomWidget | |
| Fields 
 | |
Instances
| Functor (CustomWidget widget params internalState) Source # | |
| Defined in GI.Gtk.Declarative.CustomWidget Methods fmap :: (a -> b) -> CustomWidget widget params internalState a -> CustomWidget widget params internalState b # (<$) :: a -> CustomWidget widget params internalState b -> CustomWidget widget params internalState a # | |
| (Typeable widget, Typeable internalState, IsWidget widget) => Patchable (CustomWidget widget params internalState) Source # | |
| Defined in GI.Gtk.Declarative.CustomWidget Methods create :: CustomWidget widget params internalState e -> IO SomeState Source # patch :: SomeState -> CustomWidget widget params internalState e1 -> CustomWidget widget params internalState e2 -> Patch Source # | |
| (Typeable internalState, GObject widget) => EventSource (CustomWidget widget params internalState) Source # | |
| Defined in GI.Gtk.Declarative.CustomWidget Methods subscribe :: CustomWidget widget params internalState event -> SomeState -> (event -> IO ()) -> IO Subscription Source # | |
data CustomPatch widget internalState Source #
Similar to Patch, describing a possible action to perform on a
 Widget, decided by customPatch.
Constructors
| CustomReplace | |
| CustomModify (widget -> IO internalState) | |
| CustomKeep | 
class FromWidget widget target where Source #
Convert a widget to a target type. This is deliberately unconstrained in
 it's types, and is used by smart constructors to implement return type
 polymorphism, so that a smart contructor can return either a Widget, or
 some specifically typed widget, depending on the context in which it's
 used.
Methods
fromWidget :: widget event -> target event Source #
Instances
| FromWidget widget Widget => FromWidget widget BoxChild Source # | Any widget that can be converted to a  | 
| Defined in GI.Gtk.Declarative.Widget.Conversions Methods fromWidget :: widget event -> BoxChild event Source # | |
| (Typeable parent, Typeable child, Patchable (parent child), Functor (parent child), EventSource (parent child)) => FromWidget (parent child) Widget Source # | |
| Defined in GI.Gtk.Declarative.Widget Methods fromWidget :: parent child event -> Widget event Source # | |
| a ~ b => FromWidget (Bin a) (Bin b) Source # | |
| Defined in GI.Gtk.Declarative.Bin Methods fromWidget :: Bin a event -> Bin b event Source # | |
| (Typeable widget, Typeable children, Patchable (Container widget children), EventSource (Container widget children), Functor (Container widget children)) => FromWidget (Container widget children) Widget Source # | |
| Defined in GI.Gtk.Declarative.Container Methods fromWidget :: Container widget children event -> Widget event Source # | |
| a ~ b => FromWidget (Container a children) (Container b children) Source # | |
| Defined in GI.Gtk.Declarative.Container Methods fromWidget :: Container a children event -> Container b children event Source # | |
data Widget event where Source #
A Widget value wraps a Patchable and EventSource widget, providing
 a constrained equivalent of a Dynamic value. It is used to support
 heterogeneous containers of widgets, and to support equality
 checks on different types of widgets when calculating patches.
Constructors
| Widget :: (Typeable widget, Patchable widget, Functor widget, EventSource widget) => widget event -> Widget event | 
Instances
| Functor Widget Source # | |
| Patchable Widget Source # | 
 | 
| EventSource Widget Source # | |
| Defined in GI.Gtk.Declarative.Widget | |
| (Typeable parent, Typeable child, Patchable (parent child), Functor (parent child), EventSource (parent child)) => FromWidget (parent child) Widget Source # | |
| Defined in GI.Gtk.Declarative.Widget Methods fromWidget :: parent child event -> Widget event Source # | |
| (Typeable widget, Typeable children, Patchable (Container widget children), EventSource (Container widget children), Functor (Container widget children)) => FromWidget (Container widget children) Widget Source # | |
| Defined in GI.Gtk.Declarative.Container Methods fromWidget :: Container widget children event -> Widget event Source # | |
data SingleWidget widget event Source #
Declarative version of a leaf widget, i.e. a widget without any children.
Instances
| Functor (SingleWidget widget) Source # | |
| Defined in GI.Gtk.Declarative.SingleWidget Methods fmap :: (a -> b) -> SingleWidget widget a -> SingleWidget widget b # (<$) :: a -> SingleWidget widget b -> SingleWidget widget a # | |
| Patchable (SingleWidget widget) Source # | |
| Defined in GI.Gtk.Declarative.SingleWidget Methods create :: SingleWidget widget e -> IO SomeState Source # patch :: SomeState -> SingleWidget widget e1 -> SingleWidget widget e2 -> Patch Source # | |
| EventSource (SingleWidget widget) Source # | |
| Defined in GI.Gtk.Declarative.SingleWidget Methods subscribe :: SingleWidget widget event -> SomeState -> (event -> IO ()) -> IO Subscription Source # | |
Arguments
| :: (Typeable widget, Typeable event, Functor (Attribute widget), IsWidget widget, FromWidget (SingleWidget widget) target) | |
| => (ManagedPtr widget -> widget) | A widget constructor from the underlying gi-gtk library. | 
| -> Vector (Attribute widget event) | List of  | 
| -> target event | The target, whose type is decided by  | 
Construct a leaf widget, i.e. one without any children.
data BoxChildProperties Source #
Values used when packing child widgets into boxes.
Instances
| Default BoxChildProperties Source # | |
| Defined in GI.Gtk.Declarative.Container.Box Methods | |
Describes a child widget to be added with boxAppend to a Box.
Constructors
| BoxChild | |
| Fields 
 | |
Instances
| Functor BoxChild Source # | |
| Patchable BoxChild Source # | |
| EventSource BoxChild Source # | |
| Defined in GI.Gtk.Declarative.Container.Box | |
| IsContainer Box BoxChild Source # | |
| Defined in GI.Gtk.Declarative.Container.Box | |
| FromWidget widget Widget => FromWidget widget BoxChild Source # | Any widget that can be converted to a  | 
| Defined in GI.Gtk.Declarative.Widget.Conversions Methods fromWidget :: widget event -> BoxChild event Source # | |
| ToChildren Box Vector BoxChild Source # | |
| Defined in GI.Gtk.Declarative.Container.Box | |
defaultBoxChildProperties :: BoxChildProperties Source #
Defaults for BoxChildProperties. Use these and override
 specific fields.
data Container widget children event Source #
Declarative version of a container widget, i.e. a widget with zero
 or more child widgets. The type of children is parameterized, and differs
 across the supported container widgets, as some containers require specific
 types of child widgets. These type relations are decided by IsContainer,
 and instances can found in GI.Gtk.Declarative.Container.Patch.
Instances
| Functor (Container widget children) Source # | |
| (Patchable child, Typeable child, IsContainer container child) => Patchable (Container container (Children child)) Source # | |
| (Typeable child, EventSource child) => EventSource (Container widget (Children child)) Source # | |
| Defined in GI.Gtk.Declarative.Container | |
| (Typeable widget, Typeable children, Patchable (Container widget children), EventSource (Container widget children), Functor (Container widget children)) => FromWidget (Container widget children) Widget Source # | |
| Defined in GI.Gtk.Declarative.Container Methods fromWidget :: Container widget children event -> Widget event Source # | |
| a ~ b => FromWidget (Container a children) (Container b children) Source # | |
| Defined in GI.Gtk.Declarative.Container Methods fromWidget :: Container a children event -> Container b children event Source # | |
Arguments
| :: (Patchable (Container widget (Children child)), Typeable widget, Typeable child, Typeable event, Functor child, IsWidget widget, IsContainer widget, FromWidget (Container widget (Children child)) target, ToChildren widget parent child) | |
| => (ManagedPtr widget -> widget) | A container widget constructor from the underlying gi-gtk library. | 
| -> Vector (Attribute widget event) | |
| -> parent (child event) | The container's  | 
| -> target event | The target, whose type is decided by  | 
Construct a container widget, i.e. a widget with zero or more children.
data PaneProperties Source #
Values used when packing a pane into a Paned.
Constructors
| PaneProperties | |
Instances
| Default PaneProperties Source # | |
| Defined in GI.Gtk.Declarative.Container.Paned Methods | |
Describes a pane to be packed with
 'Gtk.panePack1'/'Gtk.panePack2' in a Paned.
Instances
| Functor Pane Source # | |
| Patchable Pane Source # | |
| EventSource Pane Source # | |
| Defined in GI.Gtk.Declarative.Container.Paned | |
| IsContainer Paned Pane Source # | |
| Defined in GI.Gtk.Declarative.Container.Paned | |
defaultPaneProperties :: PaneProperties Source #
Defaults for PaneProperties. Use these and override specific
 fields.
pane :: PaneProperties -> Widget event -> Pane event Source #
Construct a pane to be packed with
 'Gtk.panePack1'/'Gtk.panePack2' in a Paned.
paned :: Typeable event => Vector (Attribute Paned event) -> Pane event -> Pane event -> Widget event Source #
Construct a Paned based on attributes and two child Panes.
data Bin widget event Source #
Declarative version of a bin widget, i.e. a widget with exactly one child.
Instances
| ToChildren ListBox Vector (Bin ListBoxRow) Source # | |
| Defined in GI.Gtk.Declarative.Container.ListBox | |
| IsContainer ListBox (Bin ListBoxRow) Source # | |
| Defined in GI.Gtk.Declarative.Container.ListBox | |
| Functor (Bin widget) Source # | |
| IsBin parent => Patchable (Bin parent) Source # | |
| IsBin parent => EventSource (Bin parent) Source # | |
| Defined in GI.Gtk.Declarative.Bin | |
| a ~ b => FromWidget (Bin a) (Bin b) Source # | |
| Defined in GI.Gtk.Declarative.Bin Methods fromWidget :: Bin a event -> Bin b event Source # | |
Arguments
| :: (Patchable (Bin widget), Typeable widget, Typeable event, IsContainer widget, IsBin widget, IsWidget widget, FromWidget (Bin widget) target) | |
| => (ManagedPtr widget -> widget) | A bin widget constructor from the underlying gi-gtk library. | 
| -> Vector (Attribute widget event) | List of  | 
| -> Widget event | The bin's child widget | 
| -> target event | The target, whose type is decided by  | 
Construct a bin widget, i.e. a widget with exactly one child.
A menu item widget used for Menu children.
Instances
| Functor MenuItem Source # | |
| Patchable MenuItem Source # | |
| EventSource MenuItem Source # | |
| Defined in GI.Gtk.Declarative.Container.MenuItem | |
| IsContainer Menu MenuItem Source # | |
| Defined in GI.Gtk.Declarative.Container.MenuItem | |
| IsContainer MenuBar MenuItem Source # | |
| Defined in GI.Gtk.Declarative.Container.MenuItem | |
| IsContainer MenuShell MenuItem Source # | |
| Defined in GI.Gtk.Declarative.Container.MenuItem | |
| ToChildren Menu Vector MenuItem Source # | |
| Defined in GI.Gtk.Declarative.Container.MenuItem | |
| ToChildren MenuBar Vector MenuItem Source # | |
| Defined in GI.Gtk.Declarative.Container.MenuItem | |