gi-gtk-declarative-0.7.0: Declarative GTK+ programming in Haskell
Safe HaskellNone
LanguageHaskell2010

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

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

Instances details
Functor (EventHandler gtkEventHandler widget purity) Source # 
Instance details

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 #

type ClassSet = HashSet Text Source #

A set of CSS classes.

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 AttrLabelProxy is parameterized by attr, which represents the GTK-defined attribute name. The underlying GI object needs to support the construct, get, and set operations for the given attribute.

Classes :: IsWidget widget => ClassSet -> Attribute widget event

Defines a set of CSS classes for the underlying widget's style context. Use the classes function instead of this constructor directly.

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 on function, instead of this constructor directly.

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 on function, instead of this constructor directly.

Instances

Instances details
Functor (Attribute widget) Source #

Attributes have a Functor instance that maps events in all event handler.

Instance details

Defined in GI.Gtk.Declarative.Attributes

Methods

fmap :: (a -> b) -> Attribute widget a -> Attribute widget b #

(<$) :: a -> Attribute widget b -> Attribute widget a #

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.

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

Instances details
Patchable Widget Source #

Widget is itself patchable, by delegating to the underlying widget instances.

Instance details

Defined in GI.Gtk.Declarative.Widget

Patchable GridChild Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Grid

Patchable BoxChild Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Box

Patchable Pane Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Paned

Methods

create :: Pane e -> IO SomeState Source #

patch :: SomeState -> Pane e1 -> Pane e2 -> Patch Source #

Patchable MenuItem Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.MenuItem

Patchable (SingleWidget widget) Source # 
Instance details

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 # 
Instance details

Defined in GI.Gtk.Declarative.Bin

Methods

create :: Bin parent e -> IO SomeState Source #

patch :: SomeState -> Bin parent e1 -> Bin parent e2 -> Patch Source #

(Patchable child, Typeable child, IsContainer container child) => Patchable (Container container (Children child)) Source # 
Instance details

Defined in GI.Gtk.Declarative.Container

Methods

create :: Container container (Children child) e -> IO SomeState Source #

patch :: SomeState -> Container container (Children child) e1 -> Container container (Children child) e2 -> Patch Source #

(Typeable widget, Typeable internalState, IsWidget widget) => Patchable (CustomWidget widget params internalState) Source # 
Instance details

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 #

data 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 IO action to apply to a Widget to make it reflect an updated declarative widget. The action to apply is calculated from the difference between the old and the new declarative widget.

Replace (IO SomeState)

Replace the current Widget by the widget returned by the IO action.

Keep

Do nothing, i.e. keep the Widget as it is.

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 internalState as 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

Instances details
Functor (CustomWidget widget params internalState) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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

Instances details
FromWidget widget Widget => FromWidget widget BoxChild Source #

Any widget that can be converted to a Widget can be wrapped as a BoxChild with the default properties.

Instance details

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 # 
Instance details

Defined in GI.Gtk.Declarative.Widget

Methods

fromWidget :: parent child event -> Widget event Source #

a ~ b => FromWidget (Bin a) (Bin b) Source # 
Instance details

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)) => FromWidget (Container widget children) Widget Source # 
Instance details

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 # 
Instance details

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

Instances details
Functor Widget Source # 
Instance details

Defined in GI.Gtk.Declarative.Widget

Methods

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

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

Patchable Widget Source #

Widget is itself patchable, by delegating to the underlying widget instances.

Instance details

Defined in GI.Gtk.Declarative.Widget

EventSource Widget Source # 
Instance details

Defined in GI.Gtk.Declarative.Widget

Methods

subscribe :: Widget event -> SomeState -> (event -> IO ()) -> IO Subscription Source #

IsContainer Notebook Widget Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Notebook

Methods

appendChild :: Notebook -> Widget event -> Widget0 -> IO () Source #

replaceChild :: Notebook -> Widget event -> Int32 -> Widget0 -> Widget0 -> IO () Source #

ToChildren Notebook Vector Widget Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Notebook

