(* #FORMAT FormatSlides *) ========================================== Introduction to Lablgtk ------------------------------------------ Adrien Nader ========================================== \Caml( (* let indent = [ tT " " ] *) (* let brown = RGB { red = 0.5; green = 0.5; blue = 0.5 } let cv c text = color c [ tT text ] *) let ocaml_code text = ListLabels.iter text ~f:(fun t -> newPar D.structure ~environment:verbEnv Complete.normal ragged_left (lang_OCaml t)) ;; ) \begin{slide} \begin{center} \bold{Introduction to Lablgtk (from its internals)} \end{center} \begin{center} Adrien Nader - OCaml Users in PariS \end{center} \end{slide} \begin{slide} \begin{center} \bold{Table Of Contents} \end{center} \TableOfContents \end{slide} == Introduction == \begin{slide} \Title{What is GTK+} \begin{itemize} \item Graphical toolkit available on many platforms \item C code with an object layer done through macros and runtime checks \item Objects have methods, signals, properties (with automatic getters, setters and \verb{notify::${property-name}} signals) \item Uses an event loop to trigger callbacks on the emission of signals \end{itemize} \end{slide} \begin{slide} \Title{Lablgtk} \begin{itemize} \item Bindings to GTK+-2 (and GTK+-1); GTK+-3 WIP \item and gtkGL, glade, gnomecanvas, gnomehtml, gnomeui, gtkspell, rsvg, gtksourceview(2) \item Provides a high-level OCaml-style API (e.g labels are used everywhere) \end{itemize} \end{slide} \begin{slide} \Title{Development} \begin{itemize} \item Project is hosted on the OCaml Forge with Git \item Development depends on demand \item API coverage increased only on-demand to avoid bit-rot of unused code \item Additions most usually simple to do: they're done quickly \item Join to work on what you want to change \end{itemize} \end{slide} \begin{slide} \Title{GTK+-3 Status} \begin{itemize} \item New GTK+ version which was released around 2 years ago \item Not that many big changes but a few annoying ones \item Pushes the use of gobject-introspection \item ... which is a good idea but has its issues: undocumented, pythonic, not meant for compiled bindings \end{itemize} \end{slide} == Lablgtk Primer == \begin{slide} \Title{Lablgtk Primer} \begin{center} \bold{Lablgtk Primer} \end{center} \end{slide} \begin{slide} \Title{A basic example} A window with a big text zone and a button. When the button is clicked, a modal window pops up and asks the user for text to put in the text zone below. Step-by-step in the slides that follow. \end{slide} \begin{slide} \Title{How to browse the API} \begin{itemize} \item ocamlfind ocamlbrowser -package lablgtk2 \item Merlin for emacs and vim, ocp-index, ... \item gtk.org for detailled explanation: lablgtk's API follows the C API very closely \end{itemize} \end{slide} \begin{slide} \Title{Handy additions} \begin{itemize} \item GToolbox has convenience functions: menus, dialog boxes, lists and trees, shortcuts, ... yours (* \item GUtil to help blend OCaml objects in GTK+ *) \item Extra libs like lablgtk-extras \item Integrate lwt/ocamlnet into glib's main loop \item Glade, either by loading the description at runtime or translating it to OCaml \end{itemize} \end{slide} \begin{slide} \Title{About the code in these slides} To run the codes, load ocamlfind, lablgtk2 and react in the toplevel: \Caml( ocaml_code [ " #use \"topfind\";;"; " #require \"lablgtk2.auto-init\";;"; " #require \"react\";;" ] ) \end{slide} \begin{slide} Initialize glib and GTK+ (requires a display). \Caml( ocaml_code [ ""; "let () ="; " GMain.init ();"; ""; ""; ""; ""; ""; ""; ""; ""; ""; ""; ] ) \end{slide} \begin{slide} Create a window with some default values. \Caml( ocaml_code [ ""; "let () ="; " GMain.init ();"; " let w = GWindow.window ~width:320 ~height:240 ~title:\"Mini demo\" () in"; ""; ""; ""; ""; ""; ""; ""; ""; ""; ] ) \end{slide} \begin{slide} Windows can only contain objects; insert a box which can hold many objects and arrange them. \Caml( ocaml_code [ ""; "let () ="; " GMain.init ();"; " let w = GWindow.window ~width:320 ~height:240 ~title:\"Mini demo\" () in"; " let vbox = GPack.vbox ~packing:w#add () in"; ""; ""; ""; ""; ""; ""; ""; ""; ] ) \end{slide} \begin{slide} Add a label in the box with default settings and make it take as much space as available. \Caml( ocaml_code [ ""; "let () ="; " GMain.init ();"; " let w = GWindow.window ~width:320 ~height:240 ~title:\"Mini demo\" () in"; " let vbox = GPack.vbox ~packing:w#add () in"; " let label = GMisc.label ~text:\"\" ~selectable:true ~line_wrap:true"; " ~justify:`CENTER ~packing:(vbox#pack ~expand:true) () in"; ""; ""; ""; ""; ""; ""; ] ) \end{slide} \begin{slide} Add a button at the end of the box. \Caml( ocaml_code [ ""; "let () ="; " GMain.init ();"; " let w = GWindow.window ~width:320 ~height:240 ~title:\"Mini demo\" () in"; " let vbox = GPack.vbox ~packing:w#add () in"; " let label = GMisc.label ~text:\"\" ~selectable:true ~line_wrap:true"; " ~justify:`CENTER ~packing:(vbox#pack ~expand:true) () in"; " let t = \"Change text\" in"; " let btn = GButton.button ~packing:vbox#pack ~label:t () in"; ""; ""; ""; ""; ] ) \end{slide} \begin{slide} Add a callback which is triggered upon clicking the button. \Caml( ocaml_code [ ""; "let () ="; " GMain.init ();"; " let w = GWindow.window ~width:320 ~height:240 ~title:\"Mini demo\" () in"; " let vbox = GPack.vbox ~packing:w#add () in"; " let label = GMisc.label ~text:\"\" ~selectable:true ~line_wrap:true"; " ~justify:`CENTER ~packing:(vbox#pack ~expand:true) () in"; " let t = \"Change text\" in"; " let btn = GButton.button ~packing:vbox#pack ~label:t () in"; " btn#connect#clicked (fun () ->"; ""; ""; ""; ] ) \end{slide} \begin{slide} The callback spawns a toolbox asking for text which will replace the text in our label above. \Caml( ocaml_code [ ""; "let () ="; " GMain.init ();"; " let w = GWindow.window ~width:320 ~height:240 ~title:\"Mini demo\" () in"; " let vbox = GPack.vbox ~packing:w#add () in"; " let label = GMisc.label ~text:\"\" ~selectable:true ~line_wrap:true"; " ~justify:`CENTER ~packing:(vbox#pack ~expand:true) () in"; " let t = \"Change text\" in"; " let btn = GButton.button ~packing:vbox#pack ~label:t () in"; " btn#connect#clicked (fun () -> match GToolbox.input_text ~title:t t with"; " | Some text -> label#set_text text | None -> ());"; ""; ""; ] ) \end{slide} \begin{slide} Show the window. \Caml( ocaml_code [ ""; "let () ="; " GMain.init ();"; " let w = GWindow.window ~width:320 ~height:240 ~title:\"Mini demo\" () in"; " let vbox = GPack.vbox ~packing:w#add () in"; " let label = GMisc.label ~text:\"\" ~selectable:true ~line_wrap:true"; " ~justify:`CENTER ~packing:(vbox#pack ~expand:true) () in"; " let t = \"Change text\" in"; " let btn = GButton.button ~packing:vbox#pack ~label:t () in"; " btn#connect#clicked (fun () -> match GToolbox.input_text ~title:t t with"; " | Some text -> label#set_text text | None -> ());"; " w#show ();"; ""; ] ) \end{slide} \begin{slide} Start the mainloop. \Caml( ocaml_code [ ""; "let () ="; " GMain.init ();"; " let w = GWindow.window ~width:320 ~height:240 ~title:\"Mini demo\" () in"; " let vbox = GPack.vbox ~packing:w#add () in"; " let label = GMisc.label ~text:\"\" ~selectable:true ~line_wrap:true"; " ~justify:`CENTER ~packing:(vbox#pack ~expand:true) () in"; " let t = \"Change text\" in"; " let btn = GButton.button ~packing:vbox#pack ~label:t () in"; " btn#connect#clicked (fun () -> match GToolbox.input_text ~title:t t with"; " | Some text -> label#set_text text | None -> ());"; " w#show ();"; " GMain.main ()"; ] ) \end{slide} \begin{slide} \Title{Recap: most common constructs} \begin{itemize} \item new widgets: \verb{GWindow.window}, \verb{GPack.vbox} \item properties: \begin{itemize} \item set when creating the widget: \verb{GWidget.widget ~property:value ()} \item set later on: \verb{widget#set_property value} \item get : \verb{widget#property} \end{itemize} \item register callbacks: \Caml( ocaml_code [ "- #connect#clicked (fun () -> eprintf \"Clicked!\")"; "- #connect#notify_${property} ~callback:()"; ] ) \item add items to containers: \begin{itemize} \item When creating the widget, \verb{#pack} if available, \verb{#add} otherwise: \Caml( ocaml_code [ "- GButton.button ~text:\"42\" ~packing:(box#pack ~expand:false) ()"; "- GButton.button ~text:\"42\" ~packing:win#add ()"; ] ) \item Or afterwards: \verb{#coerce} the object to the base \verb{widget} type: \Caml( ocaml_code [ " box#pack button#coerce"; ] ) \end{itemize} \end{itemize} \end{slide} == Functional Reactive Programming for GUIs == \begin{slide} \Title{Functional Reactive Programming for GUIs} \begin{center} \bold{Functional Reactive Programming for GUIs} \end{center} \end{slide} \begin{slide} === Functional vs. imperative mismatch === \Title{Functional vs. imperative mismatch} \begin{itemize} \item Callbacks for signals usually don't return a value: \Caml( ocaml_code [ " (GButton.button ())#connect#clicked;;"; " - : callback:(unit -> unit) -> GtkSignal.id = "; ] ) \item We have to use imperative code to count the number of clicks on a button: \Caml( ocaml_code [ " type state = { count : int } ;;"; " let s = ref { count = 0 } ;;"; " let () ="; " let w = GWindow.window ~show:true () in"; " let b = GButton.button ~packing:w#add () in"; " let callback () ="; " s := { !s with count = !s.count + 1 } in"; " b#connect#clicked ~callback;"; " GMain.main ()"; ] ) \end{itemize} \end{slide} \begin{slide} \Title{Functional vs. imperative mismatch (cont.)} \begin{itemize} \item But OCaml is multi-paradigm! \item Impossible to be both imperative and functional for the program architecture. \item Once \verb{type state} becomes more complicated, initialization becomes \Caml( ocaml_code [ " let state = ref (Obj.magic 0)"; ] ) or \Caml( ocaml_code [ " type state1 = state Lazy.t ;;"; " let state = ref (lazy { init with values you hope to be \"ready\" })"; ] ) \item Having laziness by default like in Haskell probably helps but only slightly. \end{itemize} \end{slide} \begin{slide} \Title{Functional vs. imperative mismatch - some FRP} \begin{itemize} \item We want functional updates: callbacks would be \verb{(state -> state)}: \Caml( ocaml_code [ " ~callback:(fun state0 -> { state0 with count = state0.count + 1 })"; ] ) And no init to \verb{Obj.magic} or using \verb{lazy}. \item FRP can help (and it's simple) \end{itemize} \end{slide} \begin{slide} \Title{Functional vs. imperative mismatch - some FRP} A trivial example which counts the number of clicks on a button. \Caml( ocaml_code [ " type state = { count : int }"; ""; " let event, event_send = React.E.create ()"; ""; " let state_machine (s : state) event ="; " Printf.printf \"Count was %d.\n%!\" s.count;"; " match event with"; " | `Incr -> { s with count = s.count + 1 }"; " | `Decr -> { s with count = s.count - 1 }"; ""; " let () ="; " let w = GWindow.window ~show:true () in"; " let b = GButton.button ~packing:w#add () in"; " b#connect#clicked (fun () -> event_send `Incr);"; " let _state = React.E.fold state_machine { count = 0 } event in"; " GMain.main ()"; ] ) \end{slide} (* \begin{slide} \Title{Quadratic growth of relations} \begin{itemize} \item Problem: only "enable" a set of buttons when a checkbox is ticked. \item Typical approach: add a callback on the checkbox. \item Issue: after a while there can be lots of such callbacks: could be $n*(n-1)/2$. \item Or sometimes too few, or not the right ones. \item A central function like the one above reduces this to $O(n)$ and should provide exhaustive coverage. \end{itemize} \end{slide} *) (* \begin{slide} \Title{Tree Views and List Views} \begin{itemize} \item API is really difficult to use; issue comes from GTK+ \item Model-View-Controller with imperative models \item Model can be implemented in OCaml \item but the API really is difficult to use \item An additional wrapper library would help \end{itemize} \end{slide} *) == Bindings creation == \begin{slide} \Title{Bindings creation} \begin{center} \bold{Bindings creation} \end{center} \end{slide} \begin{slide} \Title{Bindings creation} \begin{itemize} \item Several layers: C stubs, object layer, signals, properties... \item Mostly generated \item Some hand-written code, especially for the higher-level layers (convenience functions) \end{itemize} \end{slide} \begin{slide} \Title{Stubs and low-level API - 1} \begin{itemize} \item C macros: \Caml( ocaml_code [ " ML_1 (gtk_window_new, Window_type_val, Val_GtkWidget_window)" ] ) \item A DSL, varcc:\cr \Caml( ocaml_code [ " type arrow_type = \"GTK_ARROW_\""; " [ `UP | `DOWN | `LEFT | `RIGHT ]" ] ) \item Another DSL, propcc:\cr \Caml( ocaml_code [ " class Window set wrap : Bin {"; " \"title\" gchararray : Read / Write"; " method resize : \"width:int -> height:int -> unit\""; " signal activate_default"; " }"; ] ) \end{itemize} \end{slide} \begin{slide} \Title{Stubs and low-level API - 2} \begin{itemize} \item gtkWindow.ml: \Caml( ocaml_code [ " module Window = struct"; " include Window (* from propcc's output. *)"; " external get_wmclass_name : [> `window ] obj -> string"; " = \"ml_gtk_window_get_wmclass_name\""; " (* From before propcc *)"; " end"; ] ) \item Inheritance is handled through polymorphic variants: \Caml( ocaml_code [ " type text_view = [ container | `textview ]" ] ) Functions then require values of type \verb{[> `textview] Gtk.obj}. \end{itemize} \end{slide} \begin{slide} \Title{Object API} Mostly boiler-plate apart from the convenience functions: \begin{itemize} \item From gWindow.ml: \Caml( ocaml_code [ " class window_skel obj = object"; " inherit window_props (* comes from propcc in ogtkBaseProps.ml *)"; (* " method as_window = (obj :> Gtk.window obj)"; *) " method resize = Window.resize obj"; " end"; ] ;; ocaml_code [ " [...]" ] ;; (* ocaml_code [ " class window obj = object"; " inherit window_skel (obj : [> Gtk.window] obj)"; " method connect = new container_signals_impl obj"; " end"; ] ;; *) ocaml_code [ " let window ?kind ="; " make_window [] ~create:(fun p -> new window (Window.create ?kind p))"; ] ;; ) \end{itemize} \end{slide} \begin{slide} \Title{Signals} Again, mostly boiler-plate code: \begin{itemize} \item From ogtkBaseProps.ml (generated by propcc): \Caml( ocaml_code [ " class virtual container_sigs = object (self)"; " method add = self#connect"; " { Container.S.add with"; " marshaller = fun f -> marshal1 conv_widget \"GtkContainer::add\" f }"; " end"; ] ) \item From gObj.ml: \Caml( ocaml_code [ " class ['a] gobject_signals obj = object"; " method private connect ="; " fun sgn ~callback -> GtkSignal.connect obj ~sgn ~callback"; " end"; ] ) \end{itemize} \end{slide} (* \begin{slide} \Title{API Principles} Schéma des différents modules et de leurs liens. \end{slide} *) (* == Offtopic - Patoline == \begin{slide} \Title{Offtopic - A few words on Patoline} \begin{center} \bold{Offtopic - A few words on Patoline} \end{center} \end{slide} \begin{slide} \Title{Patoline} \begin{itemize} \item New layout engine in OCaml; same job as TeX \item Used to create this document \item Works well but doesn't have the many packages of LateX \item Waaaaaaaay faster \item Unexpectedly takes advantage of improvements to OCaml: ### File "lablgtk_oups_intro.txp", line 125, characters 248-251: Error: Unbound value ver Did you mean vec or verb? ### \end{itemize} \end{slide} *) == Links == \begin{slide} \Title{Links} \begin{itemize} \item lablgtk sources: README (must-read!), doc/ \item Dawid Toton's description on how to bind GtkPrint (need to find it again) \item cowboy(-glib): http://git.ocamlcore.org/cgi-bin/gitweb.cgi?p=cowboy/cowboy.git \item lablgtk-extras: http://gtk-extras.forge.ocamlcore.org/ \item lablgtk-react: http://git.ocamlcore.org/cgi-bin/gitweb.cgi?p=lablgtk-react/lablgtk-react.git \item \verb{#self}: will probably appear as part of the documentation \end{itemize} \end{slide} \begin{slide} \begin{center} \bold{Questions?} (and Patoline is nice) \end{center} \end{slide}