Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- class FromWidget widget event target | target -> event where
- type Markup event a = MarkupOf Widget event a
- data MarkupOf widget event a
- data Widget event where
- runMarkup :: MarkupOf widget event () -> Vector (widget event)
- single :: widget event -> MarkupOf widget event ()
- multiple :: Vector (widget event) -> MarkupOf widget event ()
- data BoxChild event = BoxChild {}
- boxChild :: Bool -> Bool -> Word32 -> Widget event -> MarkupOf BoxChild event ()
- data SingleWidget widget event
- widget :: (Typeable widget, Typeable event, Functor (Attribute widget), IsWidget widget, FromWidget (SingleWidget widget) event target) => (ManagedPtr widget -> widget) -> Vector (Attribute widget event) -> target
- data Bin widget child event
- bin :: (Patchable (Bin widget child), Typeable widget, Typeable child, Typeable event, Functor child, IsContainer widget, IsBin widget, IsWidget widget, FromWidget (Bin widget child) event target) => (ManagedPtr widget -> widget) -> Vector (Attribute widget event) -> child event -> target
- 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)) event target) => (ManagedPtr widget -> widget) -> Vector (Attribute widget event) -> MarkupOf child event () -> target
- data MenuItem event
- menuItem :: (IsMenuItem item, Typeable event, BinChild item Widget, Typeable item, IsContainer item, IsBin item, IsWidget item) => (ManagedPtr item -> item) -> Vector (Attribute item event) -> Widget event -> MarkupOf MenuItem event ()
- subMenu :: Typeable event => Text -> MarkupOf MenuItem event () -> MarkupOf 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.
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 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.
(:=) :: (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.
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 MenuItem Source # | |
Patchable (SingleWidget widget) Source # | |
Defined in GI.Gtk.Declarative.SingleWidget create :: SingleWidget widget e -> IO SomeState Source # patch :: SomeState -> SingleWidget widget e1 -> SingleWidget widget e2 -> Patch Source # | |
(BinChild parent child, Patchable child) => Patchable (Bin parent child) Source # | |
(Patchable child, Typeable child, IsContainer container child) => Patchable (Container container (Children child)) Source # | |
A possible action to take on an existing Widget
, decided by the
patch
method when comparing declarative widgets.
Modify (IO SomeState) | An |
Replace (IO SomeState) | Replace the current |
Keep | Do nothing, i.e. keep the |
class FromWidget widget event target | target -> event 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 MarkupOf
, depending on the context in which it's
used.
fromWidget :: (Typeable widget, Typeable event) => widget event -> target Source #
Instances
FromWidget Widget event (Widget event) Source # | |
Defined in GI.Gtk.Declarative.Markup fromWidget :: Widget event -> Widget event Source # | |
(Typeable widget, Functor (SingleWidget widget)) => FromWidget (SingleWidget widget) event (Widget event) Source # | |
Defined in GI.Gtk.Declarative.SingleWidget fromWidget :: SingleWidget widget event -> Widget event Source # | |
(Typeable widget, Functor (SingleWidget widget)) => FromWidget (SingleWidget widget) event (Markup event ()) Source # | |
Defined in GI.Gtk.Declarative.SingleWidget fromWidget :: SingleWidget widget event -> Markup event () Source # | |
FromWidget (SingleWidget widget) event (MarkupOf (SingleWidget widget) event ()) Source # | |
Defined in GI.Gtk.Declarative.SingleWidget fromWidget :: SingleWidget widget event -> MarkupOf (SingleWidget widget) event () Source # | |
(BinChild widget child, Typeable widget, Patchable child, EventSource child, Functor (Bin widget child)) => FromWidget (Bin widget child) event (Widget event) Source # | |
Defined in GI.Gtk.Declarative.Bin fromWidget :: Bin widget 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) event (Widget event) Source # | |
Defined in GI.Gtk.Declarative.Container fromWidget :: Container widget children event -> Widget event Source # | |
(BinChild widget child, a ~ (), Typeable widget, Patchable child, EventSource child, Functor (Bin widget child)) => FromWidget (Bin widget child) event (Markup event a) Source # | |
Defined in GI.Gtk.Declarative.Bin fromWidget :: Bin widget child event -> Markup event a Source # | |
(a ~ (), Typeable widget, Typeable children, Patchable (Container widget children), EventSource (Container widget children), Functor (Container widget children)) => FromWidget (Container widget children) event (Markup event a) Source # | |
Defined in GI.Gtk.Declarative.Container fromWidget :: Container widget children event -> Markup event a Source # | |
FromWidget (Bin widget child) event (Bin widget child event) Source # | |
Defined in GI.Gtk.Declarative.Bin fromWidget :: Bin widget child event -> Bin widget child event Source # | |
a ~ () => FromWidget (Bin widget child) event (MarkupOf (Bin widget child) event a) Source # | |
Defined in GI.Gtk.Declarative.Bin | |
FromWidget (Container widget children) event (Container widget children event) Source # | |
Defined in GI.Gtk.Declarative.Container fromWidget :: Container widget children event -> Container widget children event Source # | |
a ~ () => FromWidget (Container widget children) event (MarkupOf (Container widget children) event a) Source # | |
Defined in GI.Gtk.Declarative.Container |
type Markup event a = MarkupOf Widget event a Source #
Handy type alias for the common case of markup containing Widget
s.
data MarkupOf widget event a Source #
The declarative markup builder, primarily for using its Monad
instance
and do notation to construct adjacent widgets in containers.
It is parameterized with widget
and event
, such that containers can
restrict the type of their children to other types than Widget
.
Note that the return type, a
, is not used in this library. It's a more a
technical necessity to have the Monad
instance. You can still use it if
you need to return a value from a markup function, though.
Instances
(Typeable widget, Functor (SingleWidget widget)) => FromWidget (SingleWidget widget) event (Markup event ()) Source # | |
Defined in GI.Gtk.Declarative.SingleWidget fromWidget :: SingleWidget widget event -> Markup event () Source # | |
FromWidget (SingleWidget widget) event (MarkupOf (SingleWidget widget) event ()) Source # | |
Defined in GI.Gtk.Declarative.SingleWidget fromWidget :: SingleWidget widget event -> MarkupOf (SingleWidget widget) event () Source # | |
Monad (MarkupOf widget event) Source # | |
Defined in GI.Gtk.Declarative.Markup | |
Functor (MarkupOf widget event) Source # | |
Applicative (MarkupOf widget event) Source # | |
Defined in GI.Gtk.Declarative.Markup pure :: a -> MarkupOf widget event a # (<*>) :: MarkupOf widget event (a -> b) -> MarkupOf widget event a -> MarkupOf widget event b # liftA2 :: (a -> b -> c) -> MarkupOf widget event a -> MarkupOf widget event b -> MarkupOf widget event c # (*>) :: MarkupOf widget event a -> MarkupOf widget event b -> MarkupOf widget event b # (<*) :: MarkupOf widget event a -> MarkupOf widget event b -> MarkupOf widget event a # | |
(BinChild widget child, a ~ (), Typeable widget, Patchable child, EventSource child, Functor (Bin widget child)) => FromWidget (Bin widget child) event (Markup event a) Source # | |
Defined in GI.Gtk.Declarative.Bin fromWidget :: Bin widget child event -> Markup event a Source # | |
(a ~ (), Typeable widget, Typeable children, Patchable (Container widget children), EventSource (Container widget children), Functor (Container widget children)) => FromWidget (Container widget children) event (Markup event a) Source # | |
Defined in GI.Gtk.Declarative.Container fromWidget :: Container widget children event -> Markup event a Source # | |
a ~ () => FromWidget (Bin widget child) event (MarkupOf (Bin widget child) event a) Source # | |
Defined in GI.Gtk.Declarative.Bin | |
a ~ () => FromWidget (Container widget children) event (MarkupOf (Container widget children) event a) Source # | |
Defined in GI.Gtk.Declarative.Container |
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.
Widget :: (Typeable widget, Patchable widget, Functor widget, EventSource widget) => widget event -> Widget event |
Instances
runMarkup :: MarkupOf widget event () -> Vector (widget event) Source #
Run a MarkupOf
builder and get its widgets.
multiple :: Vector (widget event) -> MarkupOf widget event () Source #
Construct markup from multiple widgets.
Described a child widget to be added with boxAppend
to a Box
.
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.Patch |
boxChild :: Bool -> Bool -> Word32 -> Widget event -> MarkupOf BoxChild event () Source #
Construct a box child with the given boxAppend
parameters.
data SingleWidget widget event Source #
Declarative version of a leaf widget, i.e. a widget without any children.
Instances
:: (Typeable widget, Typeable event, Functor (Attribute widget), IsWidget widget, FromWidget (SingleWidget widget) event target) | |
=> (ManagedPtr widget -> widget) | A widget constructor from the underlying gi-gtk library. |
-> Vector (Attribute widget event) | List of |
-> target | The target, whose type is decided by |
Construct a leaf widget, i.e. one without any children.
data Bin widget child event Source #
Declarative version of a bin widget, i.e. a widget with exactly one child.
Instances
IsContainer ListBox (Bin ListBoxRow Widget) Source # | |
Defined in GI.Gtk.Declarative.Container.Patch | |
Functor (Bin widget child) Source # | |
(BinChild parent child, Patchable child) => Patchable (Bin parent child) Source # | |
(BinChild parent child, EventSource child) => EventSource (Bin parent child) Source # | |
Defined in GI.Gtk.Declarative.Bin | |
(BinChild widget child, Typeable widget, Patchable child, EventSource child, Functor (Bin widget child)) => FromWidget (Bin widget child) event (Widget event) Source # | |
Defined in GI.Gtk.Declarative.Bin fromWidget :: Bin widget child event -> Widget event Source # | |
(BinChild widget child, a ~ (), Typeable widget, Patchable child, EventSource child, Functor (Bin widget child)) => FromWidget (Bin widget child) event (Markup event a) Source # | |
Defined in GI.Gtk.Declarative.Bin fromWidget :: Bin widget child event -> Markup event a Source # | |
FromWidget (Bin widget child) event (Bin widget child event) Source # | |
Defined in GI.Gtk.Declarative.Bin fromWidget :: Bin widget child event -> Bin widget child event Source # | |
a ~ () => FromWidget (Bin widget child) event (MarkupOf (Bin widget child) event a) Source # | |
Defined in GI.Gtk.Declarative.Bin |
:: (Patchable (Bin widget child), Typeable widget, Typeable child, Typeable event, Functor child, IsContainer widget, IsBin widget, IsWidget widget, FromWidget (Bin widget child) event target) | |
=> (ManagedPtr widget -> widget) | A bin widget constructor from the underlying gi-gtk library. |
-> Vector (Attribute widget event) | List of |
-> child event | The bin's child widget, whose type is decided by the |
-> target | The target, whose type is decided by |
Construct a bin widget, i.e. a widget with exactly one child.
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) event (Widget event) Source # | |
Defined in GI.Gtk.Declarative.Container fromWidget :: Container widget children event -> Widget event Source # | |
(a ~ (), Typeable widget, Typeable children, Patchable (Container widget children), EventSource (Container widget children), Functor (Container widget children)) => FromWidget (Container widget children) event (Markup event a) Source # | |
Defined in GI.Gtk.Declarative.Container fromWidget :: Container widget children event -> Markup event a Source # | |
FromWidget (Container widget children) event (Container widget children event) Source # | |
Defined in GI.Gtk.Declarative.Container fromWidget :: Container widget children event -> Container widget children event Source # | |
a ~ () => FromWidget (Container widget children) event (MarkupOf (Container widget children) event a) Source # | |
Defined in GI.Gtk.Declarative.Container |
:: (Patchable (Container widget (Children child)), Typeable widget, Typeable child, Typeable event, Functor child, IsWidget widget, IsContainer widget, FromWidget (Container widget (Children child)) event target) | |
=> (ManagedPtr widget -> widget) | A container widget constructor from the underlying gi-gtk library. |
-> Vector (Attribute widget event) | List of |
-> MarkupOf child event () | The container's |
-> target | The target, whose type is decided by |
Construct a container widget, i.e. a widget with zero or more 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 |