(Typeable parent, Typeable child, Patchable (parent child), Functor (parent child), EventSource (parent child)) => FromWidget (parent child) Widget Source # 
Instance details

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)) => FromWidget (Container widget children) Widget Source # 
Instance details

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

Instances details
Functor (SingleWidget widget) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in GI.Gtk.Declarative.SingleWidget

Methods

subscribe :: SingleWidget widget event -> SomeState -> (event -> IO ()) -> IO Subscription Source #

widget Source #

Arguments

:: (Typeable 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 Attributes.

-> target event

The target, whose type is decided by FromWidget.

Construct a leaf widget, i.e. one without any children.

data BoxChild event Source #

Describes a child widget to be added with boxAppend to a Box.

Constructors

BoxChild 

Instances

Instances details
Functor BoxChild Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Box

Methods

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

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

Patchable BoxChild Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Box

EventSource BoxChild Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Box

Methods

subscribe :: BoxChild event -> SomeState -> (event -> IO ()) -> IO Subscription Source #

IsContainer Box BoxChild Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Box

Methods

appendChild :: Box -> BoxChild event -> Widget -> IO () Source #

replaceChild :: Box -> BoxChild event -> Int32 -> Widget -> Widget -> IO () Source #

FromWidget widget Widget => FromWidget widget BoxChild Source #

Any widget that can be converted to a Widget can be wrapped as a BoxChild with the default properties.

Instance details

Defined in GI.Gtk.Declarative.Widget.Conversions

Methods

fromWidget :: widget event -> BoxChild event Source #

ToChildren Box Vector BoxChild Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Box

Methods

toChildren :: (ManagedPtr Box -> Box) -> Vector (BoxChild event) -> Children BoxChild event Source #

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

Instances details
Functor (Container widget children) Source # 
Instance details

Defined in GI.Gtk.Declarative.Container

Methods

fmap :: (a -> b) -> Container widget children a -> Container widget children b #

(<$) :: a -> Container widget children b -> Container widget children a #

(Patchable child, Typeable child, IsContainer container child) => Patchable (Container container (Children child)) Source # 
Instance details

Defined in GI.Gtk.Declarative.Container

Methods

create :: Container container (Children child) e -> IO SomeState Source #

patch :: SomeState -> Container container (Children child) e1 -> Container container (Children child) e2 -> Patch Source #

EventSource child => EventSource (Container widget (Children child)) Source # 
Instance details

Defined in GI.Gtk.Declarative.Container

Methods

subscribe :: Container widget (Children child) event -> SomeState -> (event -> IO ()) -> IO Subscription Source #

(Typeable widget, Typeable children, Patchable (Container widget children), EventSource (Container widget children)) => FromWidget (Container widget children) Widget Source # 
Instance details

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 # 
Instance details

Defined in GI.Gtk.Declarative.Container

Methods

fromWidget :: Container a children event -> Container b children event Source #

container Source #

Arguments

:: (Typeable widget, 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)

Attributes.

-> parent (child event)

The container's child widgets, in a MarkupOf builder.

-> target event

The target, whose type is decided by FromWidget.

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 

Fields

Instances

Instances details
Default PaneProperties Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Paned

Methods

def :: PaneProperties #

data Pane event Source #

Describes a pane to be packed with panePack1/panePack2 in a Paned.

Instances

Instances details
Functor Pane Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Paned

Methods

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

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

Patchable Pane Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Paned

Methods

create :: Pane e -> IO SomeState Source #

patch :: SomeState -> Pane e1 -> Pane e2 -> Patch Source #

EventSource Pane Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Paned

Methods

subscribe :: Pane event -> SomeState -> (event -> IO ()) -> IO Subscription Source #

IsContainer Paned Pane Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.Paned

Methods

appendChild :: Paned -> Pane event -> Widget -> IO () Source #

replaceChild :: Paned -> Pane event -> Int32 -> Widget -> Widget -> IO () Source #

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 panePack1/panePack2 in a Paned.

paned :: Vector (Attribute Paned event) -> Pane event -> Pane event -> Widget event Source #

Construct a Paned based on attributes and two child Panes.

data Page event Source #

Describes a page to be added to a Notebook

page :: Text -> Widget event -> Page event Source #

Create a page with a textual label and an arbitrary content widget.

pageWithTab :: Widget event -> Widget event -> Page event Source #

Create a page with arbitrary widgets for both label and content.

notebook :: Vector (Attribute Notebook event) -> Vector (Page event) -> Widget event Source #

Create a Notebook by combining multiple pages.

data Bin widget event Source #

Declarative version of a bin widget, i.e. a widget with exactly one child.

Instances

Instances details
ToChildren ListBox Vector (Bin ListBoxRow) Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.ListBox

IsContainer ListBox (Bin ListBoxRow) Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.ListBox

Methods

appendChild :: ListBox -> Bin ListBoxRow event -> Widget -> IO () Source #

replaceChild :: ListBox -> Bin ListBoxRow event -> Int32 -> Widget -> Widget -> IO () Source #

Functor (Bin widget) Source # 
Instance details

Defined in GI.Gtk.Declarative.Bin

Methods

fmap :: (a -> b) -> Bin widget a -> Bin widget b #

(<$) :: a -> Bin widget b -> Bin widget a #

IsBin parent => Patchable (Bin parent) Source # 
Instance details

Defined in GI.Gtk.Declarative.Bin

Methods

create :: Bin parent e -> IO SomeState Source #

patch :: SomeState -> Bin parent e1 -> Bin parent e2 -> Patch Source #

IsBin parent => EventSource (Bin parent) Source # 
Instance details

Defined in GI.Gtk.Declarative.Bin

Methods

subscribe :: Bin parent event -> SomeState -> (event -> IO ()) -> IO Subscription Source #

a ~ b => FromWidget (Bin a) (Bin b) Source # 
Instance details

Defined in GI.Gtk.Declarative.Bin

Methods

fromWidget :: Bin a event -> Bin b event Source #

bin Source #

Arguments

:: (Typeable widget, 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 Attributes.

-> Widget event

The bin's child widget

-> target event

The target, whose type is decided by FromWidget.

Construct a bin widget, i.e. a widget with exactly one child.

data MenuItem event Source #

A menu item widget used for Menu children.

Instances

Instances details
Functor MenuItem Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.MenuItem

Methods

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

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

Patchable MenuItem Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.MenuItem

EventSource MenuItem Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.MenuItem

Methods

subscribe :: MenuItem event -> SomeState -> (event -> IO ()) -> IO Subscription Source #

IsContainer MenuBar MenuItem Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.MenuItem

Methods

appendChild :: MenuBar -> MenuItem event -> Widget -> IO () Source #

replaceChild :: MenuBar -> MenuItem event -> Int32 -> Widget -> Widget -> IO () Source #

IsContainer MenuShell MenuItem Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.MenuItem

Methods

appendChild :: MenuShell -> MenuItem event -> Widget -> IO () Source #

replaceChild :: MenuShell -> MenuItem event -> Int32 -> Widget -> Widget -> IO () Source #

IsContainer Menu MenuItem Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.MenuItem

Methods

appendChild :: Menu -> MenuItem event -> Widget -> IO () Source #

replaceChild :: Menu -> MenuItem event -> Int32 -> Widget -> Widget -> IO () Source #

ToChildren MenuBar Vector MenuItem Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.MenuItem

ToChildren Menu Vector MenuItem Source # 
Instance details

Defined in GI.Gtk.Declarative.Container.MenuItem

Methods

toChildren :: (ManagedPtr Menu -> Menu) -> Vector (MenuItem event) -> Children MenuItem event Source #

menuItem :: (IsMenuItem item, Typeable item, IsContainer item, IsBin item, IsWidget item) => (ManagedPtr item -> item) -> Vector (Attribute item event) -> Widget event -> MenuItem event Source #

Construct a single menu item for a Menu.

subMenu :: Text -> Vector (MenuItem event) -> MenuItem event Source #

Construct a sub menu for a Menu, wit a text label and the child menu items.