GtkAda Contributions
version 3.32

Dmitry A. Kazakov             and                       Maxim Reznik         
(mailbox@dmitry-kazakov.de)    
[Home]    

This library is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This library is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this library; if not, write to the Free Software Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.

As a special exception, if other files instantiate generics from this unit, or you link this unit with other files to produce an executable, this unit does not by itself cause the resulting executable to be covered by the GNU General Public License. This exception does not however invalidate any other reasons why the executable file might be covered by the GNU Public License.


      ARM Intel
Download GtkAda Contributions Platform:   64- 32- 64- 32bit
Fedora packages fedora   precompiled and packaged using RPM     [Download page] [Download page] [Download page] [Download page]
CentOS packages CentOS   precompiled and packaged using RPM         [Download page] [Download page]
Debian packages Debian   precompiled and packaged for dpkg   [Download page] [Download page] [Download page] [Download page]
Ubuntu packages Ubuntu      precompiled and packaged for dpkg   [Download page] [Download page] [Download page] [Download page]
Source distribution (any platform)   gtkada_contributions_3_32.tgz (tar + gzip, Windows users may use WinZip)   [Download]

Download XPM to GtkAda converter
(embedding images into GtkAda applications see)
  64- 32- 64- 32bit
Windows i686     xpm2gtkada.exe.gz (gzip compressed, Windows users may use WinZip)   [Download]
Fedora packages fedora   is a part of the developing package (has devel suffix)   [Download page] [Download page] [Download page] [Download page]
CentOS packages CentOS   is a part of the developing package (has devel suffix)       [Download page] [Download page]
Debian packages Debian   is a part of the developing package (has dev suffix)   [Download page] [Download page] [Download page] [Download page]
Ubuntu packages Ubuntu   is a part of the developing package (has dev suffix)   [Download page] [Download page] [Download page] [Download page]

See also:


The described here packages are proposed as a contribution to GtkAda, an Ada bindings to GTK+. It deals with the following issues:

See also changes log

[TOC][Next]

1. Tasking with GTK+

The package Gtk.Main.Router provides a synchronization mechanism to use GTK+ framework with Ada tasks. GTK+ is known to be task unsafe. In particular, all calls need to be made from the same task (thread). Further GTK+ has a callback-based architecture which makes it difficult to use Ada's entry points for synchronization, because callback subprograms cannot act as entries. This package allows Ada tasks triggering some GTK+ actions to synchronize on a protected object with the task handling GTK+ events. Basically, the task waits for GTK+ be ready to serve it. Serving occurs upon idle loop processing, which performs the requested action on the context of the main GTK+ thread. Upon action completion the task is unblocked and continues its work. For the task it appears much as a rendezvous with the GTK+ main thread.

The package provides three ways to request an action to be performed on the context of GTK+ main thread.

Note that the package is based on timer events.

Quit_Error : exception;
Busy_Error : exception;

The exception propagated when servicing is impossible because the main GTK+ loop was prematurely left.

function Get_Max_Asynchronous return Positive;

This function returns the maximum number of asynchronous requests pending in the queue. When the limit is reached the new asynchronous requests are blocked. When a request stays until timeout expiration, it fails with Busy_Error exception.

function Get_Request_Info return String;

This function returns a string containing information about current requests. It is used for debugging purpose.

procedure Init
          (  Window   : not null access Gtk_Window_Record'Class;
             Period   : Duration := 0.2;
             GPS_Port : Natural  := 50_000
          );

This procedure should be called once from the main GTK+ thread after Init. Usually it is done before entering the loop of processing events and before starting tasks which might use the package functionality. Period specifies how frequently the mail loop will poll for graphic requests from other tasks. The parameter Window is the application window for which the main loop is used. The parameter GPS_Port specifies the port used to connect to the GPS, when the latter is in the server mode.

function Is_Active return Boolean;

This function returns true if servicing is active. When inactive requests fail with Quit_Error exceptions.

procedure Quit;

This procedure stops servicing request. All pending and future requests propagate Quit_Error. Normally it is not necessary to use this procedure because servicing is stopped automatically when the window specified in Init is destroyed.

procedure Set_Max_Asynchronous (Max : Positive);

This procedure sets the maximum number of asynchronous requests pending in the queue. This limit does not affect the synchronous requests because these are limited by the total number of tasks.

type Request_Data is abstract
   new
Ada.Finalization.Limited_Controlled with null record;

The base type of a request.

procedure Request (Data : in out Request_Data'Class);

This procedure is called in order to request Data to be serviced on the context of the main GTK+ task. The call is blocking. The caller will wait until the request will be serviced through a call to Service on the GTK+ context. Program_Error is propagated when Init was not called. Other exceptions are the exceptions propagated out of Service and re-raised on the caller's context. Quit_Error is propagated when the main GTK+ loop was quitted before the request was serviced.

procedure Service (Data : in out Request_Data) is abstract;

This abstract procedure which any derived type should implement. All GTK+ calls shall be placed here. Note that Service is called on the context of the main GTK+ thread. An implementation may propagate exceptions which are caught and re-raised on the context of Request.

procedure Request (Service : Gtk_Callback);

The caller will wait until the request will be serviced through a call to Service on the GTK+ context. Service is a parameterless procedure. Program_Error is propagated when Init was not called. Other exceptions are the exceptions propagated out of Service and re-raised on the caller's context. Quit_Error is propagated when the main GTK+ loop was quitted before the request was serviced.

generic
   type
User_Data (<>) is limited private;
package Generic_Callback_Request is ...

The package is instantiated with the user data type. It declares the type:

type Callback_Procedure is
   access procedure
(Data : not null access User_Data);

This is the procedure to be called on the GTK+ context.

procedure Request
          (  Callback : Callback_Procedure;
             Data     : not null access User_Data
          );

The caller will wait until the request will be serviced through a call to Callback on the GTK+ context. Program_Error is propagated when Init was not called. Other exceptions are the exceptions propagated out of Callback and re-raised on the caller's context. Quit_Error is propagated when the main GTK+ loop was quitted before the request was serviced.

generic
   type
User_Data is private;
package
Generic_Message is ...

The package is provided for execution of user-defined procedures on the GTK+ context asynchronously to the caller. The package formal parameter is the data type passed to a call. Note that the type is not limited because the values of are marshaled. Note also that this package does not provide any performance advantages over synchronous calls. It is provided for rare cases when servicing the request requires completion of the caller. For example, when the caller is a task that performs some lengthy action which upon completion should destroy a widget that owns the task. When widget destruction is requested from the task it will also wait for the task to finalize. When accomplished synchronously this would deadlock. Observe that for this reason use of Generic_Message on the GTK+ context is meaningless, though allowed.

type Handler_Procedure is access procedure (Data : in out User_Data);

This is the procedure to be called on the GTK+ context.

procedure Send
          (  Handler : Handler_Procedure;
             Data    : User_Data;
             Timeout : Duration := 0.5
          );

This call requests execution of Handler with Data parameters. It does not block the caller unless the maximum number of asynchronous requests is reached (see Set_Max_Asynchronous). When called on the context of the main loop, the callback is postponed until messages loop end. Data is marshaled. Program_Error is propagated when Init was not called. Quit_Error is propagated when the main GTK+ loop was quitted before the request was serviced. Busy_Error is propagated when Timeout is expired.

1.1. Example

The following is a small test program illustrating use of the package.

File test_gtk_tasking.adb:
with Ada.Exceptions;  use Ada.Exceptions;
with
GtkAda.Handlers; use GtkAda.Handlers;
with
Gtk.Main.Router; use Gtk.Main.Router;
with
Gtk.Window;      use Gtk.Window;
with
Gtk.Widget;      use Gtk.Widget;
with
Gtk.Table;       use Gtk.Table;
with
Gtk.Label;       use Gtk.Label;

with
Ada.Unchecked_Conversion;
with
Gtk.Missed;

procedure
Test_Gtk_Tasking is
   --
   -- All data are global, for the sake of simplicity
   --

   Window  : Gtk_Window;
   Grid    : Gtk_Table;
   Label   : Gtk_Label;
   Counter : Integer;

   -- Circumvention of access rules, don't do it, it is here only to
   -- simplify the test
   type Local_Callback is access procedure;
   function
"+" is
      new
Ada.Unchecked_Conversion (Local_Callback, Gtk_Callback);

   task type
Process;

   -- Update will write the label
   procedure Update is
   begin
  
   Label.Set_Text ("Counter" & Integer'Image (Counter));
   end
Update;

   -- The task that calls to Update
   task body Process is
   begin
      for
Index in Positive'Range loop
         Counter := Index;
         Request (+Update'Access); -- Request execution of Update
        
delay 0.5;
      end loop
;
   exception
      when
Quit_Error => -- Main loop was quitted, we follow
         null
;
      when
Error : others =>
         Say (Exception_Information (Error)); -- This is safe
   end
Process;

begin
   Gtk.Main.Init;
   Gtk.Window.Gtk_New (Window);
   Gtk.Main.Router.Init (Window); -- This must be called once
   Window.Set_Title ("Test");
   Window.On_Delete_Event (Gtk.Missed.Delete_Event_Handler'Access);
   Window.On_Destroy (Gtk.Missed.Destroy_Handler'Access);
   Gtk_New (Grid, 1, 1, False);
   Window.Add (Grid);
   Gtk_New (Label, "label");
   Grid.Attach (Label, 0, 1, 0, 1);

   Label.Show;
   Grid.Show;
   Window.Show;
   declare
      Worker : Process; -- Now the task is on
   begin
      -- Enter the events processing loop
      Gtk.Main.Main;
   end;
exception
   when
Error : others =>
      Say (Exception_Information (Error)); -- This is safe
end
Test_Gtk_Tasking;

1.2. Debugging tools

The package Gtk.Main.Router also provides two procedures for simple debugging and messaging purposes:

procedure Say
          (  Message       : UTF8_String;
             Title         : UTF8_String := "";
             Mode          : UTF8_String := Stock_Dialog_Info;
             Justification : Gtk_Justification := Justify_Left;
             Parent        : access Gtk_Widget_Record'Class := null
          );

This procedure pops a dialog box with Message in it. It can be called from any task.

procedure Trace
          (  Message : UTF8_String;
             Break   : Boolean := False
          );

This procedure represents a simplified tracing mechanism. When called first time it pops up a dialog box containing Message.

main router trace

All further calls add new messages to the box. The dialog box has the check button break. When this button is checked each call to Trace blocks until user confirmation. When the button is unchecked the procedure adds its message without waiting. The button break can be checked at any time. Once checked it will hold on the next message. Then the button next continues execution until a next message. It has the effect of checking the break button. The button record continues without further confirmations, and thus it resets the check state of break. The button quit closes the box. The box will be automatically reopened empty on the next message. The parameter Break when set to true overrides unchecked break button and enters wait after adding the message. This can be useful when the message indicates a certain error.

procedure Trace
          (  Error : Exception_Occurence;
             Break : Boolean := True
          );

This procedure is a shortcut for

Trace (Ada.Exceptions.Exception_Information (Error), Break);

It typically is used like:

   ... -- A suspicious code fragment
exception
   when
Error : others => -- Breaks execution, shows
      Trace (Error);      -- the exception message
      raise;
end;

1.3. GNAT-specific debugging tools

The child package Gtk.Main.Router.GNAT_Stack provides procedures Say and Trace of the same profile as its parent. They add stack symbolic traceback to the message printed:

procedure Say
          (  Message       : UTF8_String;
             Title         : UTF8_String := "";
             Mode          : UTF8_String := Stock_Dialog_Info;
             Justification : Gtk_Justification := Justify_Left;
             Parent        : access Gtk_Widget_Record'Class := null
          );
procedure
Trace
          (  Message : UTF8_String;
             Break   : Boolean := False
          );
procedure
Trace
          (  Error : Exception_Occurence;
             Break : Boolean := True
          );

Trace can be used as follows:

   ... -- A suspicious code fragment
exception
   when
Error : others =>                       -- Breaks execution, shows
      Gtk.Main.Router.GNAT_Stack.Trace (Error); -- the exception message
      raise;                                    -- and the call stack
end;

The procedures use GNAT.Traceback.Symbolic for this purpose. Please refer to the GNAT Reference Manual for the prerequisites of.

procedure Set_Log_Trace
          (  Domain : String;
             Level  : Log_Level_Flags := Log_Fatal_Mask or Log_Level_Critical
          );
procedure Set_Log_Trace;

This procedure is used for catching GTK+ log messages. Usually these messages indicate very severe errors which are extremely difficult to track down, because they occur in the core libraries of GTK+ written in C. The procedure eases debugging such errors by causing a log message to appear in the tracing dialog box accompanied by the call stack dump. Doing that it stops the application until user confirmation. The parameters of the procedure are Domain indicating which messages has to be caught and Level specifying the severity level of. When this procedure is called several times its effect is accumulated. Some domain names are:

Please refer GTK+ documentation for further domain names. When Domain and Level are omitted, all messages from all domains are caught. Note that this happens only if the messages are not caught by other means, i.e. it acts as a default message handler.

procedure Indent
          (  Message : UTF8_String;
             Break   : Boolean  := False;
             Step    : Positive := 2
          );

This procedure places Message in the messages box adding as the prefix a chain of spaces, which length is Step multiplied by the depth of the call step: It can be useful to trace recursive subprograms in order to determine which instance of the caller has printed the message.

type Log_Filter is abstract tagged limited private;

An object of this type is used to filter messages additionally to the domain and level.

function Ignore
         (  Filter  : not null access Log_Filter;
            Domain  : String;
            Level   : Log_Level_Flags;
            Message : UTF8_String
         )  return Boolean is abstract;

This function returns true if the message must be ignored. If any of the filters returns true the message is not traced.

1.4. Translation of addresses into the source lines

Right mouse click on the trace dialog brings the dropdown menu expanded with two items as shown below (the look and feel may vary as it depends on the operating system):

trace dropdown menu

The choice paste stack traceback is used to paste GNAT exception traceback. The traceback is a part of Exception_Information. It has the format:

0x5e1b6e 0x5e109f 0x5f1c28 0x5f850a 0x5f7511 0x5f06df 0x59544b 0x5a66a5

When pasted it is replaced by the symbolic traceback as the utility addr2line does. The prerequisite is that the application is build with debug information included.

1.5. Source navigation

The choice go to the source location is used to open a file in the GPS. When the mouse cursor point at a traceback line which contains a reference to a source file, then GPS is asked to open the file at the line specified in the traceback line. The prerequisites are

  1. The application has debug information;
  2. The file is a part of the project;
  3. GPS is running and has the project open;
  4. GPS is running in the server mode;
  5. The port GPS server listens must be available for the application (e.g. not blocked by the firewall).

The server mode of GPS is activated as follows:

> gps --server=50000

Here 50000 is the TCP/IP port GPS will listen. The port number is specified in the Init call.

1.6. Debugging GTK+ programs

It is sometimes quite tedious to track down bugs in a GTK+ application. Many of the safeguards, the Ada language has, do not really work with GTK+. Errors are usually detected at run-time at the context of the GTK+, where little can be done. Here is a summary of the basic techniques for designing and debugging GTK+ programs in Ada:

Begin your GTK+ program with:

begin
   Gtk.Main.Init;
   Gtk.Main.Router.Init; -- Start routing and tracing
   Gtk.Main.Router.GNAT_Stack.Set_Log_Trace ("Gdk");
   Gtk.Main.Router.GNAT_Stack.Set_Log_Trace ("Gtk");
   Gtk.Main.Router.GNAT_Stack.Set_Log_Trace ("GLib-GObject");
   Gtk.Main.Router.GNAT_Stack.Set_Log_Trace ("GtkAda+");
   Gtk.Main.Router.GNAT_Stack.Set_Log_Trace ("my_application");
   ...
   Gtk.Main.Main;

This enables routing and tracing, while catching GTK+ errors. The procedure Set_Log_Trace described above turns on tracing for the errors in Gdk, Gtk, GLib, GtkAda contributions and the application itself. The most of errors happen in event handlers. Note that a handler is called on the context of GTK+. Propagation of an exception out of a handler will most likely crash the application. This is the reason why all handlers should rather catch exceptions. E.g.:

procedure Button_Clicked (Button : access Gtk_Button_Record'Class) is
begin

   ...
exception
   when
Error : others =>
      Log
      (  "my_application",
         Log_Level_Critical,
         "Fault in Button_Clicked:" & Exception_Information (Error)
      );
end Button_Clicked;

In combination with an initialization shown above, the effect of an exception in Button_Clicked will cause the trace dialog popped up, with the exception information in it. The application will be stopped. If the GPS is active and in the server mode, you will be able to navigate the call stack of the error inspecting the source code locations as described above. The application can be continued from the trace dialog, which will not crash it. As it was said above it is meaningless to propagate an exception out of an event handler.

The GPS in server mode is started as:

> gps --server=50000 my-project-name.gpr

Note that even release version can be built with the -g switch. This does not have any effect on the program performance, since it only adds the debugging information necessary to translate stack trace back into source line locations.


[Back][TOC][Next]

2. GTK+ tree view

GtkTreeView provides tree views in GTK+. The following packages are provided for dealing with GtkTreeView from Ada. The code of Gtk.Tree_Model.Abstract_Store was inspired by an implementation of a custom model by Maxim Resznik.

Notes about sizing tree views placed in a scrolled window. The tree view widget does not automatically shrink or expand its parent scrolled window. The effect is that the vertical height of the tree view is often too small when the scrolled window containing it is in turn a part of a top level window, such as a dialog. An application might wish to find a better size for the scroll window than GTK+ does. That is - no blank rows beneath the last visible row, all expanded rows visible when there is not too many of them. The following code snippet illustrates a possible approach:

. . . -- Placing items into the model, expanding rows, etc
declare
   Dummy  : GInt;
   Height : GInt;
   Width  : GInt;
begin
   Tree_View.Columns_Autosize;                     -- Size columns
  
Tree_View.Get_Preferred_Width  (Dummy, Width);  -- Query the integral
  
Tree_View.Get_Preferred_Height (Dummy, Height); -- tree view size
   Tree_View.Set_Size_Request                      -- Set new size
   (  GInt'Min (Width,  600),
      GInt'Min (Height, 500)
   );
end;

Here Get_Preferred_Width and Get_Preferred_Height ask the tree view to return its integral size. Note that at this point the rows should be already added and expanded as necessary. Then Set_Size_Request sets the new tree view size to the returned height and width, but not greater than some reasonable limits, usually chosen to fit into the screen size or parent window. The container widget (a scrolled window) will automatically resize together with the tree view.

2.1. Abstract custom model

The package Gtk.Tree_Model.Abstract_Store provides an abstract base type (Gtk_Abstract_Model_Record) for developing custom tree view models:

type Gtk_Abstract_Model_Record is
   abstract new
Gtk_Root_Tree_Model_Record with private;

Objects of the types derived from Gtk_Abstract_Model_Record will implement the GtkTreeModel interface. The implementation maps GTK+ virtual functions to the abstract primitive operations of the base type. A derived type shall provide implementations for them. The abstract primitive operations to override are:

The following operations have a default implementation:

Other operations:

function Children
         (  Model  : not null access Gtk_Abstract_Model_Record;
            Parent : Gtk_Tree_Iter
         )  return Gtk_Tree_Iter is abstract;

This function return the first child of Parent or Null_Iter. When Parent is Null_Iter, the first top node should be the result.

procedure Finalize
          (  Model : not null access Gtk_Abstract_Model_Record
          )  is null;

This procedure is called upon object destruction. The override, if any, shall call the parent's version.

function Get_Column_Type
         (  Model : not null access Gtk_Abstract_Model_Record;
            Index : GInt
         )  return GType is abstract;

This function returns the type of the model column. Index is the column number, zero based. GType_Invalid is returned when the column does not exist.

function Get_Flags (Model : not null access Gtk_Abstract_Model_Record)
   return
Tree_Model_Flags is abstract;

This function returns the flags of Model.

function Get_Iter
         (  Model : not null access Gtk_Abstract_Model_Record;
            Path  : Gtk_Tree_Path
         )  return Gtk_Tree_Iter is abstract;

This function converts Path to iterator. The result is Null_Iter when the path is invalid.

function Get_N_Columns (Model : not null access Gtk_Abstract_Model_Record)
   return GInt is abstract;

This function returns number of columns in Model.

function Get_Path
         (  Model : not null access Gtk_Abstract_Model_Record;
            Iter  : Gtk_Tree_Iter
         )  return Gtk_Tree_Path is abstract;

This function gets the path from an iterator. A path is dynamically allocated and has to be freed later using Path_Free.

procedure Get_Value
          (  Model  : not null access Gtk_Abstract_Model_Record;
             Iter   : Gtk_Tree_Iter;
             Column : Gint;
             Value  : out GValue
          )  is abstract;

This procedure is used to query a value from Model for the iterator Iter and column Column (zero-based). The result is returned in Value. Values are freed by the caller using Unset. It means that the implementation must always initialize Value. When no value can be returned because of some errors an invalid value can be used instead:

Init (Value, GType_Invalid);

Here the value is initialized for the type GType_Invalid.

function Has_Child
         (  Model : not null access Gtk_Abstract_Model_Record;
            Iter  : Gtk_Tree_Iter
         )  return Boolean is abstract;

This function returns true if the row indicated by Iter has a child in Model.

procedure Initialize
          (  Model   : not null access Gtk_Abstract_Model_Record'Class;
             Type_Of : GType
          );

This procedure has to be called by any derived type upon object construction. Normally it is the first call of its Initialize, which in turn is called from a Gtk_New. The parameter Type_Of must be a value returned by Register called with the name assigned to the GTK+ type of the derived type. Note that Register shall be called only once. So its result must be stored somewhere in the package that derives the type. The following code snippets illustrate use of Register: The package specification:

type My_Model_Record is new Gtk_Abstract_Model_Record with private;
type
My_Model is access all My_Model_Record'Class;

function
Get_Type return Gtk_Type;
function
Gtk_New (Model : out My_Model);
procedure Initialize (Model : not null access My_Model_Record'Class);
. . . -- Overriding primitive operations

The package body:

My_Model_Type : GType := GType_Invalid;

function
Get_Type return Gtk_Type is
begin
  if
My_Model_Type = GType_Invalid then
    
My_Model_Type := Register ("MyModel");
  end if;
  return
My_Model_Type; -- Registering the GTK+ type
end Get_Type;

procedure
Initialize (Model : not null access My_Model_Record'Class) is
begin
   Initialize (Model, Get_Type);
   . . . -- Custom initialization
end Initialize;

procedure Next
          (  Model : not null access Gtk_Abstract_Model_Record;
             Iter  : in out Gtk_Tree_Iter
          )  is abstract;

This function moves Iter to the next sibling node. Null_Iter is the result when there is no more siblings.

function Nth_Child
         (  Model  : not null access Gtk_Abstract_Model_Record;
            Parent : Gtk_Tree_Iter;
            N      : GInt
         )  return Gtk_Tree_Iter is abstract;

This gets iterator to a child of Parent by its zero-based number N. Null_Iter is the result when there is no such child. When Parent is Null_Iter roots are returned.

function N_Children
         (  Model : not null access Gtk_Abstract_Model_Record;
            Iter  : Gtk_Tree_Iter := Null_Iter
         )  return GInt is abstract;

This function returns the number of children of Iter.

function Parent
         (  Model : not null access Gtk_Abstract_Model_Record;
            Child : Gtk_Tree_Iter
         )  return GInt is abstract;

This function returns the parent of Child. For roots Null_Iter is returned.

procedure Previous
          (  Model : not null access Gtk_Abstract_Model_Record;
             Iter  : in out Gtk_Tree_Iter
          )  is abstract;

This function moves Iter to the previous sibling node. Null_Iter is the result when there is no more siblings.

procedure Ref_Node
          (  Model : not null access Gtk_Abstract_Model_Record;
             Iter  : Gtk_Tree_Iter
         );

The default implementation does nothing.

function Register
         (  Name       : String;
            Signals    : Chars_Ptr_Array := Null_Array;
            Parameters : Signal_Parameter_Types :=
                            Null_Parameter_Types
         )  return GType;

For each non-abstract derived type of Gtk_Abstract_Model_Record this function shall be called once before creation of the first object of. For each element of Signals a signal with this name and parameters from the corresponding row of Parameters is added to the registered type. The rows of the array Parameters are padded by GType_None.

procedure Unref_Node
          (  Model : not null access Gtk_Abstract_Model_Record;
             Iter  : Gtk_Tree_Iter
         );

The default implementation does nothing.

2.1.1. Custom model example

Here we consider using the package Gtk_Abstract_Model_Record for developing a custom tree view model. The custom store is based on a doubly-linked list of records. The records contain imaginary transaction data:

The subdirectory test_gtkada contains the full source:

File gtk.tree_model.custom_store.ads:

with Ada.Strings.Unbounded;          use Ada.Strings.Unbounded;
with Ada.Calendar;                   use Ada.Calendar;
with GLib;                           use GLib;
with GLib.Values;                    use GLib.Values;
with Gtk.Tree_Model;                 use Gtk.Tree_Model;
with Gtk.Tree_Model.Abstract_Store;  use Gtk.Tree_Model.Abstract_Store;

package Gtk.Tree_Model.Custom_Store is
   type Account_No is range 1..100_000_000;
   type Currency is delta 0.01 range -1_000_000_000.0..1_000_000_000.0;
--
-- Gtk_Transaction_Store_Record -- The type of the model
--

   type Gtk_Transaction_Store_Record is
      new
Gtk_Abstract_Model_Record with private;
--
-- Gtk_Transaction_Store -- The access type to deal with the objects of
--

   type Gtk_Transaction_Store is
      access all
Gtk_Transaction_Store_Record'Class;
--
-- Insert -- Add a new row into the model
--

   procedure Insert
             (  Model   : not null access Gtk_Transaction_Store_Record;
                Account : Account_No;
                User    : String;
                Amount  : Currency;
                Date    : Time
             );
--
-- Gtk_New -- Create a new object
--
-- Model - The result
--

   procedure Gtk_New (Model : out Gtk_Transaction_Store);

The package defines the types of the record fields. Then Gtk_Transaction_Store_Record is derived from Gtk_Abstract_Model_Record. According to GtkAda conventions this type is not used directly. An access type Gtk_Transaction_Store to it is used instead. The rationale is that GTK+ objects are subject of garbage collection. So they are never allocated on the stack and are never freed explicitly.

Finally the public part of the interface contains the procedure Insert used to add new record to the store and the procedure Gtk_New, whch creates an empty store.

File gtk.tree_model.custom_store.ads (continued):
private
   type Transaction_Record;
   type Transaction_Record_Ptr is access Transaction_Record;
--
-- Gtk_Transaction_Store_Record -- Implemenbtation is a doubly-linked
--                                 list of Transaction_Record. The store
-- holds a pointer to the first element in the list.
--

   type Gtk_Transaction_Store_Record is
      new
Gtk_Abstract_Model_Record with
   record

      First : Transaction_Record_Ptr;
   end record;

In the private part the Gtk_Transaction_Store_Record completed. It holds a pointer to the first element of a doubly-linked list of Transaction_Record items. Then the abstract primitive operations of Gtk_Abstract_Model_Record get overridden:

File gtk.tree_model.custom_store.ads (continued):
--
-- Now, the implementation of the Gtk_Abstract_Model_Record primitive
-- operations follows:
--

   function Children
            (  Model  : not null access Gtk_Transaction_Store_Record;
               Parent : Gtk_Tree_Iter
            )  return Gtk_Tree_Iter;
   function Get_Column_Type
            (  Model : not null access Gtk_Transaction_Store_Record;
               Index : GInt
            )  return GType;
   function Get_Flags (Model : not null access Gtk_Transaction_Store_Record)
      return Tree_Model_Flags;
   function Get_Iter
            (  Model : not null access Gtk_Transaction_Store_Record;
               Path  : Gtk_Tree_Path
            )  return Gtk_Tree_Iter;
   function Get_N_Columns (Model : not null access Gtk_Transaction_Store_Record)
      return GInt;
   function Get_Path
            (  Model : not null access Gtk_Transaction_Store_Record;
               Iter  : Gtk_Tree_Iter
            )  return Gtk_Tree_Path;
   procedure Get_Value
             (  Model  : not null access Gtk_Transaction_Store_Record;
                Iter   : Gtk_Tree_Iter;
                Column : Gint;
                Value  : out GValue
             );
   procedure Finalize (Model : not null access Gtk_Transaction_Store_Record);
   function Has_Child
            (  Model : not null access Gtk_Transaction_Store_Record;
               Iter  : Gtk_Tree_Iter
            )  return Boolean;
   procedure Next
             (  Model : not null access Gtk_Transaction_Store_Record;
                Iter  : in out Gtk_Tree_Iter
             );
   function Nth_Child
            (  Model  : not null access Gtk_Transaction_Store_Record;
               Parent : Gtk_Tree_Iter;
               N      : GInt
            )  return Gtk_Tree_Iter;
   function N_Children
            (  Model : not null access Gtk_Transaction_Store_Record;
               Iter  : Gtk_Tree_Iter := Null_Iter
            )  return GInt;
   function Parent
            (  Model : not null access Gtk_Transaction_Store_Record;
               Child : Gtk_Tree_Iter
            )  return Gtk_Tree_Iter;
   procedure
Previous
             (  Model : not null access Gtk_Transaction_Store_Record;
                Iter  : in out Gtk_Tree_Iter
             );

And finally Transaction_Record is defined. It contains the data fields described above and two pointers to link items of the list.

File gtk.tree_model.custom_store.ads (continued):
--
-- Transaction_Record -- Describes one row of the store
--

   type Transaction_Record is record
      Account  : Account_No;
      User     : Unbounded_String;
      Amount   : Currency;
      Date     : Time;
      Previous : Transaction_Record_Ptr;
      Next     : Transaction_Record_Ptr;
   end record;
end Gtk.Tree_Model.Custom_Store;

The implementation of the package specification:

File gtk.tree_model.custom_store.adb:
with Ada.Unchecked_Conversion;
with Ada.Unchecked_Deallocation;
with System.Address_To_Access_Conversions;

package body Gtk.Tree_Model.Custom_Store is

   GTK_Type : GType := GType_Invalid;

The implementation starts with the definition of the GTK+ type used for the store object. The type cannot be determined until GTK+ runs, so it is initialized as invalid and will be resolved later at run-time.

File gtk.tree_model.custom_store.adb (continued):
   function To_Iter (Node : Transaction_Record_Ptr)
      return Gtk_Tree_Iter is
      function To_Address is
         new Ada.Unchecked_Conversion
             (  Transaction_Record_Ptr,
                System.Address
             );
   begin
     return

     (  Stamp      => 1,
        User_Data  => To_Address (Node),
        User_Data2 => System.Null_Address,
        User_Data3 => System.Null_Address
     );
   end To_Iter;

   function To_Ptr (Node : Gtk_Tree_Iter)
      return Transaction_Record_Ptr is
      function
To_Transaction_Record_Ptr is
         new
Ada.Unchecked_Conversion
            (  System.Address,
               Transaction_Record_Ptr
            );
   begin
      if Node = Null_Iter then
         return null;
      else
         return
To_Transaction_Record_Ptr (Node.User_Data);
      end if;
   end To_Ptr;

The first thing we need to consider is an implementation of the iterators. An iterator unambiguously identifies a row of the store. In our case rows are represented by Transaction_Record accessed via pointers. So it is naturally to pack pointers into iterators. In GTK+ an iterator has four fields. Three of them have address size. We will use the first field to store a pointer to Transaction_Record. The function To_Iter converts a pointer to the item to an iterator. It simply converts the pointer to an address and stores it into the first address field. The backward conversion provides the function To_Ptr. Null-iterators are converted to null. A more advanced implementation would perform some additional sanity checks, but this is out of the scope of this small example.

File gtk.tree_model.custom_store.adb (continued):
   function Children
            (  Model  : not null access Gtk_Transaction_Store_Record;
               Parent : Gtk_Tree_Iter
            )  return Gtk_Tree_Iter is
   begin
      return
Null_Iter;
   end Children;

Our store is a pure list, so there is no children and parents, i.e neither row can have any child rows.

File gtk.tree_model.custom_store.adb (continued):
   function Get_Column_Type
            (  Model : not null access Gtk_Transaction_Store_Record;
               Index : GInt
            )  return GType is
   begin
      case
Index is
         when
0 => return GType_Int;    -- Account_No
         when 1 => return GType_String; -- User
         when 2 => return GType_Double; -- Amount
         when 3 => return GType_Int;    -- Year
         when 4 => return GType_Int;    -- Month
         when 5 => return GType_Int;    -- Day
         when 6 => return GType_Int;    -- Hour
         when 7 => return GType_Int;    -- Minute
         when 8 => return GType_Double; -- Seconds
         when others => return GType_Invalid;
      end case;
   end Get_Column_Type;

The store publishes 8 columns, which GTK+ types of are reported by Get_Column_Type. The columns 0..2 represent Account No., User name and Amount. The following 5 represent the time stamp. In a more advanced application you might want to put more complex types into columns, for example by using handles. For such types you would probably need to develop a custom cell renderer as well.

File gtk.tree_model.custom_store.adb (continued):
   function Get_Flags (Model : not null access Gtk_Transaction_Store_Record)
      return Tree_Model_Flags is
   begin
      return
Tree_Model_Iters_Persist + Tree_Model_List_Only;
   end Get_Flags;

The function Get_Flags informs GTK+ about heuristics it can apply to the store, like that the store is not a tree. The value Tree_Model_Iters_Persist indicates that the iterators stay valid after changes applied to rows. This is true in out case because iterators are just wrapped pointers.

File gtk.tree_model.custom_store.adb (continued):
   function Get_Iter
            (  Model : not null access Gtk_Transaction_Store_Record;
               Path  : Gtk_Tree_Path
            )  return Gtk_Tree_Iter is
   begin
     if
Get_Depth (Path) = 1 and Model.First /= null then
        declare

           Indices : GInt_Array renames Get_Indices (Path);
           This    : Transaction_Record_Ptr := Model.First;
        begin
           for
Row in 0..Indices (Indices'First) - 1 loop
              if
This.Next = Model.First then
                 return
Null_Iter;
              end if;
              This := This.Next;
           end loop;
           return To_Iter (This);
        end;
      end if;
      return Null_Iter;
   end Get_Iter;

This function converts a tree path to an iterator. In GTK+ a path is an array of child numbers. All children rows of a row are enumerated from 0. So any path is equivalent to some iterator and reverse. In our case conversion first checks if the path is exactly one item long. After this check the child number is the number of the row. We walk through the list of records to that record. Then the pointer to it is converted to an iterator using To_Iter function described above. Observe, that this has O(n) complexity. Obviously, for relatively long lists a more elaborated implementation would definitely use some indexing schema to improve performance.

File gtk.tree_model.custom_store.adb (continued):
   function Get_N_Columns (Model : not null access Gtk_Transaction_Store_Record)
      return GInt is
   begin
      return
9;
   end Get_N_Columns;

   function Get_Path
            (  Model : access Gtk_Transaction_Store_Record;
               Iter  : Gtk_Tree_Iter
            )  return Gtk_Tree_Path is
      This : Transaction_Record_Ptr := Model.First;
      That : Transaction_Record_Ptr := To_Ptr (Iter);
      No   : GInt := 0;
   begin
      if
This = null or else That = null then
         return null
;
      end if;
      while This /= That loop
         if
This.Next = Model.First then
            return null
;
         end if;
         This := This.Next;
         No   := No + 1;
      end loop;
      declare
         Path : Gtk_Tree_Path := Gtk_New;
      begin
         Append_Index (Path, No);
         return Path;
      end;
   end Get_Path;

The function Get_N_Columns returns the number of columns. The function Get_Path is reverse to Get_Iter described above.

File gtk.tree_model.custom_store.adb (continued):
   procedure Get_Value
             (  Model  : not null access Gtk_Transaction_Store_Record;
                Iter   : Gtk_Tree_Iter;
                Column : Gint;
                Value  : out GValue
             )  is
      Node    : Transaction_Record_Ptr := To_Ptr (Iter);
      Year    : Year_Number;
      Month   : Month_Number;
      Day     : Day_Number;
      Seconds : Duration;
   begin
      if Node /= null then
         case
Column is
            when
0 => -- Account_No
               Init (Value, GType_Int);
               Set_Int (Value, GInt (Node.Account));
            when 1 => -- User
               Init (Value, GType_String);
               Set_String (Value, To_String (Node.User));
            when 2 => -- Amount
               Init (Value, GType_Double);
               Set_Double (Value, GDouble (Node.Amount));
            when 3 => -- Time, year
               Split (Node.Date, Year, Month, Day, Seconds);
               Init (Value, GType_Int);
               Set_Int (Value, GInt (Year));
            when 4 => -- Time, month
               Split (Node.Date, Year, Month, Day, Seconds);
               Init (Value, GType_Int);
               Set_Int (Value, GInt (Month));
            when 5 => -- Time, day
               Split (Node.Date, Year, Month, Day, Seconds);
               Init (Value, GType_Int);
               Set_Int (Value, GInt (Day));
            when 6 => -- Time, hour
               Split (Node.Date, Year, Month, Day, Seconds);
               Init (Value, GType_Int);
               Set_Int (Value, GInt (Seconds) / 3600);
            when 7 => -- Time, minute
               Split (Node.Date, Year, Month, Day, Seconds);
               Init (Value, GType_Int);
               Set_Int (Value, (GInt (Seconds) / 60) mod 60);
            when 8 => -- Time, seconds
               Split (Node.Date, Year, Month, Day, Seconds);
               Init (Value, GType_Double);
               Set_Double
               (  Value,
                  GDouble'Remainder (GDouble (Seconds), 60.0)
               );
            when others =>
               Init (Value, GType_Invalid);
         end case;
      end if;
   end Get_Value;

For the given row and column Get_Value returns the value of the cell. The row is specified by an iterator. The column is by its zero-based number. The parameter Value is the result. The pair of GTK+ procedures Init, Set_type is the way to place a value there. Init specifies the GTK+ type of the value. Set_type stores the value there. The caller is responsible to call Unset on Value.

File gtk.tree_model.custom_store.adb (continued):
   procedure Gtk_New (Model : out Gtk_Transaction_Store) is
   begin
      if
GTK_Type = GType_Invalid then
         GTK_Type := Register ("GtkTransactionStore");
      end if;
      Model := new Gtk_Transaction_Store_Record;
      Initialize (Model, GTK_Type);
   end Gtk_New;

The procedure Gtk_New is the store factory. It creates a new store object. First it checks if the GTK+ type was already registered. If not it registers it under the name GtkTransactionStore. This name can be later used in the GTK+ files for instance. Register shall be called once before any use of any store object. Initialize shall be called for each store object. Note that it takes the GTK+ type as a paramter.

File gtk.tree_model.custom_store.adb (continued):
   procedure Finalize (Model : not null access Gtk_Transaction_Store_Record) is
      procedure
Free is
         new
Ada.Unchecked_Deallocation
             (  Transaction_Record,
                Transaction_Record_Ptr
             );
      This : Transaction_Record_Ptr := Model.First;
      Next : Transaction_Record_Ptr := This;
   begin
      Finalize (Gtk_Abstract_Model_Record'Class (Model.all)'Access);
      while This /= null loop
         Next := This.Next;
         Free (This);
         This := Next;
      end loop;
   end Finalize;

Finalize is provided for custom finalization. It is analogous to the Ada.Finalization's one. The implementation calls to the parent Finalize and then deletes all items of the list.

File gtk.tree_model.custom_store.adb (continued):
   function Has_Child
            (  Model : not null access Gtk_Transaction_Store_Record;
               Iter  : Gtk_Tree_Iter
            )  return Boolean is
   begin
      return
False;
   end Has_Child;

There is no children, it is not a tree.

File gtk.tree_model.custom_store.adb (continued):
   procedure Insert
             (  Model   : not null access Gtk_Transaction_Store_Record;
                Account : Account_No;
                User    : String;
                Amount  : Currency;
                Date    : Time
             )  is
      Node : Transaction_Record_Ptr :=
                new Transaction_Record'
                    (  Account  => Account,
                       User     => To_Unbounded_String (User),
                       Amount   => Amount,
                       Date     => Date,
                       Next     => null,
                       Previous => null
                    );
   begin
      if
Model.First = null then
         Model.First   := Node;
         Node.Next     := Node;
         Node.Previous := Node;
      else
         Node.Next          := Model.First;
         Node.Previous      := Model.First.Previous;
         Node.Next.Previous := Node;
         Node.Previous.Next := Node;
      end if;
      Row_Inserted -- Notify about changes made
      (  Model,
         Get_Path (Model, To_Iter (Node)),
         To_Iter (Node)
      );
   end Insert;

The procedure Insert allocates a new record, initializes its fields according to the parameters and appends the record to the list. Then, very importantly, it emits a GTK+ signal that a row was inserted. For this it calls Row_Inserted of Gtk.Tree_Model. The parameters are the path and the iterator of the new row. Get_Path and To_Iter are used to obtain them.

File gtk.tree_model.custom_store.adb (continued):
   procedure Next
             (  Model : not null access Gtk_Transaction_Store_Record;
                Iter  : in out Gtk_Tree_Iter
             )  is
      Node : Transaction_Record_Ptr := To_Ptr (Iter);
   begin
      if Node = null or else Node.Next = Model.First then
         Iter := Null_Iter;
      else
         Iter := To_Iter (Node.Next);
      end if;
   end Next;

The procedure Next moves the iterator to the next row.

File gtk.tree_model.custom_store.adb (continued):
   function Nth_Child
            (  Model  : not null access Gtk_Transaction_Store_Record;
               Parent : Gtk_Tree_Iter;
               N      : GInt
            )  return Gtk_Tree_Iter is
      This : Transaction_Record_Ptr := Model.First;
   begin
      if
Parent = Null_Iter then
         for
Index in 0..N - 1 loop
            if
This.Next = Model.First then
               return
Null_Iter;
            end if;
            This := This.Next;
         end loop;
         return To_Iter (This);
      end if;
      return Null_Iter;
   end Nth_Child;

The function Nth_Child returns an iterator to the n-th child of a row. Note that when Parent is null-iterator the result is the n-th row. This is the only case we should take care of. Remember the note of O(n) complexity of such operations on doubly-linked lists.

File gtk.tree_model.custom_store.adb (continued):
   function N_Children
            (  Model : not null access Gtk_Transaction_Store_Record;
               Iter  : Gtk_Tree_Iter := Null_Iter
            )  return GInt is
      This  : Transaction_Record_Ptr := Model.First;
      Count : GInt := 0;
   begin
      if
Iter = Null_Iter and then This /= null then
         loop

            Count := Count + 1;
            exit when This.Next = Model.First;
            This := This.Next;
         end loop;
      end if;
      return Count;
   end N_Children;

This function is analogous to Nth_Child, it counts the children. Again our case is when the parameter is null-iterator.

File gtk.tree_model.custom_store.adb (continued):
   function Parent
            (  Model : not null access Gtk_Transaction_Store_Record;
               Child : Gtk_Tree_Iter
            )  return Gtk_Tree_Iter is
   begin
      return
Null_Iter;
   end Parent;

We have no children and parents, so the implementation of Parent is trivial.

File gtk.tree_model.custom_store.adb (continued):
   procedure Previous
             (  Model : not null access Gtk_Transaction_Store_Record;
                Iter  : in out Gtk_Tree_Iter
             )  is
      Node : Transaction_Record_Ptr := To_Ptr (Iter);
   begin
      if Node = null or else Node = Model.First then
         Iter := Null_Iter;
      else
         Iter := To_Iter (Node.Next);
      end if;
   end Previous;

end Gtk.Tree_Model.Custom_Store;
 

The same subdirectory test_gtkada contains a small test program for this store in the file test_custom_store.adb. The program creates a store and tree view. Observe, that it adds some records to the store in a quasi-concurrent way from GTK+ timer to illustrate that tree view would properly react on the content changes.

2.2. Generic sortable model

The generic package Gtk.Tree_Model.Generic_Sort provides an interface to GtkTreeSortable. The package is instantiated with a custom tree model derived from Gtk_Abstract_Model_Record:

generic
   type
Tree_Model_Record (<>) is
      new
Gtk_Abstract_Model_Record with private;
   type
Tree_Model is access all Tree_Model_Record'Class;
package
Gtk.Tree_Model.Generic_Sort is
   ...

The generic parameters are a type derived from Gtk_Abstract_Model_Record and an access type used with it. The package defines a new model based on one of Gtk_Abstract_Model_Record, which has the sorted data of the underlying model. The type of the new model is:

type Gtk_Tree_Model_Sort_Record is
   new
Gtk_Tree_Model_Record with private;
type Gtk_Tree_Model_Sort is
   access all
Gtk_Tree_Model_Sort_Record'Class;

The type Gtk_Tree_Model_Sort_Record is normally used as a base type for a derived user type which overrides the function Compare, which is used to when the widget sorts its contents:

function Compare
         (  Store : not null access Gtk_Tree_Model_Sort_Record;
            Left  : Gtk_Tree_Iter;
            Right : Gtk_Tree_Iter
         )  return Gtk.Missed.Row_Order;

This function is used for sorting if Set_Sort_Func was called for the current sort column or as a default. Left and Right are the iterators in the unsorted model. The current sort column can be queried using Get_Sort_Column_ID. The unsorted model can be obtained using Get_Model. Note that the sort order as returned by Get_Sort_Column_ID should not influence the result of this function. The caller automatically translates the result into descending order if necessary. The type Row_Order is defined in Gtk.Missed as follows:

type Row_Order is (Before, Equal, After);

The procedure Set_Sort_Func is used to activate Compare for desired columns:

procedure Set_Sort_Func
          (  Store  : not null access Gtk_Tree_Model_Sort_Record'Class;
             Column : GInt
          );
procedure
Set_Sort_Func
          (  Store : not null access Gtk_Tree_Model_Sort_Record'Class
          );

The second variant activates Compare for default sorting. Default sorting in GTK+ refers to an unsorted model.

2.3. Custom cell renderer

This package Gtk.Cell_Renderer.Abstract_Renderer provides an abstract base type Gtk_Abstract_Renderer_Record_for GTK+ tree view column renderers. An object of this type functions as GtkCellRenderer. The type is declared as:

type Gtk_Abstract_Renderer_Record is
   abstract new
Gtk_Cell_Renderer_Record with private;

A derived type shall override the following primitive operations:

function Get_Aligned_Area
         (  Cell      : not null access Gtk_Abstract_Renderer_Record;
            Widget    : not null access Gtk_Widget_Record'Class;
            Flags     : Gtk_Cell_Renderer_State;
            Cell_Area : Gdk_Rectangle
         )  return Gdk_Rectangle is abstract;

This function returns the are inside Cell_Area that would be used to render the content.

function Get_Size
         (  Cell      : not null access Gtk_Abstract_Renderer_Record;
            Widget    : not null access Gtk.Widget.Gtk_Widget_Record'Class;
            Cell_Area : Gdk_Rectangle
         )  return Gdk_Rectangle is abstract;
function Get_Size
         (  Cell   : not null access Gtk_Abstract_Renderer_Record;
            Widget : not null access Gtk.Widget.Gtk_Widget_Record'Class
         )  return Gdk_Rectangle is abstract;

These functions return the desired area of the renderer in the form of a rectangle.

procedure Render
          (  Cell            : not null access Gtk_Abstract_Renderer_Record;
             Context         : Cairo_Context;
             Widget          : not null access Gtk_Widget_Record'Class;
             Background_Area : Gdk_Rectangle;
             Cell_Area       : Gdk_Rectangle;
             Flags           : Gtk_Cell_Renderer_State
          )  is abstract;

This procedure is called to perform rendering. Context is the drawing context. Background_Area is the rectangle around the cell which includes the border. Cell_Area is the area where things should be drawn into.

Other operations include:

overriding
function
Activate
         (  Cell   : not null access Gtk_Abstract_Renderer_Record;
            Event  : Gdk_Event;
            Widget : not null access Gtk_Widget_Record'Class;
            Path            : UTF8_String;
            Background_Area : Gdk_Rectangle;
            Cell_Area       : Gdk_Rectangle;
            Flags           : Gtk_Cell_Renderer_State
         )  return Boolean;

This function can be overridden to make the renderer activatable. Such a renderer may hold a toggle button in it. The default implementation returns false. Path specifies the activation event location, e.g. the tree path to the model.

procedure Commit (Cell : not null access Gtk_Abstract_Renderer_Record);

This procedure is used to notify the tree view about the changes made (this is used for editable renderers). From here the render changes the model.

procedure Finalize (Cell : not null access Gtk_Abstract_Renderer_Record);

This procedure can be overridden to provide an Ada-style finalization. When overridden, it must call the default implementation from the body.

function Get_Mode (Cell : not null access Gtk_Abstract_Renderer_Record)
   return Gtk_Cell_Renderer_Mode;

This function returns the renderer mode, such as inert, editable or activatable.

function Get_Path (Cell : not null access Gtk_Abstract_Renderer_Record)
   return UTF8_String;

This function returns returns the path of the cell being edited.

overriding
procedure
Get_Preferred_Height
          (  Cell   : not null access Gtk_Abstract_Renderer_Record;
             Widget : not null access Gtk_Widget_Record'Class;
             Minimum_Height : out GInt;
             Natural_Height : out GInt
          );

This procedure retrieves the renderer's height if rendered to Widget. The default implementation re-dispatches to Get_Size.

overriding
procedure
Get_Preferred_Height_For_Width
          (  Cell   : not null access Gtk_Abstract_Renderer_Record;
             Widget : not null access Gtk_Widget_Record'Class;
             Width  : GInt;
             Minimum_Height : out GInt;
             Natural_Height : out GInt
          );

This procedure retrieves the renderer's width for given Width if rendered to Widget. The default implementation re-dispatches to Get_Size.

overriding
procedure
Get_Preferred_Get_Width
          (  Cell   : not null access Gtk_Abstract_Renderer_Record;
             Widget : not null access Gtk_Widget_Record'Class;
             Minimum_Height : out GInt;
             Natural_Height : out GInt
          );

This procedure retrieves the renderer's width if rendered to Widget. The default implementation re-dispatches to Get_Size.

overriding
procedure
Get_Preferred_Width_For_Height
          (  Cell   : not null access Gtk_Abstract_Renderer_Record;
             Widget : not null access Gtk_Widget_Record'Class;
             Height : GInt;
             Minimum_Width : out GInt;
             Natural_Width : out GInt
          );

This procedure retrieves the renderer's width for given Height if rendered to Widget. The default implementation re-dispatches to Get_Size.

procedure Get_Property
          (  Cell          : not null access Gtk_Abstract_Renderer_Record;
             Param_ID      : Property_ID;
             Value         : out GValue;
             Property_Spec : Param_Spec
          );

This procedure returns the value of a GTK+ property the renderer understands. The properties are the values the renderer can show. Each property is specified as a text string which then appears in Add_Attribute. The procedure shall initialize Value. It is the caller's responsibility to unset it.

overriding
function
Get_Request_Mode
         (  Cell : not null access Gtk_Abstract_Renderer_Record;
         )  return Gtk_Size_Request_Mode;

This function returns preferred method of estimation of the area needed to renderer content. The default implementation returns Constant_Size.

function Get_X_Align
         (  Cell : not null access Gtk_Abstract_Renderer_Record
         )  return GFloat;
function
Get_X_Pad
         (  Cell : not null access Gtk_Abstract_Renderer_Record
         )  return GUInt;
function
Get_Y_Align
         (  Cell : not null access Gtk_Abstract_Renderer_Record
         )  return GFloat;
function
Get_Y_Pad
         (  Cell : not null access Gtk_Abstract_Renderer_Record
         )  return GUInt;

These functions return some widget properties.

procedure Initialize
          (  Cell    : not null access Gtk_Abstract_Renderer_Record'Class;
             Type_Of : GType
          );

This procedure has to be called by any derived type upon object construction. Normally it is the first call of its Initialize, which in turn is called from a Gtk_New. The parameter Type_Of must be a value returned by Register called with the name assigned to the GTK+ type of the derived type. Note that Register shall be called only once. So its result must be stored somewhere in the package that derives the type.

type Commit_Callback is access procedure
    
(  Cell : not null access Gtk_Abstract_Renderer_Record'Class
     );

procedure On_Commit
          (  Cell    : not null access Gtk_Abstract_Renderer_Record;
             Handler : not null Commit_Callback;
             After   : Boolean := False
          );

This procedure can be used to attach a handler to the commit signal.

function Register
         (  Name : String;
            Init : not null C_Class_Init := Base_Class_Init'Access
         )  return GType;

This procedure is used to register the GTK+ type of the renderer. The following code snippets illustrate use of Register: In the package specification:

type My_Renderer_Record is new Gtk_Abstract_Renderer_Record with private;
type
My_Renderer is access all My_Renderer_Record'Class;

function
Get_Type return Gtk_Type;
function
Gtk_New (Cell : out My_Renderer);
overriding
procedure
Initialize (Cell : not null access My_Renderer_Record'Class);
. . . -- Overriding primitive operations

In the package body:

My_Renderer_Type : GType := GType_Invalid;

function
Get_Type return Gtk_Type is
begin
  if
My_Renderer_Type = GType_Invalid then
    
My_Renderer_Type := Register ("MyRenderer", My_Class_Initialize'Access);
  end if;
  return
My_Renderer_Type; -- Registering the GTK+ type
end Get_Type;

procedure
Initialize (Cell : not null access My_Renderer_Record'Class) is
begin
   Initialize (Cell, Get_Type);
   . . . -- Custom initialization
end Initialize;

Usually Register specifies a user-provided procedure to be called upon initialization of the GTK+ class of the renderer. It is necessary to declare GTK+ properties of the renderer. The procedure has the following profile:

type C_Class_Init is access procedure (Class : GObject_Class);
pragma Convention (C, C_Class_Init);

The parameter Class is the class to initialize. When a user-defined procedure is provided, it shall call to Base_Class_Init from its body, before it begins to declare properties of the renderer.

procedure Set_Mode
          (  Cell : not null access Gtk_Abstract_Renderer_Record;
             Mode : Gtk_Cell_Renderer_Mode
          );

This procedure sets the renderer's mode property. The renderer can be inert, activatable or editable.

procedure Set_Property
          (  Cell          : not null access Gtk_Abstract_Renderer_Record;
             Param_ID      : Property_ID;
             Value         : GValue;
             Property_Spec : Param_Spec
          );

This procedure sets the value of a GTK+ property. The default implementation calls the parent's version.

function Start_Editing
         (  Cell   : not null access Gtk_Abstract_Renderer_Record;
            Event  : Gdk_Event;
            Widget : not null access Gtk_Widget_Record'Class;
            Path            : UTF8_String;
            Background_Area : Gdk_Rectangle;
            Cell_Area       : Gdk_Rectangle;
            Flags           : Gtk_Cell_Renderer_State
         )  return Gtk_Widget;

This procedure is called for editable cells upon start editing. The implementation returns a widget responsible for editing or null. The widget returned should implement the Gtk_Cell_Editable interface. Otherwise, the behaviour of the renderer will be as if Start_Editing would return null. The caller is responsible to Ref the result it gets and to Unref where appropriate. The default implementation returns null. A typical implementation would create a Gtk_Cell_Editable widget, like Gtk_Entry, initialize it with the current renderer's value, connect to the editing_done and focus_out_event signals of the widget and return the widget as the result.

overriding
procedure
Stop_Editing
          (  Cell      : not null access Gtk_Abstract_Renderer_Record;
             Cancelled : Boolean
          );

This procedure ends editing.

The widget declares commit signal, which is emitted by a call to the procedure Commit. This signal a tree view widget or its model would like to connect to, when an editable renderer is used in the widget. The handler of the signal would set the modified value into the tree model.

2.4. Editable renderers

The protocol of an editable GTK+ cell render is as follows. When the renderer's mode is Cell_Renderer_Editable (see Get_Mode) then:

  1. Upon editing activation the cell renderer receives a start editing notification. This is translated into a call to the Start_Editing primitive operation;
  2. If Start_Editing rejects editing attempt, it returns null. Otherwise it creates a widget with Gtk_Cell_Editable interface. Usually it is Gtk_Entry. Normally the returned widget should be initialized with the current cell value. The implementation might also wish to connect to the editing_done and focus_out_event signals of the widget;
  3. Upon focus_out_event the handler of calls Stop_Editing with Canceled set to true;
  4. Upon editing_done the handler of takes the edited value from the widget. If it decides to dismiss the value, it calls to Stop_Editing with Canceled set to true. If it accepts the value, it calls Stop_Editing with Canceled set to false followed by a call to Commit, which notifies about the changes made. Commit emits the signal commit;
  5. The renderer does not touch the tree model. It is the responsibility the commit handler. Within the handler Get_Path can be called to determine the string representation of the row, of which cell has been edited (see Get_Iter_From_String). Note that due to limitations of GTK+, there is no obvious way to determine the column of the cell. It should become known to the handler in some other way. The handler sets the value into the tree model. This ends editing.

2.5. Fixed-point renderer

The package Gtk.Cell_Renderer_Fixed provides a simple, yet, usable example a cell renderer. It defines a fixed-point numeric renderer. The numbers are represented in the form xxxx.yyyy using facilities of the package Ada.Text_IO.Float_IO. The renderer aligns all numbers along the positions of their decimal points. The renderer is editable. The package defines the rendrerer's type:

type Gtk_Cell_Renderer_Fixed_Record is
   new
Gtk.Cell_Renderer.Abstract_Renderer.
       Gtk_Abstract_Renderer_Record with private;
type
Gtk_Cell_Renderer_Fixed is
   access all
Gtk_Cell_Renderer_Fixed_Record'Class;

and the operations on it:

function Get_Type return Gtk_Type;

This function returns the GTK+ type of the fixed-point renderers.

procedure Gtk_New
          (  Cell  : out Gtk_Cell_Renderer_Fixed;
             After : Natural := 0
          );

This procedure creates a new renderer. The parameter After determines the number of decimal places shown after the point.

procedure Initialize
          (  Cell  : access Gtk_Cell_Renderer_Fixed_Record'Class;
             After : Natural
          );

This procedure shall be called from any type derived from Cell_Renderer_Fixed upon initialization.

The renderer provides the following properties:

2.4.1. Annotated source code of the renderer

The package specification file:

File gtk.cell_renderer_fixed.ads:
with Cairo;                     use Cairo;
with
Gdk.Event;                 use Gdk.Event;
with
Gdk.Rectangle;             use Gdk.Rectangle;
with GLib.Properties.Creation;  use GLib.Properties.Creation;
with GLib.Values;               use GLib.Values;
with Gtk.Cell_Renderer;         use Gtk.Cell_Renderer;
with Gtk.GEntry;                use Gtk.GEntry;
with Gtk.Handlers;              use Gtk.Handlers;
with Gtk.Widget;                use Gtk.Widget;
with Pango.Layout;              use Pango.Layout;

with Gtk.Cell_Renderer.Abstract_Renderer;
with Gdk.Event;

package Gtk.Cell_Renderer_Fixed is
   pragma Elaborate_Body (Gtk.Cell_Renderer_Fixed);
--
-- Gtk_Cell_Renderer_Fixed_Record -- The renderer type
--
-- Customary,  we need to declare  a representation record  type  and an
-- interface access type for dealing with renderer's objects. The record
-- type is never used directly, though all operations are defined in its
-- terms.
--

   type Gtk_Cell_Renderer_Fixed_Record is
      new
Gtk.Cell_Renderer.Abstract_Renderer.
          Gtk_Abstract_Renderer_Record with private;
   type Gtk_Cell_Renderer_Fixed is
      access all
Gtk_Cell_Renderer_Fixed_Record'Class;

The type Gtk_Cell_Renderer_Fixed_Record is derived from the abstract cell renderer type Gtk_Abstract_Cell_Renderer_Record. The GtkAda convention is that the names of implementation types ends with the suffix _Record. The public type to use is Cell_Renderer_Fixed, which is an access type. GTK+ uses a reference counting to collect objects like Gtk_Abstract_Cell_Renderer_Record, more or less transparently to the user.

File gtk.cell_renderer_fixed.ads (continued):
--
-- Finalize -- Overrides Gtk.Cell_Renderer.Abstract_Renderer...
--

   overriding
   procedure
 Finalize (Cell : not null access Gtk_Cell_Renderer_Fixed_Record);

The procedure Finalize of the parent type is overridden to have an ability to clean-up some internal data upon object finalization.

File gtk.cell_renderer_fixed.ads (continued):
--
-- Get_Aligned_Area -- Overrides Gtk.Cell_Renderer.Abstract_Renderer...
--

   overriding
   function
Get_Aligned_Area
            (  Cell   : not null access Gtk_Cell_Renderer_Fixed_Record;
               Widget : not null access Gtk_Widget_Record'Class;
               Flags  : Gtk_Cell_Renderer_State;
               Cell_Area : Gdk_Rectangle
            )  return Gdk_Rectangle;

This function determines the area of the widget which will be used by the renderer.

File gtk.cell_renderer_fixed.ads (continued):
--
-- Get_Property -- Overrides Gtk.Cell_Renderer.Abstract_Renderer...
--

   overriding
   procedure
Get_Property
             (  Cell     : not null access Gtk_Cell_Renderer_Fixed_Record;
                Param_ID : Property_ID;
                Value    : out GValue;
                Property_Spec : Param_Spec
             );

Get_Property needs to be overridden to provide interface to the renderer's properties. The properties is the way GTK+ communicates with the renderer when it renders a cell. It extracts the cell value and sets the corresponding property of the renderer. Then it ask the renderer about the size required to show the value or ask it to render the value.

File gtk.cell_renderer_fixed.ads (continued):
--
-- Get_Size -- Overrides Gtk.Cell_Renderer.Abstract_Renderer...
--

   overriding
   function
Get_Size
            (  Cell      : not null access Gtk_Cell_Renderer_Fixed_Record;
               Widget    : not null access Gtk.Widget.Gtk_Widget_Record'Class;
               Cell_Area : Gdk_Rectangle
            )  return Gdk_Rectangle;
   overriding
   function
Get_Size
            (  Cell   : not null access Gtk_Cell_Renderer_Fixed_Record;
               Widget : not null access Gtk.Widget.Gtk_Widget_Record'Class
            )  return Gdk_Rectangle;
--
-- Get_Type -- Get the type of cell renderer
--
-- Returns :
--
-- The type of
--

   function Get_Type return Gtk_Type;

The procedures Get_Size are called to get the screen size required to render the currently set property of the renderer. The function Get_Type returns the GTK+ type of the renderer.

File gtk.cell_renderer_fixed.ads (continued):
--
-- Gtk_New -- Factory
--
--    Cell  - The result
--    After - The number of digits after decimal point
--

   procedure Gtk_New
             (  Cell  : out Gtk_Cell_Renderer_Fixed;
                After : Natural := 0
             );
--
-- Initialize -- Construction to be called once by any derived type
--
--    Cell - The renderer to initialize
--    After - The number of digits after decimal point
--
-- This procedure is never called directly, only from Gtk_New or else
-- from Initialize of a derived type. In the latter case a call to
-- Initialize is obligatory.
--

   procedure Initialize
             (  Cell  : not null access
                      
 Gtk_Cell_Renderer_Fixed_Record'Class;
                After : Natural
             );

The procedure Get_New provides the standard way to create a new renderer object. Internally, it calls to Iniialize, which shall be called by any derived type upon initialization of the latter.

File gtk.cell_renderer_fixed.ads (continued):
--
-- Render -- Overrides Gtk.Cell_Renderer.Abstract_Renderer...
--

   overriding
   procedure
Render
             (  Cell    : not null access Gtk_Cell_Renderer_Fixed_Record;
                Context : Cairo_Context;
                Widget  : not null access Gtk_Widget_Record'Class;
                Background_Area : Gdk_Rectangle;
                Cell_Area       : Gdk_Rectangle;
                Flags           : Gtk_Cell_Renderer_State
             );
--
-- Set_Property -- Overrides Gtk.Cell_Renderer.Abstract_Renderer...
--

   overriding
   procedure
Set_Property
             (  Cell          : not null access Gtk_Cell_Renderer_Fixed_Record;
                Param_ID      : Property_ID;
                Value         : GValue;
                Property_Spec : Param_Spec
             );

Render is called to display the renderer's property on the screen. Set_Property is a counterpart of Get_Property described above.

File gtk.cell_renderer_fixed.ads (continued):
--
-- Start_Editing -- Overrides Gtk.Cell_Renderer.Abstract_Renderer...
--
  
overriding
   function
Start_Editing
            (  Cell   : not null access Gtk_Cell_Renderer_Fixed_Record;
               Event  : Gdk_Event;
               Widget : not null access Gtk_Widget_Record'Class;
               Path            : UTF8_String;
               Background_Area : Gdk_Rectangle;
               Cell_Area       : Gdk_Rectangle;
               Flags           : Gtk_Cell_Renderer_State
            )  return Gtk_Widget;

Because the renderer is editable Start_Editing is overridden to provide the functionality.

File gtk.cell_renderer_fixed.ads (continued):
private
--
-- Gtk_Cell_Renderer_Fixed_Record -- Implementation
--
-- The renderer maintains its state global to the column it renders.
-- That is the text widget it uses to render the number, the number of
-- places after the decimal point and the maximal width of the number
-- places before the point including the sign. This field is evaluated
-- dynamically and adjusted each time the renderer is queried for its
-- size or asked to render a cell. This heuristics might not work if new
-- rows are added to the tree model after it was rendered once.
--

   type Gtk_Cell_Renderer_Fixed_Record is
      new
Gtk.Cell_Renderer.
          Abstract_Renderer.Gtk_Abstract_Renderer_Record with
   record

      Text       : Pango_Layout;   -- The text to display
      Value      : GDouble := 0.0; -- Current value
      After      : Natural := 0;   -- Places after the point
      Max_Offset : GInt    := 0;   -- Pixel offset to the point
      Height     : GInt    := 0;   -- Current pixel height
      Width      : GInt    := 0;   -- Current pixel width
      Left_Width : GInt;           -- Current space before the point
      Focus_Out  : Handler_Id;     -- Current focus_out_event handler
   end record;

The renderer's implementation consists of the following fields:

File gtk.cell_renderer_fixed.ads (continued):
--
-- Editing_Done -- The handler of editing_done
--
   procedure Editing_Done
             (  Editor : access Gtk_Entry_Record'Class;
                Cell   : Gtk_Cell_Renderer_Fixed
             );
--
-- Focus_Out -- The handler of focus_out
--
   function Focus_Out
            (  Editor : access Gtk_Entry_Record'Class;
               Event  : Gdk.Event.Gdk_Event;
               Cell   : Gtk_Cell_Renderer_Fixed
            )  return Boolean;
--
-- Entry_Callbacks -- To handle editing_done
--
   package Entry_Callbacks is
      new
Gtk.Handlers.User_Callback
          (  Widget_Type => Gtk_Entry_Record,
             User_Type   => Gtk_Cell_Renderer_Fixed
          );
--
-- Entry_Return_Callbacks -- To handle focus_out_event
--
   package Entry_Return_Callbacks is
      new
Gtk.Handlers.User_Return_Callback
          (  Widget_Type => Gtk_Entry_Record,
             Return_Type => Boolean,
             User_Type   => Gtk_Cell_Renderer_Fixed
          );
end Gtk.Cell_Renderer_Fixed;

Here we declare the handlers for editing_done and focus_out_event. The handles will be connected to a Gtk_Entry widget, which will perform editing. We also instantiate User_Callback to connect Editing_Done and User_Return_Callback to connect Focus_Out.

The implementation of the package:

File gtk.cell_renderer_fixed.adb:
with Ada.Strings.Fixed;  use Ada.Strings.Fixed;
with
GLib.Properties;    use GLib.Properties;
with Gtk.Enums;          use Gtk.Enums;
with Gtk.Missed;         use Gtk.Missed;
with Gtk.Style;          use Gtk.Style;
with Gtk.Style_Context;  use Gtk.Style_Context;
with
Gtk.Widget;         use Gtk.Widget;
with Pango.Cairo;        use Pango.Cairo;
with
Pango.Enums;        use Pango.Enums;
with Pango.Font;         use Pango.Font;

with Ada.Text_IO;

package body Gtk.Cell_Renderer_Fixed is

   package GDouble_IO is new Ada.Text_IO.Float_IO (GDouble);
   use GDouble_IO;

The package GDouble_IO is an instance of Ada.Text_IO.Float_IO used to render GDouble numbers to text.

File gtk.cell_renderer_fixed.adb (continued):
   Renderer_Type : GType := GType_Invalid;
   Value_ID      : constant Property_ID := 1;
   After_ID      : constant Property_ID := 2;

   procedure Class_Init (Class : GObject_Class);
   pragma Convention (C, Class_Init);

   procedure Class_Init (Class : GObject_Class) is
      use
Gtk.Cell_Renderer.Abstract_Renderer;
   begin
      Base_Class_Init (Class);
      Class_Install_Property
      (  Class,
         Value_ID,
         Gnew_Double
         (  Name    => "value",
            Nick    => "value",
            Blurb   => "fixed point number",
            Minimum => GDouble'First,
            Maximum => GDouble'Last,
            Default => 0.0
      ) );
      Class_Install_Property
      (  Class,
         After_ID,
         Gnew_UInt
         (  Name    => "after",
            Nick    => "aft",
            Blurb   => "digits after decimal point",
            Minimum => 0,
            Maximum => GDouble'Digits,
            Default => 0
   )  );
   end Class_Init;

The variable Renderer_Type holds the GTK+ type of the renderer. It is queried by Get_Type to determine whether the type is already registered in GTK+. Upon registration the procedure Class_Init will be  called. The next two constants are the identifiers of the renderer's properties. GTK+ translates property name to the identifier when it calls Get_Property or Set_Property.

The procedure Class_Init is called by Get_Type once upon type registration. The implementation of Class_Init calls to the parent's Class_Init and then registers the properties of the renderer. Each renderer object will have these two properties.

File gtk.cell_renderer_fixed.adb (continued):
   procedure Editing_Done
             (  Editor : access Gtk_Entry_Record'Class;
                Cell   : Gtk_Cell_Renderer_Fixed
             )  is
   begin
      if
Cell.Focus_Out.Id /= Null_Handler_Id then
         Disconnect (Editor, Cell.Focus_Out);
         Cell.Focus_Out.Id := Null_Handler_Id;
      end if;
      Cell.Value :=
         GDouble'Value (Trim (Get_Text (Editor), Ada.Strings.Both));
      Stop_Editing (Cell, False);
      Commit (Cell);
   exception
      when others
=>
         Stop_Editing (Cell, True);
   end Editing_Done;

The handler of editing_done receives the Gtk_Entry widget as the parameter. The second parameter is the user data identifying the renderer. First the handler disconnects the renderer from focus_out_event. Then it takes the text from the entry widget and converts it to GDouble. Upon any error it cancels editing by calling Stop_Editing with Canceled = true. Otherwise it stores the new value into the renderer. Then it stops editing using, this time by using Stop_Editing with Canceled = false. Then it calls Commit to emit the commit signal.

File gtk.cell_renderer_fixed.adb (continued):
   procedure Finalize
             (  Cell : not null access Gtk_Cell_Renderer_Fixed_Record
             )  is
      use Gtk.Cell_Renderer.Abstract_Renderer;
   begin
      if Cell.Text /= null then
         Unref (Cell.Text);
      end if;
      Finalize (Gtk_Abstract_Renderer_Record (Cell.all)'Access);
   end Finalize;

Finalize releases the field Text and then calls the parent type's Finalize.

File gtk.cell_renderer_fixed.adb (continued):
   function Focus_Out
            (  Editor : access Gtk_Entry_Record'Class;
               Event  : Gdk.Event.Gdk_Event;
               Cell   : Gtk_Cell_Renderer_Fixed
            )  return Boolean is
   begin

      Editing_Done (Editor, Cell);
      return False;
   end Focus_Out;

The handler of focus_out_event simply calls to Editing_Done and returns.

File gtk.cell_renderer_fixed.adb (continued):
   function Get_Aligned_Area
            (  Cell   : not null access Gtk_Cell_Renderer_Fixed_Record;
               Widget : not null access Gtk_Widget_Record'Class;
               Flags  : Gtk_Cell_Renderer_State;
               Cell_Area : Gdk_Rectangle
            )  return Gdk_Rectangle is
      Area   : Gdk_Rectangle := Cell.Get_Size (Widget, Cell_Area);
      Result : Gdk_Rectangle;
   begin
      Result.X :=
         (  Cell_Area.X
         +  GInt (Get_X_Pad (Cell))
         +  Area.X
         +  (Cell.Max_Offset - Cell.Left_Width)
         );
      Result.Y :=
         (  Cell_Area.Y
         +  GInt (Get_Y_Pad (Cell))
         +  Area.Y
         );
      Result.Width :=
         GInt'Min
         (  Result.X - Cell_Area.X + Cell_Area.Width,
            Area.Width
         );
      Result.Height :=
         GInt'Min (Result.Y - Cell_Area.Y + Cell_Area.Height, Area.Height);
      return Result;
   end Get_Aligned_Area;

This function evaluates the area which will be used to render the value, see implementation of Render below.

File gtk.cell_renderer_fixed.adb (continued):
   procedure Get_Property
             (  Cell          : not null access Gtk_Cell_Renderer_Fixed_Record;
                Param_ID      : Property_ID;
                Value         : out GValue;
                Property_Spec : Param_Spec
             )  is
   begin
      case
Param_ID is
         when
Value_ID =>
            Init (Value, GType_Double);
            Set_Double (Value, Cell.Value);
         when After_ID =>
            Init (Value, GType_UInt);
            Set_UInt (Value, GUInt (Cell.After));
         when others =>
            Init (Value, GType_String);
            Set_String (Value, "unknown");
      end case;
   end Get_Property;

The implementation of Get_Property is straightforward. It receives the identifier of the property and has to initialize the parameter Value with the value of the type of the property. Then it sets the property value into Value.

File gtk.cell_renderer_fixed.adb (continued):
--
-- Update -- The widget associated with the renderer
--
--    Cell   - The renderer
--    Widget - The widget it is used at
--
-- This procedure is used upon each call to either to render or to
-- evaluate the geometry of a cell. The renderer has no data associated
-- with any concrete cell of the tree view. It is called at random to
-- indicate all of them.
--

   procedure Update
             (  Cell   : in out Gtk_Cell_Renderer_Fixed_Record'Class;
                Widget : in out Gtk.Widget.Gtk_Widget_Record'Class
             )  is
      Text      : String (1..40);
      Start_Pos : Integer := Text'Last + 1;
      Point_Pos : Integer := Text'Last + 1;
      Right     : GInt    := Cell.Width - Cell.Max_Offset;
      Line      : GInt;
   begin
      if
Cell.Text = null then
         Cell.Text := Widget.Create_Pango_Layout;
      end if;
      Put (Text, Cell.Value, Cell.After, 0);
      for Index in reverse Text'Range loop
         -- Find the beginning of the number in the output string
        
if ' ' = Text (Index) then
            Start_Pos := Index + 1;
            exit;
         end if;
      end loop;
      for Index in Start_Pos..Text'Last loop
         -- Find the position of the decimal point in the output
        
if '.' = Text (Index) then
            Point_Pos := Index;
            exit;
         end if;
      end loop;
      Cell.Text.Set_Text (Text (Start_Pos..Text'Last));
      Cell.Text.Get_Pixel_Size (Cell.Width, Cell.Height);
      if Point_Pos <= Text'Last then
         Cell.Text.Index_To_Line_X
         (  GInt (Point_Pos - Start_Pos),
            False,
            Line,
            Cell.Left_Width
         );
         Cell.Left_Width := To_Pixels (Cell.Left_Width);
      else
         Cell.Left_Width := Cell.Width;
      end if;
      Cell.Max_Offset := GInt'Max (Cell.Left_Width, Cell.Max_Offset);
      Cell.Width :=
         (  Cell.Max_Offset
         +  GInt'Max (Right, Cell.Width - Cell.Left_Width)
         );
   end Update;

The procedure Update is used internally to evaluate the renderer's state. First it checks if the field Text is already initialized. If not, it creates it using Create_Pango_Layout call. Note that it cannot be made earlier, upon renderer construction, because Create_Pango_Layout requires a widget parameter. The procedure Finalize will destroy this field.

Then the value of the property value is rendered to text using the procedure Put. It is guaranteed UTF-8, so there is no need to care about any conversions from Latin-1 encoding. The next two loops determine where the output starts in the output string Text (the variable Start_Pos) and where the decimal point is located (the variable Point_Pos).

The rendered text is set into the field Text and its size in pixels is calculated. After that, Index_To_Line_X is used to calculate the horizontal offset to the point. The result is in units, so it is converted to pixels; before placing into Left_Width field. The value of Left_Width influences Max_Offset, which is the maximum of all Left_Widths seen.

Then the total width of the cell is calculated as the sum of the space required before the decimal point and after it. The former obviously is Max_Offset. The latter is the maximum the space required for the current value and one has been required before the call (stored Cell.Width - Cell.Max_Offset).

File gtk.cell_renderer_fixed.adb (continued):
   function Get_Size
            (  Cell   : not null access Gtk_Cell_Renderer_Fixed_Record;
               Widget : not null access Gtk.Widget.Gtk_Widget_Record'Class
            )  return Gdk_Rectangle is
   begin

      Update (Cell.all, Widget.all);
      return
      (  X      => 0,
         Y      => 0,
         Width  => Cell.Width,
         Height => Cell.Height
      );
   end Get_Size;

This variant of Get_Size is interested in only width and height of the rendered value. The implementation calls to Update and then returns the fields Width and Height.

File gtk.cell_renderer_fixed.adb (continued):
   function Get_Size
            (  Cell      : not null access Gtk_Cell_Renderer_Fixed_Record;
               Widget    : not null access Gtk.Widget.Gtk_Widget_Record'Class;
               Cell_Area : Gdk_Rectangle
            )  return Gdk_Rectangle is
   begin

      Update (Cell.all, Widget.all);
      return
      (  X      => GInt
                   (  Get_X_Align (Cell)
                   *  GFloat (Cell_Area.Width - Cell.Width)
                   ),
         Y      => GInt
                   (  Get_Y_Align (Cell)
                   *  GFloat (Cell_Area.Height - Cell.Height)
                   ),
         Width  => Cell.Width,
         Height => Cell.Height
      );
   end Get_Size;

This variant is a little bit more complex because it specifies the surrounding rectangle. Again, Update is called and the positions of the left top corner are evaluated using alignment properties of the renderer.

File gtk.cell_renderer_fixed.adb (continued):
   function Get_Type return Gtk_Type is
      use
Gtk.Cell_Renderer.Abstract_Renderer;
   begin
      if Renderer_Type = GType_Invalid then
         Renderer_Type :=
            Register ("GtkCellRendererFixed", Class_Init'Access);
      end if;
      return Renderer_Type;
   end Get_Type;

The function Get_Type checks if the renderer's GTK+ type is not yet registered and if so, then registers it by calling to Register of Gtk_Abstract_Renderer_Record. Two parameters of the function Register are the name of the GTK+ class and the class initialization procedure. Class_Init described above is used for the second.

File gtk.cell_renderer_fixed.adb (continued):
   procedure Gtk_New
             (  Cell  : out Gtk_Cell_Renderer_Fixed;
                After : Natural := 0
             )  is
   begin

      Cell := new Gtk_Cell_Renderer_Fixed_Record;
      Initialize (Cell, After);
   end Gtk_New;

   procedure Initialize
             (  Cell  : not null access
                      
 Gtk_Cell_Renderer_Fixed_Record'Class;
                After : Natural
             )  is
      use
Gtk.Cell_Renderer.Abstract_Renderer;
   begin

      Initialize (Cell, Get_Type);
      Cell.After := After;
   end Initialize;

The implementation of Gtk_New allocates the object and calls to Initialize. The first thing Initialize has to do is to call parent's Initialize of Gtk_Abstract_Renderer_Record. The second parameter of it is the renderer's type. So it calls to Get_Type, which in turn registers the GTK+ type as necessary.

File gtk.cell_renderer_fixed.adb (continued):
   procedure Render
             (  Cell    : not null access Gtk_Cell_Renderer_Fixed_Record;
                Context : Cairo_Context;
                Widget  : not null access Gtk_Widget_Record'Class;
                Background_Area : Gdk_Rectangle;
                Cell_Area       : Gdk_Rectangle;
                Flags           : Gtk_Cell_Renderer_State
             )  is
      Area  : Gdk_Rectangle     := Cell.Get_Size (Widget, Cell_Area);
      Style : Gtk_Style_Context := Get_Style_Context (Widget);
   begin
      Save (Context);
      Rectangle
      (  Context,
         GDouble (Cell_Area.X),
         GDouble (Cell_Area.Y),
         GDouble (Cell_Area.Width),
         GDouble (Cell_Area.Height)
      );
      Clip (Context);
      Render_Layout
      (  Style,
         Context,
         Get_Text_GC (Get_Style (Widget), Text_State),
         (  Cell_Area.X
         +  GInt (Get_X_Pad (Cell))
         +  Area.X
         +  (Cell.Max_Offset - Cell.Left_Width)
         ),
         (  Cell_Area.Y
         +  GInt (Get_Y_Pad (Cell))
         +  Area.Y
         ),
         Cell.Text
      );
      Restore (Context);
   end Render;

The implementation of Render first calls to Get_Size to update the renderer's state and get the rectangle where the value has to be drawn into. The current style context of the widget is stored in Style. The drawing context is saved. Then the clipping rectangle determined by the parameter Cell_Area is set in the context. After that Render_Layout is called to draw the text of the field Text. The position of the left-top corner of the output is determined by the Cell_Area parameter of the procedure Render. Get_X_Pad and Get_Y_Pad are called to obtain actual padding. Area.X and Area.Y are returned by Get_Size and relative to the corner. The horizontal offset should be additionally adjusted to the difference between the maximal width of the output field before the decimal point and the width of the rendered text of the current value. Finally the context is restored.

File gtk.cell_renderer_fixed.adb (continued):
   procedure Set_Property
             (  Cell          : not null access Gtk_Cell_Renderer_Fixed_Record;
                Param_ID      : Property_ID;
                Value         : GValue;
                Property_Spec : Param_Spec
             )  is
   begin
      case
Param_ID is
         when
Value_ID =>
            Cell.Value := Get_Double (Value);
         when After_ID =>
            Cell.After := Integer (Get_UInt (Value));
         when others =>
            null;
      end case;
   end Set_Property;

The procedure Set_Property is reverse to Get_Property described above.

File gtk.cell_renderer_fixed.adb (continued):
   function Start_Editing
            (  Cell   : not null access Gtk_Cell_Renderer_Fixed_Record;
               Event  : Gdk_Event;
               Widget : not null access Gtk_Widget_Record'Class;
               Path            : UTF8_String;
               Background_Area : Gdk_Rectangle;
               Cell_Area       : Gdk_Rectangle;
               Flags           : Gtk_Cell_Renderer_State
            )  return Gtk_Widget is
  
   Editor    : Gtk_Entry;
      Text      : String (1..40);
      Start_Pos : Integer := Text'Last + 1;
   begin
  
   Put (Text, Cell.Value, Cell.After, 0);
      for
Index in reverse Text'Range loop
         -- Find the beginning of the number in the output string
         if ' ' = Text (Index) then
    
       Start_Pos := Index + 1;
            exit
;
         end if
;
      end loop
;

The procedure Start_Editing is called upon editing request. For example when a cell is doubly clicked. First the renderer formats a string with the current value of the cell. The parameters of Start_Editing are similar to ones of Render. The additional parameter Path identifies the row the cell being edited belongs to. You don't need to store this string because the base type does it for you. Get_Path can be later used to obtain it. First, Start_Editing stores the current value in Text (1..Start_Pos).

File gtk.cell_renderer_fixed.adb (continued):
      Gtk_New (Editor);
      Set_Property (Editor, Build ("xalign"), Get_X_Align (Cell));
      Set_Property (Editor, Build ("has-frame"), False);
      Editor.Set_Text (Text (Start_Pos..Text'Last));
      Select_Region (Editor, 0, -1);
      Entry_Callbacks.Connect
      (  Editor,
         "editing_done",
         Entry_Callbacks.To_Marshaller (Editing_Done'Access),
         Cell.all'Access
      );
      Cell.Focus_Out :=
         Entry_Return_Callbacks.Connect
         (  Editor,
            "focus_out_event",
            Entry_Return_Callbacks.To_Marshaller (Focus_Out'Access),
            Cell.all'Access
         );
      Editor.Show;
      return
Editor.all'Access;
   end
Start_Editing;
end Gtk.Cell_Renderer_Fixed;

Then an entry widget is created and the text is set into the widget. Some additional settings are applied to the widget. Its horizontal alignment is set from the corresponding renderer's property. Its frame is removed. The content is selected (Select_Region). Then Editing_Done and Focus_Out are connected to the widget. Finally, it is shown and returned. Note that there is no need to care about removing the widget, it is a responsibility of the caller.

2.4.2. Test program

The following small program illustrates use of the fixed point renderer.

File test_gtk_fixed.adb:

with Ada.Numerics.Float_Random;  use Ada.Numerics.Float_Random;
with GLib;                       use GLib;
with GLib.Properties;            use GLib.Properties;
with GLib.Values;                use GLib.Values;
with Gtk.Enums;                  use Gtk.Enums;
with Gdk.Event;                  use Gdk.Event;
with Gtk.List_Store;             use Gtk.List_Store;
with Gtk.Widget;                 use Gtk.Widget;
with Gtk.Window;                 use Gtk.Window;
with Gtk.Cell_Renderer_Fixed;    use Gtk.Cell_Renderer_Fixed;
with Gtk.Cell_Renderer_Text;     use Gtk.Cell_Renderer_Text;
with Gtk.Tree_View_Column;       use Gtk.Tree_View_Column;
with Gtk.Tree_Model;             use Gtk.Tree_Model;
with Gtk.Tree_View;              use Gtk.Tree_View;
with Gtk.Scrolled_Window;        use Gtk.Scrolled_Window;

with Ada.Unchecked_Conversion;
with
Gtk.Main;
with Gtk.Missed;
with Test_Gtk_Fixed_Handlers;

procedure Test_Gtk_Fixed is

   Window     : Gtk_Window;
   Table_View : Gtk_Tree_View;
   Scroller   : Gtk_Scrolled_Window;

   type Local_Callback is access procedure
        (  Cell  : access Gtk_Cell_Renderer_Fixed_Record'Class;
           Store : Gtk_List_Store
        );
   function "+" is
      new
Ada.Unchecked_Conversion
          (  Local_Callback,
             Test_Gtk_Fixed_Handlers.Simple_Handler
          );

   procedure Commit
             (  Cell  : access Gtk_Cell_Renderer_Fixed_Record'Class;
                Store : Gtk_List_Store
             )  is
      Row : Gtk_Tree_Iter :=
         Get_Iter_From_String (Store, Get_Path (Cell));
      Value : GValue;
   begin
      if Row /= Null_Iter then
         Init (Value, GType_Double);
         Set_Double (Value, Get_Property (Cell, Build ("value")));
         Set_Value (Store, Row, 0, Value);
         Unset (Value);
      end if;
   end Commit;

begin
   Gtk.Main.Init;
   Gtk.Window.Gtk_New (Window);
   Window.Set_Title ("Test Fixed-Point Cell Renderer");
   Window.On_Delete_Event (Gtk.Missed.Delete_Event_Handler'Access);
   Window.On_Destroy (Gtk.Missed.Destroy_Handler'Access);
   Gtk_New (Scroller);
   Gtk_New (Table_View);

The above is mostly standard GTK+ initialization stuff, except the procedure Commit and instantiation of User_Callback for it. The variables Table_View is a tree view widget and its scroll bar. The procedure Commit is attached to the renderer to store editing changes into the list store. It uses Get_Iter_From_String applied to Get_Path to obtain the iterator of the edited row. Then it queries the value from the renderer and stores it into the first column of the row. The package Test_Gtk_Fixed_Handlers is the following instantiation of event handlers:

File test_gtk_fixed_handlers.ads:

with Gtk.Cell_Renderer_Fixed;  use Gtk.Cell_Renderer_Fixed;
with Gtk.List_Store;           use Gtk.List_Store;

with Gtk.Handlers;

package Test_Gtk_Fixed_Handlers is
   new
Gtk.Handlers.User_Callback
       (  Gtk_Cell_Renderer_Fixed_Record,
          Gtk_List_Store
       );

File test_gtk_fixed.adb (continued):

   -- Creating a column of numbers (list store)
   declare
      Table : Gtk_List_Store;
      declare
         Row    : Gtk_Tree_Iter := Null_Iter;
         Value  : GValue;
         Source : Generator;
      begin
         Init (Value, GType_Double);
         Gtk_New (Table, (0 => GType_Double));
         -- Filling the column with random numbers
         for Item in 1..1000 loop
            Table.Append (Row);
            Set_Double
            (  Value,
               GDouble (100.0 * (Random (Source) - 0.5))
            );
            Set_Value (Table, Row, 0, Value);
         end loop;
         -- Attaching the column store to its view
         Table_View.Set_Model (To_Interface (Table));
         Unset (Value);
      end;

This fragment creates a list store (Table) consisting of one column of GDouble data. The column is filled with randomly generated numbers from in the range -50..50. Finally the store is attached to the widget.

File test_gtk_fixed.adb (continued):

      -- Creating columns in the view
      declare
         Column_No : GInt;
         Column    : Gtk_Tree_View_Column;
         Numeric   : Gtk_Cell_Renderer_Fixed;
         Text      : Gtk_Cell_Renderer_Text;
      begin
         -- The first column will use the fixed-point renderer
         Gtk_New (Column);
         Column.Set_Title ("Value");
         Gtk_New (Numeric, 3);
         Numeric.Set_Mode (Cell_Renderer_Mode_Editable);
         Commit_Handlers.Connect
         (  Numeric,
            "commit",
            Commit'Access,
            Table
         );
         Column.Pack_Start (Numeric, False);
         -- Map column's renderer to the table's column 0
         Column.Add_Attribute (Numeric, "value", 0);
         Column_No := Table_View.Append_Column (Column);
         Column.Set_Resizable (True);
         Column.Set_Sort_Column_Id (0);

         -- The second column uses the standard text renderer
  
      Gtk_New (Column);
         Column.Set_Title ("Text");
         Gtk_New (Text);
         Column.Pack_Start (Text, True);
         -- Map column's renderer to the table's column 0
         Column.Add_Attribute (Text, "text", 0);
         Column_No := Table_View.Append_Column (Column);
         Column.Set_Resizable (True);
         Column.Set_Sort_Column_Id (0);
      end;
   end;

Here the two columns are added to the tree view widget. The first column uses Gtk_Cell_Renderer_Fixed to render the first column of the list store. Note that Add_Attribute refers to the property value of the renderer. The renderer is set to editable mode using Set_Mode. The procedure Commit is connected to the commit signal of the renderer. The second column uses the standard text renderer to render the same first column of the store.

File test_gtk_fixed.adb (continued):

   Scroller.Set_Policy (Policy_Automatic, Policy_Automatic);
   Scroller.Add (Table_View);
   Window.Add (Scroller);

   Table_View.Show;
   Scroller.Show;
   Window.Show;
   Gtk.Main.Main;
end Test_Gtk_Fixed;

Finally the scroll bar is added to the widget, all things are shown and messages loop is entered. The result might look like:

cell renderer fixed

2.6. Columned model

The package Gtk.Tree_Model.Columned_Store provides a derived tree model. The model contains columns of the reference model composed in n columns. When the reference model itself has m columns then the derived model will have total n·m columns. The cells of the reference model are arranged top-bottom, left-to-right as shown on the figure:

Reference model,
m=3
        Derived columned model,
with n=3 major columns
a1 b1 c1
a2 b2 c2
a3 b3 c3
a4 b4 c4
a5 b5 c5
a6 b6 c6
a7 b7 c7
a8 b8 c8
 
a1 b1 c1 a4 b4 c4 a7 b7 c7
a2 b2 c2 a5 b5 c5 a8 b8 c8
a3 b3 c3 a6 b6 c6      

The model is flat as a list and contains the immediate descendants of a node from the reference model. Note also the model itself does not have means to manipulate its content. When it is necessary to modify the content, the reference model is dealt with. The columned model will automatically follow the changes made on the reference model. This includes translation of the reference model signals into ones of the columned model. For example reference model row removal may manifest itself as a series of columned model signals like row changing and row deletion. Additionally to the standard signals of a tree model the signal root-changed is emitted immediately after changing the root of the columned store. This may happen, for example, when the root of the columned model is deleted from the reference one. That causes it to change to the most nested ancestor node.

type Gtk_Columned_Store_Record is
   new
Gtk_Abstract_Model_Record with private;
type
Gtk_Columned_Store is
   access all
Gtk_Columned_Store_Record'Class;

The following subprograms are defined in the package:

function From_Columned
         (  Model  : not null access Gtk_Columned_Store_Record;
            Iter   : Gtk_Tree_Iter;
            Column : Positive
         )  return Gtk_Tree_Iter;
function
From_Columned
         (  Model  : not null access Gtk_Columned_Store_Record;
            Path   : Gtk_Tree_Path;
            Column : Positive
         )  return Gtk_Tree_Path;

These functions convert an iterator or path of the columned model to the corresponding iterator or path of the reference model. The additional parameter is the major column number 1..n, where n is the number of columns specified upon model creation in Gtk_New. The result is Null_Iter or null path on an error. Note that the returned path has to be freed using Path_Free.

function Get_Column_Height
         (  Model  : not null access Gtk_Columned_Store_Record;
            Column : Positive
         )  return Natural;

This function returns the number of filled rows in the major column Column. The result is 0 when Column is greater than the number of major columns.

function Get_Major_Columns
         (  Model : not null access Gtk_Columned_Store_Record
         )  return Positive;

This function returns the number of major columns, i.e. the parameter Columns as it was specified upon model creation in Gtk_New or Set_Reference.

function Get_Reference
         (  Model : not null access Gtk_Columned_Store_Record
         )  return Gtk_Tree_Model;

This function returns the reference model.

function Get_Reference_Iter
         (  Model  : not null access Gtk_Columned_Store_Record;
            Row    : Positive;
            Column : Positive
         )  return Gtk_Tree_Iter;

This function composes an iterator to the reference model row specified by its Row and Column. The result is Null_Iter when Row and Column do not specify a reference model row.

function Get_Root
         (  Model : not null access Gtk_Columned_Store_Record
         )  return Gtk_Tree_Iter;

This function returns an iterator of reference model to the root of the derived model. All nodes of the derived model are immediate descendants of.

function Get_Root
         (  Model : not null access Gtk_Columned_Store_Record
         )  return Gtk_Tree_Path;

This function returns the path in reference model to the root of the derived model. The result shall be freed using Path_Free if not null.

function Get_Rows
         (  Model  : not null access Gtk_Columned_Store_Record;
            Filled : Boolean
         )  return Natural;

This function returns the number of rows. When the parameter Filled is true, only complete rows count. Otherwise any does.

function Get_Row_Width
         (  Model : not null access Gtk_Columned_Store_Record;
            Row   : Positive
         )  return Natural;

This function returns the number of filled columns in the row Row. The result is 0 when Row is greater than the number of rows.

procedure Gtk_New
          (  Model     : out Gtk_Columned_Store;
             Reference : not null access Gtk_Root_Tree_Model_Record'Class;
             Columns   : Positive;
             Root      : Gtk_Tree_Iter := Null_Iter
          );

The model is constructed by specifying the reference model, the number of columns and the derived model's root (the parameter Root). By default the root is one of the reference model. The derived model will contain only immediate children on Root.

procedure Gtk_New (Model : out Gtk_Columned_Store);

This variant construct an empty model which can be later bound to a reference model using Set_Reference.

procedure Initialize
          (  Model     : not null access Gtk_Columned_Store_Record'Class;
             Reference : not null access Gtk_Root_Tree_Model_Record'Class;
             Columns   : Positive;
             Parent    : Gtk_Tree_Iter
          );
procedure
Initialize (Model : access Gtk_Columned_Store_Record'Class);

One of these procedures is to be called by any derived type from its Initialize.

function Is_Ancestor
         (  Model : not null access Gtk_Columned_Store_Record;
            Iter  : Gtk_Tree_Iter
         )  return Boolean;
function
Is_Ancestor
         (  Model : not null access Gtk_Columned_Store_Record;
            Path  : Gtk_Tree_Iter
         )  return Boolean;

These functions return true if the root of the columned model is an ancestor of the iterator or path specified in the reference model.

function Is_Descendant
         (  Model : not null access Gtk_Columned_Store_Record;
            Iter  : Gtk_Tree_Iter
         )  return Boolean;
function
Is_Descendant
         (  Model : not null access Gtk_Columned_Store_Record;
            Path  : Gtk_Tree_Iter
         )  return Boolean;

These functions return true if the root of the columned model is a descendant of the iterator or path in the reference model.

function To_Columned
         (  Model : not null access Gtk_Columned_Store_Record;
            Iter  : Gtk_Tree_Iter
         )  return Gtk_Tree_Iter;
function To_Columned
         (  Model : not null access Gtk_Columned_Store_Record;
            Path  : Gtk_Tree_Path
         )  return Gtk_Tree_Path;

These functions convert an iterator or path of the reference model to the corresponding iterator or path of the columned model. The result is Null_Iter or null path on an error. Note that the returned path has to be freed using Path_Free.

procedure To_Columned
          (  Model  : not null access Gtk_Columned_Store_Record;
             Iter   : in out Gtk_Tree_Iter;
             Column : out Positive
          );

This procedure is a variant of iterator conversion which also yields the major column number 1..n, where n is the number of columns specified upon model creation in Gtk_New.

procedure Set_Null_Reference
          (  Model : not null access Gtk_Columned_Store_Record;
             Root_Changed : Boolean := True
          );

This procedure makes the model empty. An empty model has no reference model associated with. The parameter Root_Changed causes root-changed emitted when Model there had a reference model. This procedure can be used if the reference model have to undergo massive changes you don't want to follow one by one in the columned model. The columned model can be detached using this procedure, then changes can be applied and, finally the columned model is reattached again using Set_Reference.

procedure Set_Reference
          (  Model     : not null access Gtk_Columned_Store_Record;
             Reference : not null access Gtk_Root_Tree_Model_Record'Class;
             Columns
   : Positive;
             Root      : Gtk_Tree_Iter
          );

This procedure changes the model, the number of columns and the root. One should use this procedure with care, because clients of the columned model might be unprepared to the changes in columns number and types. When the root or the reference model is indeed changed root-changed is emitted.

procedure Set_Root
          (  Model : not null access Gtk_Columned_Store_Record;
             Root  : Gtk_Tree_Iter
          );

This procedure changes the model root. When the root is indeed changed, root-changed is emitted.

2.7. Extension model

The package Gtk.Tree_Model.Extension_Store provides a derived tree model. The model extends its reference model by adding new columns to it:

Reference model,
columns a, b, c
 
        Derived model,
new columns d, e
a1 b1 c1
a2 b2 c2
a3 b3 c3
a4 b4 c4
 
a1 b1 c1 d1 e1
a2 b2 c2 d2 e2
a3 b3 c3 d3 e3
a4 b4 c4 d4 e4

The reference model itself is not changed, it is the derived model which keeps new columns data. It is possible both to derive multiple extension models adding different columns to the same reference model, as well as to use an extension model as a reference one with adding new columns to it. Internally the derived model is a tree store containing new columns. The extended model does not have its own row insertion and deletion operations. Instead of this the rows are manipulated in the reference model. The effect of these operations mirrors on all extended models of. When the reference model rows get inserted, their values in the extended columns can be set using Set_Extension. For this the reference model iterator should be converted to an iterator of the extension model with To_Extension. When the reference model rows get deleted, the corresponding cells of the extension model as removed automatically. This model translates the reference model signals into ones of the extension model. Thus handlers of row-changed, row-inserted, row-deleted etc can be directly used on the extension model.

type Gtk_Extension_Store_Record is
   new
Gtk_Abstract_Model_Record with private;
type
Gtk_Extension_Store is
   access all
Gtk_Extension_Store_Record'Class;

The following subprograms are defined in the package:

procedure Changed
          (  Model : not null access Gtk_Extension_Store_Record;
             Path  : Gtk_Tree_Path;
             Iter  : Gtk_Tree_Iter
          );

This procedure is called upon row change in the reference model. An implementation can override this procedure to modify extension columns using an appropriate call to Set_Extension. Alternatively it can handle row-changed signal which the provided implementation of this procedure emits. The parameters Path and Iter identify the row in the extension model.

procedure Deleted
          (  Model : not null access Gtk_Extension_Store_Record;
             Path  : Gtk_Tree_Path
          );

This procedure is called when a reference model row has been deleted. The parameter Path is a (now invalid) path to the deleted row in the extension model. It cannot be used anymore. The default implementation emits the signal row-deleted. When overriding this procedure carefully consider calling this one from there.

procedure Deleting
          (  Model : not null access Gtk_Extension_Store_Record;
             Path  : Gtk_Tree_Path;
             Iter  : Gtk_Tree_Iter
          );

This procedure is called upon row deletion. Differently to Delete it is called just before deleting the extension row. An implementation shall not modify either the reference or the extension model here. The parameters Path and Iter identify the row being deleted in the extension model. Note that they cannot be converted to the reference model or used to access it in any other way, because the corresponding row in it is already deleted there. Also at this point the extension store and its reference model are unsynchronized so it makes usually no sense to access the reference model anyway. The primary objective of this procedure is to save the data of the extension columns upon deletion. The default implementation does nothing.

function From_Extension
         (  Model : not null access Gtk_Extension_Store_Record;
            Iter  : Gtk_Tree_Iter
         )  return Gtk_Tree_Iter;
function From_Extension
         (  Model : not null access Gtk_Extension_Store_Record;
            Path  : Gtk_Tree_Path
         )  return Gtk_Tree_Path;

These functions convert an iterator or path of the extension model to an iterator or path in the reference model. Note that the returned path has to be freed using Path_Free.

function Get_Extension_Types
         (  Model : not null access Gtk_Extension_Store_Record
         )  return GType_Array;

This function returns the types of the extension columns. When the result is not empty, its bounds are set so that the array indices correspond to zero-based column numbers (as in tree model).

function Get_Reference
         (  Model : not null access Gtk_Extension_Store_Record
         )  return Gtk_Tree_Model;

This function returns the reference model.

procedure Gtk_New
          (  Model     : out Gtk_Extension_Store;
             Reference : not null access Gtk_Root_Tree_Model_Record'Class;
             Types     : GType_Array
          );

This procedure creates a new extension model. The result is returned via the parameter Model. The parameter Reference is the reference model. The parameter Types is an array of the extension columns types. For each element of the array a column of the corresponding type is added.

procedure Gtk_New
          (  Model : out Gtk_Extension_Store;
             Types : GType_Array
          );

This variant creates an empty model. It can get a reference model assigned later using Set_Reference.

procedure Initialize
          (  Model     : not null access Gtk_Extension_Store_Record'Class;
             Reference : not null access Gtk_Root_Tree_Model_Record'Class;
             Types     : GType_Array
          );
procedure
Initialize
          (  Model : not null access Gtk_Extension_Store_Record'Class;
             Types : GType_Array
          );

One of these procedures has to be called by any derived type from its Initialize.

procedure Inserted
          (  Model : not null access Gtk_Extension_Store_Record;
             Path  : Gtk_Tree_Path;
             Iter  : Gtk_Tree_Iter
          );

This procedure is called upon row insertion in the reference model. An implementation can override this procedure to initialize extension columns using an appropriate call to Set_Extension. Alternatively it can handle row-inserted signal which the provided implementation of this procedure emits. The parameters Path and Iter identify the row in the extension model. When overriding this procedure carefully consider calling this one from there.

procedure Set_Extension
          (  Model  : not null access Gtk_Extension_Store_Record'Class;
             Iter   : Gtk_Tree_Iter;
             Column : Positive;
             Value  : Boolean
          );
procedure Set_Extension
          (  Model  : not null access Gtk_Extension_Store_Record'Class;
             Iter   : Gtk_Tree_Iter;
             Column : Positive;
             Value  : GInt
          );
procedure Set_Extension
          (  Model  : not null access Gtk_Extension_Store_Record'Class;
             Iter   : Gtk_Tree_Iter;
             Column : Positive;
             Value  : UTF8_String
          );
procedure Set_Extension
          (  Model  : not null access Gtk_Extension_Store_Record'Class;
             Iter   : Gtk_Tree_Iter;
             Column : Positive;
             Value  : GValue
          );

These procedures are used to modify the extended model cells. The parameter Iter is an extension store iterator to the row of the cell. The parameter Column is the number of the extension column of the cell. The parameter Value is the value to set. Note that there is no universal way to change the reference model cells. That depends on the reference model type. When the type is known, the the reference model cell can be modified using the corresponding operations of the type with the iterator converted to the reference model iterator (see To_Extension).

procedure Set_Null_Reference
          (  Model : not null access Gtk_Extension_Store_Record
          );

This procedure sets the reference model empty. This can be used to before undertaking massive changes in the reference model. First the reference model is set to null, then changes are applied and finally Set_Reference is used to assign the reference model back.

procedure Set_Reference
          (  Model     : not null access Gtk_Extension_Store_Record;
             Reference : not null access Gtk_Root_Tree_Model_Record'Class
          );

This procedure changes the reference model. The side effect of this operation is that the extension columns become empty. The new reference model should have exactly same types of columns as its predecessor, because clients using the model might not anticipate column number and types change.

function To_Extension
         (  Model : not null access Gtk_Extension_Store_Record;
            Iter  : Gtk_Tree_Iter
         )  return Gtk_Tree_Iter;
function To_Extension
         (  Model : not null access Gtk_Extension_Store_Record;
            Path  : Gtk_Tree_Path
         )  return Gtk_Tree_Path;

These functions convert an iterator or path of the reference model to an iterator or path to the corresponding row in the extension model. Note that the returned path has to be freed using Path_Free.

2.8. Abstract browser model and widgets

The package Gtk.Abstract_Browser provides an abstract model of a caching tree browsing model. The model contains directories of items physically stored outside the model. Browsing the items is accomplished through primitive operations to interface an external items store, such as a file system for instance or a database. The model caches items as necessary, transparently to the tree views rendering the model. The policy of caching can vary and is controlled by concrete implementations of the model. A typical application example is a model of a file system. A tree view widget rendering the model will cause the file system directories cached when expanded in the tree view.

The package also provides two specialized tree view widgets for rendering the directories tree and the items of a directory.

2.8.1. Abstract caching store

The type of the caching store is:

type Gtk_Abstract_Directory_Record is
   abstract new
Gtk_Tree_Model_Record with private;
type Gtk_Abstract_Directory is
   access all
Gtk_Abstract_Directory_Record'Class;

It is a tree model with the abstract primitive operations implemented in order to access the items of. The items are uniquely identified by their full names globally or else by their simple names within a directory. The data types for the item names are;

type Item_Name is new UTF8_String;
type Item_Path is new UTF8_String;

The subprograms of the package do not interpret the content of objects of these types, they are transparently passed as is. The following requirements are imposed on paths and names:

type Item_Type is new UTF8_String;

This type characterizes an item. It can be the name of a stock image used to indicate the item type, as a directory, executable file etc.

type Directory_Item
     (  Name_Length : Natural;
        Kind_Length : Natural
     )  is
record

   Policy    : Caching_Policy;
   Directory : Boolean;
   Name      : Item_Name (1..Name_Length);
   Kind      : Item_Type (1..Kind_Length);
end record;

This type is used for querying items. Its fields are as follows:

The model has three columns:

  1. GType_String is Item_Type converted to UTF8_String;
  2. GType_String is Item_Name converted to UTF8_String;
  3. GType_Int is in 0..2 when the item is a directory and 3 otherwise.

It contain only directory items. So when viewed using a tree view it will show the cached items directory tree. An unfiltered tree model of all cached items can be obtained from the model using Get_Tree_Store. That model contains all cached items and the same columns as Gtk_Abstract_Directory. Both represent different view of the same cache.

Abstract_Directory_Class_Name : constant String :=
   "GtkAbstractDirectory";

This string constant defines the GTK+ class name of the model.

type Icon_Type is (Stock_ID, GIcon, Pixbuf, Themed);
type Icon_Data (Kind : Icon_Type; Length : Natural) is record
   case
Kind is
      when
Stock_ID | Themed =>
         Name : String (1..Length);
      when GIcon =>
         Icon : GObject;
      when Pixbuf =>
         Image : Gdk_Pixbuf;
    end case;
end record;

This type is used to return icons of items. The discriminant Kind defines the icon type:

Abstract primitive operations. The following abstract primitive operations have to be implemented by a derived type:

function Compare
         (  Store     : not null access Gtk_Abstract_Directory_Record;
            Directory : Item_Path;
            A, B      : Directory_Item;
            By_Name   : Boolean
         )  return Row_Order is abstract;

This function is used to sort items of a directory. The parameter Directory is the path of the directory containing the items A and B being compared. The parameter By_Name when true instructs to ignore anything but the item names. The result has the type Row_Order.

function Get_Directory
         (  Store : not null access Gtk_Abstract_Directory_Record;
            Item  : Item_Path
         )  return Item_Path is abstract;

This function obtains the containing directory path from Item. Name_Error is propagated when Item has no parent.

function Get_Name
         (  Store : not null access Gtk_Abstract_Directory_Record;
            Item  : Item_Path
         )  return Item_Name is abstract;

This function obtains the item name by its path Item.

function Get_Path
         (  Store     : not null access Gtk_Abstract_Directory_Record;
            Directory : Item_Path;
            Name      : Item_Name
         )  return Item_Path is abstract;

This function composes a path from the directory path and the item name in the directory.

procedure Progress
          (  Store     : not null access Gtk_Abstract_Directory_Record;
             Directory : Item_Path;
             State     : GDoubleRead
          );

This procedure is called to indicate the progress of a caching operation. Directory is the path of the folder being cached. State is the overall progress. The default operation emits the signal progress. Note that the procedure is no called to reflect every change. Too frequent occurrences are filtered out. however it is always called when State reaches 1.0.

function Read
         (  Store : not null access Gtk_Abstract_Directory_Record
         )  return Directory_Item is abstract;

This function returns the next item of the directory for which Rewind was called before. The result is the item found. The internal cursor is advanced to the item. When an implementation detects an error, it has several options to handle this. It can

Giving any error messages is the responsibility of Read not the caller. The procedures from the package never call Read without calling Rewind before it. It is also never called so that several directories could be browsed simultaneously. So an application need not to keep any history for more than one directory search. The field Policy of the result returned by Read controls caching of directories:

function Rewind
         (  Store     : not null access Gtk_Abstract_Directory_Record;
            Directory : Item_Path
         )  return Directory_Item is abstract;

This function is called before Read to initiate a new directory search. An implementation typically prepares iteration of the directory specified by its path Directory. It is guaranteed that no nested or multiple iterations happen. When the parameter Directory is an empty string, the cursor has to be set to the first root item (of the root directory). Otherwise it is set to the first item in the directory. The cursor is implementation maintained. The function returns the new state of the directory being iterated. (The first item of will be returned by the consequent Read.) Usually the returned state does not change and the implementation can return the predefined constant:

Directory_Entered : constant Directory_Item := ...

But in some cases an implementation might wish to change the directory type in order to show a different icon for a mounted volume, for example. In such cases the result's policy is interpreted as follows:

When access to the directory requires credentials or some user action, then Rewind is a place to ask the user for. When such request fails, due to cancellation, for example, then Cache_Never can be returned. When Data_Error exception is propagated out of Rewind, the corresponding item is removed from the cache.

Primitive operations:

procedure Finalize
          (  Store : not null access Gtk_Abstract_Directory_Record
          );

This subprogram has to be called upon destruction when overridden.

function Get_Cached
         (  Store : not null access Gtk_Abstract_Directory_Record;
            Path  : Item_Path
         )  return Directory_Item;

This function returns description of an already cached item by its path. Constraint_Error is propagated when Path does not specify a cached item. Name_Error is propagated when Path is illegal.

function Get_Tree_Store
         (  Store : not null access Gtk_Abstract_Directory_Record
         )  return Gtk_Tree_Store;

This function returns a tree store of the cached directory items. It contains all items of, both directories and leaf items. The model can be modified in order to add and remove items, though a safer way to do it is to use Created, Deleted and Refresh calls. This model is referenced by the model Store and thus it should not be referenced or unreferenced using Ref or Unref.

procedure Read_Error
          (  Store : access Gtk_Abstract_Directory_Record;
             Text  : UTF8_String;
             Path  : Item_Path
          );

This procedure emits read-error signal.

procedure Rewind_Error
          (  Store : not null access Gtk_Abstract_Directory_Record;
             Text  : UTF8_String;
             Path  : Item_Path
          );

This procedure emits rewind-error signal.

procedure Trace
          (  Store : not null access Gtk_Abstract_Directory_Record;
             Depth : Natural;
             Text  : String
          );

This procedure is called to trace certain actions. The parameter Depth is the depth of recursion, which can be used to decorate Text. The default implementation calls to Trace.

Class-wide operations:

procedure Cache
          (  Store : not null access Gtk_Abstract_Directory_Record'Class;
             Item  : Item_Path
          );

This procedure  caches the path to the item specified by its path. The directory structure is queried as necessary and cached. The root directory full name is empty string.

procedure Changed
          (  Store     : not null access Gtk_Abstract_Directory_Record'Class;
             Directory : Item_Path
          );

This procedure synchronizes the cache with the directory. The parameter Directory is the path of the directory changed. This procedure is used when the application gets aware of some, usually massive changes in the directory structure made from outside. In that case it uses Changed to resynchronize the store with it.

procedure Created
          (  Store     : not null access Gtk_Abstract_Directory_Record'Class;
             Directory : Item_Path;
             Item      : Directory_Item
          );

This procedure is called to synchronize the store when a new item gets inserted from outside. The parameter Item describes the item created. The parameter Directory is the path of the directory of. For the root directory items the parameter is an empty string. An alternative to Created is refreshing the cache at the directory containing the inserted item (see Changed). The latter might be preferable upon massive items insertions.

procedure Deleted
          (  Store : not null access Gtk_Abstract_Directory_Record'Class;
             Item  : Item_Path
          );

This procedure is called to synchronize the store when an item gets deleted from outside. Item is the path of the deleted item. The following code snippet illustrates moving an item from one directory to another with cache notification:

declare
   Old_Path : Item_Path := Get_Path (Store, Old_Directory, Name);
   Item     : Directory_Item := Get_Cached (Store, Old_Path);
begin
   ... -- Renaming the item using some external means
   Deleted (Store, Old_Path);            -- Removed at old directory
   Created (Store, New_Directory, Item); -- Added at the new directory
end;

function Get_Depth
         (  Store : not null access Gtk_Abstract_Directory_Record'Class
         )  return Natural;

This function returns depth of nesting calls while caching is active.

function Get_Tracing
         (  Store : not null access Gtk_Abstract_Directory_Record'Class
         )  return Traced_Actions;

This function returns the current state of tracing.

procedure Initialize
          (  Store : not null access Gtk_Abstract_Directory_Record'Class
          );

This procedure is to called upon initialization by the derived type upon object construction.

procedure Renamed
          (  Store    : not null access Gtk_Abstract_Directory_Record'Class;
             Old_Path : Item_Path;
             New_Name : Item_Name
          );

This procedure is called to synchronize the store when an item has been renamed outside while it stays in the same directory. The parameter Old_Path identifies the item. New_Nam is the new name of.

procedure Set_Tracing
          (  Store   : not null access Gtk_Abstract_Directory_Record'Class;
             Tracing : Traced_Actions
          );

This procedure changes tracing status. The parameter Tracing defines which actions need to be traced.

Signals. There are additional to standard tree model signals which Gtk_Abstract_Disrectory can emit:

2.8.2. Directory tree view

The package Gtk.Abstract_Browser defines the type of a specialized tree view widget for indication of the directory tree of a Gtk_Abstract_Directory store:

type Gtk_Directory_Tree_View_Record is
   new
Gtk_Tree_View_Record with private;
type Gtk_Directory_Tree_View is
   access all
Gtk_Directory_Tree_View_Record'Class;

The tree view filters shows only directories. It has single selection mode. The following operations are defined:

function Get_Cache
         (  Widget : not null access Gtk_Directory_Tree_View_Record
         )  return Gtk_Abstract_Directory;

This function returns the Gtk_Abstract_Directory object used with the directory tree view.

function Get_Current_Directory
         (  Widget : not null access Gtk_Directory_Tree_View_Record
         )  return Item_Path;

This function returns the path of the directory currently selected in the tree view. Name_Error is propagated when there is no directory selected.

function Get_Icon
         (  Widget       : not null access Gtk_Directory_Tree_View_Record;
            Kind         : Item_Type;
            Expanded     : Boolean;
            Has_Children : Boolean;
            Topmost      : Boolean
         )  return Icon_Data;

This function is called to obtain the icon rendered for a directory. The parameter Kind is the type of the directory as it was returned by Read. The parameter Expanded is true if the directory is currently expanded. The parameter Has_Children is true if it has children items in the cache. When it is not, then normally this indicates that the directory is not readable. Topmost is true when the directory is a root. The default implementation returns stock ID gtk-stop when Has_Children is false. Otherwise it returns the value of Kind unless Expanded is true and Kind is gtk-directory. In this latter case it returns gtk-open.

function Get_Name
         (  Widget       : not null access Gtk_Directory_Tree_View_Record;
            Name         : Item_Name;
            Kind         : Item_Type;
            Expanded     : Boolean;
            Has_Children : Boolean;
            Topmost      : Boolean
         )  return Item_Name;

This function is called to obtain the name rendered for a directory. The parameter Name is the directory name. The parameter Kind is the type of the directory as it was returned by Read. The parameter Expanded is true if the directory is currently expanded. The parameter Has_Children is true if it has children items in the cache. When it is not, then normally this indicates that the directory is not readable. The parameter Topmost is true when the directory is a root. The default implementation returns Name.

procedure Gtk_New
          (  Widget   : out Gtk_Directory_Tree_View;
             Store    : not null access Gtk_Abstract_Directory_Record'Class;
             Selected : Item_Path := ""
          );

This procedure creates the widget. The parameter Store is the Gtk_Abstract_Directory object indicated by the widget. The parameter Selected when not empty is the path of the directory to select. The directory tree is expanded as much as possibly in order to make selection. When Selected does not indicate an existing directory, then the most close match is selected.

procedure Initialize
          (  Widget   : not null access Gtk_Directory_Tree_View_Record'Class;
             Store    : not null access Gtk_Abstract_Directory_Record'Class;
             Selected : Item_Path
          );

This procedure has to be called by the derived type from its Initialize.

function Is_Editable
         (  Widget : not null access Gtk_Directory_Tree_View_Record
         )  return Boolean;

This function returns true if Widget allows editing directory names. See Set_Editable.

procedure Name_Commit
          (  Widget   : not null access Gtk_Directory_Items_View_Record;
             Old_Path : Item_Path;
             New_Name : Item_Name
          );

This procedure is called when directory name editing is done. For this the widget must have directory names editing enabled by a call to Set_Editable. The parameter Old_Path identifies the directory. The parameter New_Name specifies a new name for it. When the directory name is valid the implementation can change it outside the cache and when that succeeds notify the cache using Renamed (Get_Cache (Widget), Old_Path, New_Name). The default implementation does nothing. That means it rejects any renaming request.

procedure Set_Current_Directory
          (  Widget    : not null access Gtk_Directory_Tree_View_Record;
             Directory : Item_Path
          );

This procedure selects Directory in the widget. The directory tree is expanded as necessary. Any selected before directory is deselected. The selected one is scrolled into the view. The path to Directory is cached when required. When Directory does not exist the procedure stops by its most nested existing parent.

procedure Set_Editable
          (  Widget   : not null access Gtk_Directory_Items_View_Record;
             Editable : Boolean
          );

By default the item names listed by the widget are not editable. When Set_Editable is called with Editable set to true, then the operator will be able to edit directory names directly. The name input is confirmed through the primitive operation Name_Commit.

2.8.3. Directory items view

The package Gtk.Abstract_Browser defines the type of a specialized tree view widget for indication of the items from some directory of a Gtk_Abstract_Directory store:

type Gtk_Directory_Items_View_Record is
   new
Gtk_Tree_View_Record with private;
type Gtk_Directory_Items_View is
   access all
Gtk_Directory_Items_View_Record'Class;

The tree view shows items of one directory. It supports features usual for file managers:

Note that as usual the same store may have any number of widgets independently rendering its content.

Directory_Items_Class_Name : constant String :=
   "GtkDirectoryItemsView";

This is the name of the widget's GTK+ class. The widget emits the following signals additionally to the signals of a tree view:

The following operations are defined on the widget type:

procedure Activated
          (  Widget : not null access Gtk_Directory_Items_View_Record;
             Index  : Positive
          );

This procedure is called upon activation a directory item. That is when the user clicks doubly on an item. The parameter Index identifies the item. All items from the directory filtered by the widget are enumerated from 1 to Get_Directory_Size. The default implementation when the item is a directory selects it in the directory tree view (if any) which in turn causes the widget to show the items of this directory. When it is not a directory and the item names are editable (see Set_Editable) it starts editing the item name.

procedure Directory_Changed
          (  Widget : not null access Gtk_Directory_Items_View_Record
          );

This procedure is called when the widget is switched to show another directory. The default implementation emits the directory-changed signal.

function Filter
         (  Widget    : not null access Gtk_Directory_Items_View_Record;
            Directory : Boolean;
            Name      : Item_Name;
            Kind      : Item_Type
         )  return Boolean;

This function can be overridden to prevent some items from being visible. The default implementation lets all items in.

procedure Finalize
          (  Widget : not null access Gtk_Directory_Items_View_Record
          );

This subprogram is called upon destruction. It has to be called from its overriding.

function Get_Cache
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Gtk_Abstract_Directory;

This function returns the Gtk_Abstract_Directory object used with by the directory items view.

function Get_Column
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            Index  : Positive
         )  return Positive;

This function returns the column of an item by its index. Constraint_Error is propagated when Index is not in 1..Get_Directory_Size. Note that the number of items and their indices are constrained to only the items filtered by the function Filter.

function Get_Columns
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Positive;

This function returns the number of item columns.

function Get_Current
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Natural;

This function returns the index of the current item. The result is 0 when there is no one. Otherwise it is a number from 1 to Get_Directory_Size. The items in the directory are ordered according to the function Compare.

function Get_Directory
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Item_Path;

This function returns the path of the indicated directory. The path of the root directory is empty.

function Get_Directory_Size
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Natural;

This function returns the number of items in the indicated directory.

function Get_Directory_Tree_View
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Gtk_Directory_Tree_View;

This function returns the directory tree view widget used with Widget. The result is null if there is no any.

function Get_Icon
         (  Widget       : not null access Gtk_Directory_Items_View_Record;
            Name         : Item_Name;
            Kind         : Item_Type;
            Directory    : Boolean;
            Has_Children : Boolean
         )  return Icon_Data;

This function is called to obtain the icon used for an item. The parameters Name, Kind and Directory are the name, the type and the directory of the item as they were returned by Read. The default implementation returns the value of Kind converted to String. Note that the widget is a columned view, so this function can be called for an empty cell of a partially filled row. Such cases can be recognized when Name and Kind are empty in order to return (Stock_ID, 0, ""), so that no icon would appear. When Directory is true and Has_Children is false this usually indicates that the folder is unreadable.

function Get_Index
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            Name   : Item_Name
         )  return Natural;

This function returns the index of a cached item specified by its name. The result is 0 when there is no such item. Note that some items can be filtered out by the function Filter.

function Get_Index
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            Row    : Positive;
            Column : Positive
         )  return Natural;

This function returns the index of an item specified by its row and column. The result is 0 if Row and Column do not identify any item.

function Get_Name
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            Index  : Positive
         )  return Item_Name;

This function returns name of an item by its index. Constraint_Error is propagated when Index is not in 1..Get_Directory_Size.

function Get_Path
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            Name   : Item_Name
         )  return Item_Path;

This function returns the path of an item by its name. It is equivalent to: Get_Path (Widget.Cache, Get_Directory (Widget), Name);

function Get_Path
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            Index  : Positive
         )  return Item_Path;

This function returns path of an item by its index. Constraint_Error is propagated when Index is not in 1..Get_Directory_Size.

function Get_Row
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            Index  : Positive
         )  return Positive;

This function returns the row of an item by its index. Constraint_Error is propagated when Index is not in 1..Get_Directory_Size.

function Get_Selection
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Selection;

This function returns the array of indices of the currently selected items. The type Selection is declared in the package as:

type Selection is array (Positive range <>) of Positive;

The selection type depends on the current selection mode:

function Get_Selection_Mode
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Gtk_Selection_Mode;

This function returns the current selection mode. The default selection mode is Selection_Multiple.

function Get_Selection_Size
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Natural;

This function returns the number of currently selected items.

function Get_Type
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            Index  : Positive
         )  return Item_Type;

This function returns the type of an item by its index. Constraint_Error is propagated when Index is not in 1..Get_Directory_Size.

function Get_Visible_Height
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Natural;

This function returns the number of rows visible in the leftmost visible column of Widget. The widget has to be realized.

function Get_Visible_Width
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Natural;

This function returns the number of columns visible in the topmost visible row of Widget. The widget has to be realized.

procedure Gtk_New
          (  Widget  : out Gtk_Directory_Items_View;
             Tree    : not null access Gtk_Directory_Tree_View_Record'Class;
             Columns : Positive
          );

This procedure creates Widget of directory items view. The parameter Tree is the directory tree view widget associated with. A directory selected in the tree is automatically shown by Widget. Similarly, when the current directory is changed for example when the operator activates a directory item, this item gets selected in Tree and the path to it is expanded. The parameter Columns specifies the number item columns in Widget.

procedure Gtk_New
          (  Widget  : out Gtk_Directory_Items_View;
             Store   : not null access Gtk_Abstract_Directory_Record'Class;
             Columns : Positive;
             Current : Item_Path := ""
          );

This variant is used when no directory tree view has to be associated with the widget. In this case the parameter Store is a Gtk_Abstract_Directory store object which items are indicates: The parameter Current is the path of the directory to show. When empty the root directory is shown. When non-existent the most nested existing parent is shown.

procedure Initialize
          (  Widget  : not null access Gtk_Directory_Items_View_Record'Class;
             Tree    : not null access Gtk_Directory_Tree_View_Record'Class;
             Columns : Positive
          );
procedure Initialize
          (  Widget  : not null access Gtk_Directory_Items_View_Record'Class;
             Store   : not null access Gtk_Abstract_Directory_Record'Class;
             Columns : Positive;
             Current : Item_Path
          );

One of these procedures shall be called from the Initialize of the derived type.

function Input_Event
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            Index  : Positive;
            Event  : Gdk_Event
         )  return Boolean;

This function is called upon a key or button press event not handled otherwise by the widget. It is a convenience function to ease handling events. It has the parameter Index identifying the item on which the event happened. The result is false when the event should be passed to other handlers. The default implementation returns false.

function Is_Directory
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            Index  : Positive
         )  return Boolean;

This function returns true if the item specified by Index is a directory. Constraint_Error is propagated when Index is not in 1..Get_Directory_Size.

function Is_Editable
         (  Widget : not null access Gtk_Directory_Items_View_Record
         )  return Boolean;

This function returns true if Widget allows editing item names listed in it. See Set_Editable.

function Is_Selected
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            Index  : Positive
         )  return Boolean;

This function returns true if the item specified by Index is a selected. Constraint_Error is propagated when Index is not in 1..Get_Directory_Size.

function Locate
         (  Widget : not null access Gtk_Directory_Items_View_Record;
            X, Y   : GDouble
         )  return Natural;

This function returns the index of an item at the coordinates X, Y relative to the Widget's bin_window. The result is 0 when X and Y do not specify any item.

procedure Move
          (  Widget       : not null access Gtk_Directory_Items_View_Record;
             Changed      : out Boolean;
             Modifier     : Gdk_Modifier_Type;
             To           : Natural;
             By           : Integer := 0;
             Fixed_Row    : Boolean := False
             Fixed_Column : Boolean := False
          );

This procedure moves the current position to the item with the index To + By. It does nothing when To is less than 1. When the position after incrementing using By is out of 1..Get_Directory_Size, it is saturated to the nearest existing one. The parameter Modifier controls selection change caused by the operation:

Shift_Mask Control_Mask Description
- - Single selection of the target item. All other items are deselected
- + Toggling selection of the target item
+ - Single range selection nearest to the target item. The items outside range are deselected.
+ + Range nearest to the target item selection.

The effect depends on the constraints imposed by the selection mode as specified by Set_Selection_Mode. The parameters Fixed_Row and Fixed_Column when true prevent the row or column of To from being left. This procedure can be used for item navigation. For instance navigation upwards can be achieved by specifying To = Get_Current (Widget) and By = -1. The output parameter Changed is set to true if the position was changed. Otherwise it is set to false.

procedure Name_Commit
          (  Widget : not null access Gtk_Directory_Items_View_Record;
             Index  : Positive;
             Name   : Item_Name
          );

This procedure is called when item name editing is done. For this the widget must have item names editing enabled by a call to Set_Editable. The parameter Index identifies the item. The parameter Name specifies a new name for it. When the item name is valid the implementation can change it outside the cache and when that succeeds notify the cache using Renamed (Widget, Index, Name). The default implementation does nothing.

procedure Refilter
          (  Widget : not null access Gtk_Directory_Items_View_Record
          );

This procedure is called when the item filtering logic changes, i.e. the behavior of the primitive operation Filter alters. The procedure forces scanning the directory items in order to decide whether they should be made visible or not.

procedure Refresh
          (  Widget : not null access Gtk_Directory_Items_View_Record
          );

This procedure refreshes the widget contents.

procedure Renamed
          (  Widget : not null access Gtk_Directory_Items_View_Record;
             Index  : in out Natural;
             Name   : Item_Name
          );

This procedure is provided for convenience. It calls to Renamed upon item renaming. Index identifies the item by its position. Name is the new item name. Constraint_Error is propagated when Index is not in 1..Get_Directory_Size. Note that the result might become invisible as the result of filtering. In this case Index is set to 0. Otherwise it is the renamed item index.

procedure Reset_Selection
          (  Widget : not null access Gtk_Directory_Items_View_Record;
          );

This procedure removes selection of any items.

procedure Selection_Changed
          (  Widget : not null access Gtk_Directory_Items_View_Record
          );

This procedure is called when the selection state changes. The default implementation emits the selection-changed signal.

procedure Set_Editable
          (  Widget   : not null access Gtk_Directory_Items_View_Record;
             Editable : Boolean
          );

By default the item names listed by the widget are not editable. When Set_Editable is called with Editable set to true, the operator will be able to edit the item names. The name input is confirmed through the primitive operation Name_Commit.

procedure Set_Selection
          (  Widget : not null access Gtk_Directory_Items_View_Record;
             Name   : Item_Name;
             State  : Boolean
          );
procedure
Set_Selection
          (  Widget : not null access Gtk_Directory_Items_View_Record;
             Index  : Position;
             State  : Boolean
          );

These procedures set selection of an item by its name or else position. The parameter Name or else Index specify the item to select if State is true or deselect if State is false. Nothing happens if Name or Index do not specify any item.

procedure Set_Selection_Mode
          (  Widget : not null access Gtk_Directory_Items_View_Record;
             Mode   : Gtk_Selection_Mode
          );

This procedure changes the selection mode. The default selection mode is Selection_Multiple. Other modes are:

2.9. Files directory cache and a browsing widget

The package Gtk.Directory_Browser provides an implementations of the abstract browsing model and a customized widget to use with it. It caches and renders the file system directory structure in a two-pane way customary to modern file managers. The widget is a composite widget derived from Gtk_Paned_Record:

directory browser

The implementation is rather straightforward because all work is actually done by Gtk_Directory_Tree_View and Gtk_Directory_Items_View. The widget just assembles then together and adds scroll bars.

2.9.1. Files directory cache

The type Gtk_Directory is an implementation of Gtk_Abstract_Directory that caches the file system directory structure:

type Gtk_Directory_Record is
   new Gtk_Abstract_Directory_Record with private;
type Gtk_Directory is access all Gtk_Directory_Record'Class;

The full names of Ada.Directories are used as Gtk_Abstract_Directory paths. The simple names of Ada.Directories are used as item names. File_Kind is mapped to Gtk_Abstract_Directory item type. The type value is chosen from the stock items as follows: The value Directory is mapped to gtk-directory, Ordinary_File to gtk-file, Special_File to gtk-execute.

procedure Delete
          (  Store : not null access Gtk_Directory_Record;
             File  : UTF8_String
          );

This procedure is used to remove a file or directory. It synchronizes the cache Store after completion of physical removal.

procedure Finalize (Store : not null access Gtk_Directory_Record);

This procedure is called upon finalization. When overridden it has to be called from the overriding.

procedure Gtk_New
          (  Store   : out Gtk_Directory;
             Policy  : Caching_Policy := Cache_Expanded;
             Tracing : Traced_Actions := Trace_Nothing
          );

This procedure creates a new caching store. The result is returned through the parameter Store. The parameter Policy determines the caching policy. For a discussion concerning different policies see the description of the abstract primitive operation Read. The parameter Tracing specifies, which actions are desired for tracing.

procedure Initialize
          (  Store   : not null access Gtk_Directory_Record'Class;
             Policy  : Caching_Policy;
             Tracing : Traced_Actions
          );

This procedure has to be called from the Initialize of the derived type.

2.9.2. Files directory browsing widget

The directory browsing widget provides functionality close to one of Microsoft explorer. It is a composite widget consisting of two panes. One pane contains a directory tree widget for navigating folders. Another pane contains a directory items widget for browsing files. The widget is derived from the paned widget. Its panes contain scrolled windows which in turn contain the tree and item view widgets:

type Gtk_Directory_Browser_Record is
   new
Gtk_Paned_Record with private;
type Gtk_Directory_Browser is
   access all
Gtk_Directory_Browser_Record'Class;

The following subprograms are defined on the widget:

function Filter
         (  Widget    : not null access Gtk_Directory_Browser_Record;
            Directory : Boolean;
            Name      : Item_Name;
            Kind      : Item_Type
         )  return Boolean;

This function can be overridden to prevent some items from being visible in the files view pane. The default implementation lets all items in.

function Get_Cache
         (  Widget : not null access Gtk_Directory_Browser_Record
         )  return Gtk_Directory;

The function returns the directory cache associated with the widget.

function Get_Files_View
         (  Widget : not null access Gtk_Directory_Browser_Record
         )  return Gtk_Directory_Items_View;

The function returns the files browsing widget.

function Get_Tracing
         (  Store : not null access Gtk_Directory_Browser_Record
         )  return Traced_Actions;

This function returns the current state of tracing.

function Get_Tree_View
         (  Widget : not null access Gtk_Directory_Browser_Record
         )  return Gtk_Directory_Tree_View;

The function returns the directory tree browsing widget.

procedure Gtk_New
          (  Widget    : out Gtk_Directory_Browser;
             File      : UTF8_String := Current_Directory;
             Columns   : Positive    := 4;
             Vertical  : Boolean     := False;
             Tree_Size : Gtk_Requisition := (Width => 180, Height => 500);
             List_Size : Gtk_Requisition := (Width => 600, Height => 500);
             Store     : Gtk_Directory   := null;
             Tracing   : Traced_Actions  := Trace_Nothing
          );

The procedure creates a new widget. The parameter File is the full name of a file to browse. Its most nested existing parent is selected in the directory tree view. Correspondingly it is shown in the files view. The parameter Columns specifies the number columns in the files view. When the parameter Vertical is false the tree view is shown left of the files view. Otherwise it is shown above. The parameters Tree_Size and List_Size control size of the directory tree and files list panes. The widget wiil try to render them so that no scroll bars will appear. For this the panes will be expanded but not larger than the corresponding parameters specify. The parameter Store is the directory cache to use with the widget. When specified as null a new directory cache is created transparently. The parameter Tracing specifies the actions desired for tracing.

procedure Initialize
          (  Widget    : not null access Gtk_Directory_Browser_Record'Class;
             File      : UTF8_String;
             Columns   : Positive;
             Vertical  : Boolean;
             Tree_Size : Gtk_Requisition;
             List_Size : Gtk_Requisition;
             Store     : Gtk_Directory;
             Tracing   : Traced_Actions
          );

This procedure has to be called from the Initialize of the derived type.

procedure Set_Tracing
          (  Widget  : not null access Gtk_Directory_Browser_Record;
             Tracing : Traced_Actions
          );

This procedure changes tracing status. The parameter Tracing defines which actions need to be traced.

function Get_Root_Directory (File : String) return String;

This procedure returns the full name of the root directory indicated by the widget.

2.9.3. Wildcard browsing widget

The package Gtk.Wildcard_Directory_Browser provides a specialized directory browsing widget with files list pane filtered using wildcard patterns.

Note this package requires Strings_Edit library.

type Gtk_Wildcard_Directory_Browser_Record is
   new
Gtk_Directory_Browser_Record with private;
type Gtk_Wildcard_Directory_Browser is
   access all
Gtk_Wildcard_Directory_Browser_Record'Class;

The following subprograms are defined on the widget:

procedure Finalize
          (  Widget : not null access Gtk_Wildcard_Directory_Browser_Record
          );

This procedure has to be called by the derived type when overridden upon its finalization.

function Get_Pattern
         (  Widget : not null access Gtk_Wildcard_Directory_Browser_Record
         )  return String_List.GList;

This function returns the currently used pattern. The result shall not be modified.

procedure Gtk_New
          (  Widget    : out Gtk_Wildcard_Directory_Browser;
             Pattern   : String_List.GList := Any;
             File      : UTF8_String := Current_Directory;
             Columns   : Positive    := 4;
             Vertical  : Boolean     := False;
             Tree_Size : Gtk_Requisition := (Width => 180, Height => 500);
             List_Size : Gtk_Requisition := (Width => 600, Height => 500);
             Store     : Gtk_Directory   := null;
             Tracing   : Traced_Actions  := Trace_Nothing
          );
procedure Gtk_New
          (  Widget    : out Gtk_Wildcard_Directory_Browser;
             Pattern   : Controlled_String_List;
             File      : UTF8_String := Current_Directory;
             Columns   : Positive    := 4;
             Vertical  : Boolean     := False;
             Tree_Size : Gtk_Requisition := (Width => 180, Height => 500);
             List_Size : Gtk_Requisition := (Width => 600, Height => 500);
             Store     : Gtk_Directory   := null;
             Tracing   : Traced_Actions  := Trace_Nothing
          );

These procedures create a new widget. The parameter Pattern is the files filter pattern. It can be specified either as a list or as a controlled wrapper around. When omitted the pattern is considered as matching anything. The parameter File is the full name of a file to browse. Its most nested existing parent is selected in the directory tree view. Correspondingly it is shown in the files view. The parameter Columns specifies the number columns in the files view. When the parameter Vertical is false the tree view is shown left of the files view. Otherwise it is shown above. The parameters Tree_Size and List_Size control size of the directory tree and files list panes. The widget will try to render them so that no scroll bars will appear. For this the panes will be expanded but not larger than the corresponding parameters specify. The parameter Store is the directory cache to use with the widget. When specified as null a new directory cache is created transparently. The parameter Tracing specifies the actions desired for tracing.

procedure Initialize
          (  Widget    : not null access Gtk_Wildcard_Directory_Browser_Record'Class;
             Pattern   : String_List.GList;
             File      : UTF8_String;
             Columns   : Positive;
             Vertical  : Boolean;
             Tree_Size : Gtk_Requisition;
             List_Size : Gtk_Requisition;
             Store     : Gtk_Directory;
             Tracing   : Traced_Actions
          );

This procedure has to be called from the Initialize of the derived type.

procedure Set_Pattern
          (  Widget  : not null access Gtk_Wildcard_Directory_Browser_Record;
             Pattern : String_List.GList := Any
          );
procedure Set_Pattern
          (  Widget  : not null access Gtk_Wildcard_Directory_Browser_Record;
             Pattern : UTF8_String
          );
procedure Set_Pattern
          (  Widget  : not null access Gtk_Wildcard_Directory_Browser_Record;
             Pattern : Controlled_String_List
          );

These procedures set new pattern. The pattern can be specified as a single alternative, as a list or as a controlled wrapper around.

2.10. Persistent storage browsing

The package Gtk.Persistent_Storage_Browser provides specialized cache and widgets for browsing persistent storages.

Note this package requires Simple Components and optionally GNADE ODBC libraries.

2.10.1. Paths, URI, Credentials

Paths. Persistent objects are identified by paths. Path have the type Item_Path. A path consists of UTF-8 encoded names separated by forward slashes (/). Slash and any other characters within a name can be escaped using backward slash (\). The first name of a path specified a persistent storage. The following operations are defined on paths:

function "&" (Path : Item_Path; Name : Item_Name) return Item_Path;

This function composes a path from a path to the directory and the item name within the directory. Name_Error is propagated when Name is empty.

function Get_Name (Path : Item_Path) return Item_Name;

This function returns the name part of Path. Name_Error is propagated when Path is illegal.

function Get_Directory (Path : Item_Path) return Item_Path;

This function returns the directory part of Path. Name_Error is propagated when Path is illegal or else there when there is no directory part.

function Is_Root (Path : Item_Path) return Boolean;

This function returns true if Path specifies a root-level item, i.e. a persistent storage.

URI. Uniform Resource Identifiers (URI) of persistent objects are used to identify them outside the application. An URI describes the persistent storage, user credentials used to access it and the path within the storage. URI syntax supports storing encrypted user credentials. The type:

type Scheme_Type is (DSN_Scheme, SQLite_Scheme);

defines URI schemes of the supported persistent storages:

The following operations are defined for object's URI:

procedure Get_Credentials
          (  URI          : UTF8_String;
             User         : out Unbounded_String;
             Password     : out Unbounded_String;
             Has_Password : out Boolean
          );

This procedure takes user credentials from URI. The output parameters User and Password are set from the corresponding parts of URI. The parameter Has_Password is returned true, when URI contains password. Otherwise Password is returned empty. Two URI schemes are supported:

function Get_DSN (URI : UTF8_String) return Item_Name;

This function returns the persistent storage name from URI. The result is an empty string when URI has syntax errors.

function Get_Path (URI : UTF8_String) return Item_Path;

This function returns the object path from URI. The result is an empty string when URI has syntax errors.

function Get_Scheme (URI : UTF8_String) return Scheme_Type;

This function returns the URI scheme. Constraint_Error is propagated when the scheme is unknown.

function To_DSN_URI
         (  DSN             : UTF8_String;
            User            : UTF8_String;
            Password        : UTF8_String := "";
            Stored_Password : Boolean     := False
         )  return UTF8_String;

This function composes a DSN URI from the data source name DSN and user credentials. When the parameter Stored_Password is true, the result will contain Password. For such URI the procedure Get_Credentials will return true in Has_Password.

function To_SQLite_URI
         (  DSN  : UTF8_String;
            File : UTF8_String;
         )  return UTF8_String;

This function composes a SQLite URI from the data source name DSN and the data base file name File.

Credentials. Accessing persistent storage may require querying user credentials. The package provides an abstract interface for.

type Abstract_Credentials_Query is abstract
   new
Object.Entity with null record;
type Abstract_Credentials_Query_Ptr is
   access
Abstract_Credentials_Query'Class;

The type Abstract_Credentials_Query is the abstract base type of credentials query. Usually it is implemented as a dialog. The following abstract operations have to be implemented:

procedure Create
          (  Query           : in out Abstract_Credentials_Query;
             Scheme          : out Scheme_Type;
             Name            : out Unbounded_String;
             User            : out Unbounded_String;
             Password        : out Unbounded_String;
             Stored_Password : out Boolean;
             Storage         : out Storage_Handle
          )  is abstract;

The function asks user to input the persistent storage type, name, user name and password. After successful completion the output parameters are set and the the parameter Storage is a valid handle to the persistent storage. When user cancels input Storage is invalid. An implementation may propagate Use_Error to indicate that the persistent storage should not be used, i.e. dropped. The output parameter Scheme indicates the type of the credentials, which then determines other output parameters:

procedure Get
          (  Query           : in out Abstract_Credentials_Query;
             Scheme          : Scheme_Type;
             Name            : UTF8_String;
             User            : in out Unbounded_String;
             Password        : in out Unbounded_String;
             Stored_Password : in out Boolean;
             Storage         : out Storage_Handle
          )  is abstract;

This procedure is like Create, but has initial values for Scheme, Name, User and Stored_Password. Further, Scheme and  Name cannot be changed.

package Query_Handles is
   new
Object.Handle
       (  Abstract_Credentials_Query,
          Abstract_Credentials_Query_Ptr
       );
use Query_Handles;

This package provides handles to query objects.

2.10.2. Cache

The package Gtk.Persistent_Storage_Browser defines a specialized directory cache of persistent objects:

type Gtk_Persistent_Directory_Record is
   new
Gtk_Abstract_Directory_Record with private;
type Gtk_Persistent_Directory is
   access all
Gtk_Persistent_Directory_Record'Class;

The following additional operations are defined:

procedure Add_Storage
          (  Store   : access Gtk_Persistent_Directory_Record;
             Storage : out Storage_Handle
          );

This procedure can be called in order to query the user for a new persistent storage. for this it uses the credential dialog associated with the store. When the storage was successfully added a handle to it is returned. Otherwise it is set invalid. The storage is added at the root level. When the user chooses an already connected storage, its handle is returned.

procedure Browse
          (  Store   : access Gtk_Persistent_Directory_Record;
             Path    : Item_Path;
             Storage : out Storage_Handle;
             Object  : out Deposit_Handle;
             Partial : Boolean := False
          );

This procedure browses a path specified by the parameter Path. It returns a handle to the object indicated by the path (the parameter Object) and a handle to the persistent storage of (the parameter Storage). The persistent storage must be connected to be browsed. When the storage is not yet connected, or some items of the path do not exist End_Error is propagated. If the parameter Partial is true, then the path is browsed as far as possible and End_Error is not propagated. Use_Error is propagated when an object on the path cannot be restored from the persistent storage because its class is unknown.

Exceptions
Data_Error Inconsistent storage
End_Error Wrong path (some items do not exist)
Name_Error Syntactically illegal path
Use_Error Unknown object's class

procedure Delete
          (  Store : access Gtk_Persistent_Directory_Record;
             Path  : Item_Path
          );

The object specified by Path is unnamed and then the cache is synchronized as necessary. When Path specifies a persistent storage, then it is only disconnected and removed from the cache. Nothing happens when object does not exist.

Exceptions
Data_Error Inconsistent storage
Name_Error Syntactically illegal path

function Get_Class
         (  Store : access Gtk_Persistent_Directory_Record;
            Path  : Item_Path
         )  return String;

This function is similar to Browse except that it returns the object's class rather than the object itself. Though it restores all objects along the path in order to get the class.

Exceptions
Data_Error Inconsistent storage
End_Error Wrong path (some items do not exist)
Name_Error Syntactically illegal path
Use_Error Unknown object's class

function Get_Creation_Time
         (  Store : access Gtk_Persistent_Directory_Record;
            Path  : Item_Path
         )  return Time;

This function is similar to Browse except that it returns the object's creation time. Though it restores all objects along the path in order to get the class.

Exceptions
Data_Error Inconsistent storage
End_Error Wrong path (some items do not exist)
Name_Error Syntactically illegal path
Use_Error Unknown object's class

function Get_DSN
         (  Store   : access Gtk_Persistent_Directory_Record;
            Storage : Storage_Handle
         )  return Item_Name;

The result is the DSN name of Storage as registered in Store. Constraint_Error is propagated when Storage is not cached in Store.

function Get_Manager
         (  Widget : access Gtk_Persistent_Directory_Record
         )  return Gtk_Recent_Manager;

This function returns the recent resource manager used by the store.

function Get_Path
         (  Store   : access Gtk_Persistent_Directory_Record;
            Storage : Storage_Handle;
            Object  : Deposit_Handle
         )  return Item_Path;

This function returns a path to Object in Storage. When Object is invalid the result is the root directory path, i.e. same as returned by Get_DSN, converted to Item_Path.

Exceptions
Constraint_Error Object not persistent in Storage
Data_Error Inconsistent storage
Name_Error The object is anonymous

function Get_Query
         (  Store : access Gtk_Persistent_Directory_Record
         )  return Query_Handles.Handle;

This function returns a handle to the credential query dialog used with Store.

function Get_Storage
         (  Store : access Gtk_Persistent_Directory_Record;
            Path  : Item_Path
         )  return Storage_Handle;

This function returns a handle to the storage where the object specified by Path belongs. Root-level paths denote the storage itself. The result is an invalid handle if the storage is not yet connected.

Exceptions
Data_Error Inconsistent storage
Name_Error Syntactically illegal path

procedure Gtk_New
          (  Store   : out Gtk_Persistent_Directory;
             Query   : Query_Handles.Handle;
             Manager : access Gtk_Recent_Manager_Record'Class :=
                              Get_Default;
             Tracing : Traced_Actions := Trace_Nothing
          );

This procedure creates a new cache. The parameter Manager is a recent resource manager to use. The manager keeps the configured persistent storage data sources as items. Each such item appears at the root level of the cache. When Query is an invalid handle no querying is used and so any root-level items attempted for browsing, which cannot be connected will be simply removed. The parameter Tracing specifies the actions desired for tracing.

procedure Initialize
          (  Store   : access Gtk_Persistent_Directory_Record'Class;
             Query   : Query_Handles.Handle;
             Manager : access Gtk_Recent_Manager_Record'Class;
             Tracing : Traced_Actions := Trace_Nothing
          );

This procedure has to be called upon initialization of a derived type object.

function Is_Directory
         (  Store : access Gtk_Persistent_Directory_Record;
            Name  : String;
            Class : String
         )  return Boolean;

This function is used to determine if a persistent object should be considered a directory. Only the objects for which this function returns true are scanned for having children. In fact any persistent object may serve as a directory. But usually there is some restriction put on. The default implementation returns true only for the objects that have class Directory.

procedure Set_Query
          (  Store : access Gtk_Persistent_Directory_Record;
             Query : Query_Handles.Handle
          );

This procedure changes the credential query dialog of Store to Query.

2.10.3. Persistent storage tree view

The package Gtk.Persistent_Storage_Browser provides a specialized tree view widget for persistent directories tree (see Gtk_Directory_Tree_View):

type Gtk_Persistent_Storage_Tree_View_Record is
   new
Gtk_Directory_Tree_View_Record with private;
type Gtk_Persistent_Storage_Tree_View is
   access all
Gtk_Persistent_Storage_Tree_View_Record'Class;

The following additional operations are provided:

function Get_Current_Object
         (  Widget : access Gtk_Persistent_Storage_Tree_View
         )  return Deposit_Handle;

This function returns a handle to the currently selected directory. The result is an invalid handle if no directory is selected. Data_Error is propagated on storage errors.

function Get_Current_Storage
         (  Widget : access Gtk_Persistent_Storage_Tree_View
         )  return Storage_Handle;

This function returns a handle to the storage where the currently selected directory resides. The result is an invalid handle if no directory is selected. Data_Error is propagated on storage errors.

function Get_Directory_Cache
         (  Widget : access Gtk_Persistent_Storage_Tree_View
         )  return Gtk_Persistent_Directory;

The function returns the directory cache associated with the widget.

procedure Gtk_New
          (  Widget   : out Gtk_Persistent_Storage_Tree_View;
             Store    : access Gtk_Persistent_Directory_Record'Class;
             Selected : Item_Path := ""
          );

This procedure creates a new widget. The parameter Selected is the path of an item to expand the directory tree to. When the item is a directory it is selected. Otherwise its parent is selected. When Selected is an empty string then nothing is done.

procedure Initialize
          (  Widget   : access Gtk_Persistent_Storage_Tree_View_Record'Class;
             Store    : access Gtk_Persistent_Directory_Record'Class;
             Selected : Item_Path
          );

This procedure has to be called upon initialization of a derived type object.

Persistent_Storage_Tree_View_Class_Name : constant String :=
   "GtkPersistentStorageTreeView";

This string constant contains the GTK+ class name of the widget. The widget has the following additional style properties:

Name GTK+ type Description
message-title string The message dialog title
name-conflict-error string The message shown when a name of a renamed object is already in use
null-renaming-error string The message shown when a name specified is empty
root-renaming-error string The message shown when a storage (root-level item) is renamed. Storage (data sources) can be renamed only by operating system specific means.
storage-error string The message shown on a persistent storage fault

2.10.4. Persistent storage objects view

The package Gtk.Persistent_Storage_Browser provides a specialized tree view widget for persistent object directories rendered as a columned list:

type Gtk_Persistent_Storage_Items_View_Record is
   new
Gtk_Directory_Items_View_Record with private;
type Gtk_Persistent_Storage_Items_View is
   access all
Gtk_Persistent_Storage_Items_View_Record'Class;

The following additional operations are provided:

function Get_Directory_Cache
         (  Widget : access Gtk_Persistent_Storage_Items_View
         )  return Gtk_Persistent_Directory;

The function returns the directory cache associated with the widget.

function Get_Directory_Object
         (  Widget : access Gtk_Persistent_Storage_Items_View
         )  return Deposit_Handle;

This function returns a handle to the current directory. The result is an invalid handle if no directory is selected. Data_Error is propagated on storage errors.

function Get_Storage
         (  Widget : access Gtk_Persistent_Storage_Items_View
         )  return Storage_Handle;

This function returns a handle to the storage where the currentl directory resides. The result is an invalid handle if no directory is selected. Data_Error is propagated on storage errors.

procedure Gtk_New
          (  Widget  : out Gtk_Persistent_Storage_Items_View;
             Store   : access Gtk_Persistent_Directory_Record'Class;
             Columns : Positive;
             Current : Item_Path := ""
          );

This procedure creates a new widget. The parameter Store is a cache object to use with. The parameter Columns is the number of columns. The parameter Current is the directory to render initially.

procedure Gtk_New
          (  Widget  : out Gtk_Persistent_Storage_Items_View;
             Tree    : access Gtk_Persistent_Storage_Tree_View_Record'Class;
             Columns : Positive;
          );

This variant of the procedure creates a new widget which works with a directory browsing widget specified by the parameter Tree.

procedure Initialize
          (  Widget  : access Gtk_Persistent_Storage_Items_View_Record'Class;
             Store   : access Gtk_Persistent_Directory_Record'Class;
             Columns : Positive;
             Current : Item_Path
          );
procedure Initialize
          (  Widget  : access Gtk_Persistent_Storage_Items_View_Record'Class;
             Tree    : access Gtk_Persistent_Storage_Tree_View_Record'Class;
             Columns : Positive
          );

One of these procedures have to be called upon initialization of a derived type object.

Persistent_Storage_Items_View_Class_Name : constant String :=
   "GtkPersistentStorageItemsView";

This string constant contains the GTK+ class name of the widget. The widget has the same additional style properties as Persistent_Storage_Tree_View_Class_Name.

2.10.5. Persistent storage browsing widget

The package Gtk.Persistent_Storage_Browser provides a composite widget for browsing persistent storage directories:

type Gtk_Persistent_Storage_Browser_Record is
   new
Gtk_Paned_Record with private;
type Gtk_Persistent_Storage_Browser is
   access all
Gtk_Persistent_Storage_Browser_Record'Class;

The widget is a descendant of paned. One of its children is a tree view of the persistent storage directory browsed another is a columned list of persistent objects in the currently viewed directory. The following operations are provided:

function Filter
         (  Widget    : access Gtk_Persistent_Storage_Browser_Record;
            Directory : Boolean;
            Name      : Item_Name;
            Kind      : Item_Type
         )  return Boolean;

This function can be overridden to prevent some objects from being shown in the directory items pane. The default implementation lets all items in.

function Get_Cache
         (  Widget : access Gtk_Persistent_Storage_Browser_Record
         )  return Gtk_Persistent_Directory;

This function returns the cache used by the widget.

function Get_Items_View
         (  Widget : access Gtk_Persistent_Storage_Browser_Record
         )  return Gtk_Persistent_Storage_Items_View;

This function returns the widget of columned list pane.

function Get_Manager
         (  Widget : access Gtk_Persistent_Storage_Browser_Record
         )  return Gtk_Recent_Manager;

This function returns the recent resource manager used by the widget.

function Get_Tracing
         (  Store : access Gtk_Persistent_Storage_Browser_Record
         )  return Traced_Actions;

This function returns the current state of tracing.

function Get_Tree_View
         (  Widget : access Gtk_Persistent_Storage_Browser_Record
         )  return Gtk_Persistent_Storage_Tree_View;

This function returns the widget of tree view pane.

procedure Gtk_New
          (  Widget    : out Gtk_Persistent_Storage_Browser;
             Query     : Query_Handles.Handle;
             Path      : Item_Path       := "";
             Columns   : Positive        := 4;
             Vertical  : Boolean         := False;
             Tree_Size : Gtk_Requisition := (Width => 180, Height => 500);
             List_Size : Gtk_Requisition := (Width => 600, Height => 500);
             Store     : Gtk_Persistent_Directory := null;
             Manager   : access Gtk_Recent_Manager_Record'Class :=
                            Get_Default;
             Tracing   : Traced_Actions  := Trace_Nothing
         );

This procedure creates a new widget. The parameter Query is a handle to a querying object. When Query is an invalid handle no querying is used and so any root-level items attempted for browsing, which cannot be connected will be simply removed. The parameter Path is the path to select initially. It is expanded as far as possible. The parameter Columns specifies the number columns in the objects view. When the parameter Vertical is false the tree view is shown left of the objects view. Otherwise it is shown above it. The parameters Tree_Size and List_Size control size of the directory tree and objects list panes. The widget will try to render them so that no scroll bars will appear. For this the panes will be expanded but not larger than the corresponding parameters specify. The parameter Store is the directory cache to use with the widget. When specified as null a new directory cache is created transparently. The parameter Manager is a recent resource manager to use. The manager keeps the configured persistent storage data sources as items. Each such item appears at the root level of the cache. The parameter Tracing specifies the actions desired for tracing.

procedure Initialize
          (  Widget    : access Gtk_Persistent_Storage_Browser_Record'Class;
             Query     : Query_Handles.Handle;
             Path      : Item_Path;
             Columns   : Positive;
             Vertical  : Boolean;
             Tree_Size : Gtk_Requisition;
             List_Size : Gtk_Requisition;
             Store     : Gtk_Persistent_Directory;
             Manager   : access Gtk_Recent_Manager_Record'Class;
             Tracing   : Traced_Actions
         );

One of these procedures have to be called upon initialization of a derived type object.

procedure Set_Tracing
          (  Widget  : access Gtk_Persistent_Storage_Browser_Record;
             Tracing : Traced_Actions
          );

This procedure changes tracing status. The parameter Tracing defines which actions need to be traced.

2.10.6. User credentials input

The package Gtk.Persistent_Storage_Credentials_Dialog provides an abstract implementation of querying object based on a dialogue:

type Dialog_Credentials_Query is abstract
   new
Abstract_Credentials_Query with private;

It has an abstract primitive operation to implement:

function Connect
         (  Query    : Dialog_Credentials_Query;
            Name     : UTF8_String;
            User     : UTF8_String;
            Password : UTF8_String
         )  return Storage_Handle is abstract;

The implementation uses the parameters Name, User and Password in order to connect to a persistent storage. A handle to it is returned. Data_Error is propagated on storage errors. Use_Error is propagated when the credentials are wrong.

type Gtk_Persistent_Storage_Credentials_Dialog_Record is
   new
Gtk_Dialog_Record with private;
type Gtk_Persistent_Storage_Credentials_Dialog is
   access all
Gtk_Persistent_Storage_Credentials_Dialog_Record'Class;

is the dialogue used by Dialog_Credentials_Query: The widget has the following additional style properties:

Name GTK+ Type Default Description
cancel-button-label string _Cancel The label of the cancel button
column-spacing GInt 3 Column spacing of the dialog elements
confirm-button-label string _OK The label of the confirm button
credentials-error string   The message on data source access error
empty-name-error string   The message when data source name is empty
name-label string Name The label of the data source name entry
open-error string   The message on data source open error
password-label string Password The label of the password entry
row-spacing GInt 3 Row spacing of the dialog elements
stored-password-label string Remember password The label of the password storing check box
user-label string User The label of the user name entry
title string User credentials The dialog title

Persistent_Storage_Credentials_Dialog_Class_Name : constant String :=
   "GtkPersistentStorageCredentialsDialog";

This string constant contains the GTK+ class name of the widget.

2.10.7. User credentials input for GNADE

The package Gtk.Persistent_Storage_Credentials_Dialog.ODBC provides an implementation of Dialog_Credentials_Query for GNADE ODBC persistent storages.

function Create return Query_Handles.Handle;

This function create a new querying object and returns a handle to it.


[Back][TOC][Next]

3. Embeddable images

The utility xpm2gtkada is a small utility which reads an XPM file from the standard input and creates Ada packages for embedding the image into a GtkAda application. Differently to gdk_pixmap_create_from_xpm_d and its equivalent in GtkAda it stores the image as a GdkPixbuf object that can be directly rendered.

The generated files are named after the XPM image name stored in the XPM file. Each XPM file usually starts as:

/* XPM */
static char
* <name> [] = {

Basically an XPM file is a C program snippet. <name> from the file is used to name the generated files. Three files are created:

The utility creates image as a GdkPixbuf object. The package <name>.ads will look like:

File <name>.ads:
with Gdk.Pixbuf;    use Gdk.Pixbuf;
with GLib;          use GLib;
with Interfaces.C;  use Interfaces.C;
with System;        use System;

package <name> is
   X_Size : constant GInt := ...;
   Y_Size : constant GInt := ...;
   type Pixbuf_Image is array (Natural range ...) of GUChar;
   pragma Convention (C, Pixbuf_Image);
   Pixels : constant Pixbuf_Image := ...
   function Get_Pixbuf return Gdk_Pixbuf;

Here X_Size and Y_Size are the image width and height. Pixels is the array of image pixels. The function Get_Pixbuf creates a Gdk_Pixbuf object from the pixel data. It will contain the alpha channel when the file has a transparent color. The returned value of Get_Pixbuf should be freed when no more needed. The object created by Get_Pixbuf is just a reference to the statically allocated buffer Pixels. The file <name>.adb contains the implementation of the package.

The package <name>-image.ads provides an easy way to create an image object on demand:

File <name>.ads:
with Gtk.Image;  use Gtk.Image;

function <name>.Image return Gtk_Image;

The function returns a new Gtk_Image object corresponding to the image.

3.1. Building xpm2gtkada from the source

To compile the utility from sources one needs simple components. Under Windows it can be compiled with GNAT Ada:

>gnatmake -I<components> -I<components>\xpm xpm2gtkada.adb

Under Linux it can be compiled as:

>gnatmake -I<components> -I<components>/xpm xpm2gtkada.adb

In both cases <components> refers to the directory where simple components are situated.

3.2. Usage of xpm2gtkada

The utility is called as follows:

>xpm2gtkada < <file>.xpm

The optional argument determines the type of images to use. By default it is pixbuf. XPM files can be created and edited using any appropriate imaging tool. For example, by GIMP

First you create a my_image.xpm file with the image in. Then you call:

>xpm2gtkada < my_image.xpm

This produces my_image_xpm.ads, my_image_xpm-image.ads and my_image_xpm-image.adb. Then the following code snippet could be used to create a button with an image on it:

with My_Image_XPM.Image;
...
procedure Gtk_New_Button
          (  Button : out Gtk_Button;
             Text   : UTF8_String;
             Image  : access Gtk_Widget_Record'Class
          )  is
   Label : Gtk_Label;
   Box   : Gtk_Box;
begin
   Gtk_New_HBox (Box, False, 0);
   Gtk_New (Label, Text);
   Set_Border_Width (Box, 2);
   Pack_Start (Box, Image, False, False, 3);
   Pack_Start (Box, Label, False, False, 3);
   Show (Image);
   Show (Label);
   Gtk_New (Button);
   Add (Button, Box);
end Gtk_New_Button;
...
Gtk_New_Button (My_Button, "My button", My_Image_XPM.Image);

Another example where embedded images are useful is stock icons. A stock icon can be used by GtkCellRendererPixbuf's property "stock-id". The following code snippet shows how to add stock icons from pixbuf images generated by xmp2gtkada:

with My_Image_XPM; -- The image data

with Gdk.Pixbuf;           use Gdk.Pixbuf;
with Gtk.Icon_Factory;     use Gtk.Icon_Factory;
with Gtk.Stock;            use Gtk.Stock;
with Interfaces.C.Strings; use Interfaces.C.Strings;

...
   type Gtk_Stock_Item_Ptr is access all Gtk_Stock_Item;
   pragma Convention (C, Gtk_Stock_Item_Ptr);
   -- This is a helper procedure, for standard ones aren't
   -- much convenient...
   procedure Add_Stock
             (  Picture : Gdk_Pixbuf;
                Name    : String;
                Label   : String
             )  is
      procedure Unref (Set : Gtk_Icon_Set);
      pragma Import (C, Unref, "gtk_icon_set_unref");
      function New_From_Pixbuf (Pxibvuf : Gdk_Pixbuf)
         return Gtk_Icon_Set;
      pragma Import
             (  C,
                New_From_Pixbuf,
                "gtk_icon_set_new_from_pixbuf"
             );
      Item : Gtk_Stock_Item_Ptr := new Gtk_Stock_Item;
      Set  : Gtk_Icon_Set;
   begin
      Set := New_From_Pixbuf (Picture);
      Add (Icons, Name, Set);
      Unref (Set);
      Unref (Picture);
      Item.Stock_ID := New_String (Name); -- Don't free it!
      Item.Label    := New_String (Label);
      Item.Modifier := 0;
      Item.KeyVal   := 0;
      Item.Translation_Domain := Null_Ptr;
      Add_Static (Item.all); -- This is important to do
   end Add_Stock;
   ...
   Icons : Gtk_Icon_Factory;
   ...
   Gtk_New (Icons);      -- Do it once, and don't Unref
   Add_Default (Icons);  -- This is important
   Add_Stock
   (  My_Image_XPM.Get_Pixbuf,
      "my-image",
      "The label of"
   );

Now if GtkCellRendererPixbuf meets the string "my-image" it will render it as the image from My_Image_XPM.ads. Note that Gtk_Stock_Item, the factory Icons and some other stuff are allocated, but never freed. GTK+ reference counting isn't much consequent...

3.3. Memory-mapped images

The package Gdk.Pixbuf.Image provides memory-mapped images. The image pixels can be manipulated directly in the memory. The image can be rendered on a cairo context without additional conversions. The package declares the following types:

type X_Axis is new GInt;
type Y_Axis is new GInt;

These are the types of the horizontal and vertical coordinates of the image. The left top corner of the image has the coordinates (1, 1).

type RGB_Pixel is record
   Red   : GUChar;
   Green : GUChar;
   Blue  : GUChar;
end record;
for RGB_Pixel'Size use 3 * 8;
pragma Convention (C, RGB_Pixel);

This is the type of a pixel. The representation allows effective rendering without additional conversions. The following operations are provided:

function From_Pixel (Pixel : RGB_Pixel) return Gdk_Color;

This function converts its parameter to color.

function To_Pixel (Color : Gdk_Color) return RGB_Pixel;

This function converts its color parameter to pixel.

type RGB_Image is tagged private;

Objects of this type represent memory-mapped imaged. Note that the object not limited and thus can be copied. The following operations are defined on the type:

procedure Draw
          (  Image   : RGB_Image;
             Context : Cairo_Context;
             X       : GInt;
             Y       : GInt;
             X1, X2  : X_Axis;
             Y1, Y2  : Y_Axis
          );

This procedure draws Image's rectangle X1..X2 × Y1..Y2 in Context at (X, Y). Constraint_Error is propagated when the rectangle is not completely in the image.

procedure Erase
          (  Image : in out RGB_Image;
             Pixel : RGB_Pixel
          );
procedure Erase
          (  Image : in out RGB_Image;
             Color : Gdk_Color
          );

These procedures erase the image using specified color.

function Get
         (  Image : RGB_Image;
            X     : X_Axis;
            Y     : Y_Axis
         )  return RGB_Pixel;

This function returns pixel at (X, Y). Constraint_Error is propagated on subscript error.

function Get_Height (Image : RGB_Image) return Y_Axis;

This function returns image height.

function Get_Width (Image : RGB_Image) return X_Axis;

This function returns image width.

procedure Set
          (  Image : in out RGB_Image;
             X     : X_Axis;
             Y     : Y_Axis;
             Pixel : RGB_Pixel
          );
procedure Set
          (  Image : in out RGB_Image;
             X     : X_Axis;
             Y     : Y_Axis;
             Color : Gdk_Color
          );

These procedures update image pixel at (X, Y). Constraint_Error is propagated on subscript error.

procedure Set_Size
          (  Image  : in out RGB_Image;
             Width  : X_Axis;
             Height : Y_Axis
          );

This procedure changes image size. Note that image content is not preserved after the change is made.


[Back][TOC][Next]

4. Style properties

GTK+. provides a framework for customization of widget appearance through resource files. A resource file may define widget style properties using a pattern matching mechanism. Styles can be matched against widget name or its class. The child package Gtk.Widget.Styles provides interface functions for dealing with style properties:

4.1. Installing style properties

The properties are installed on a class of widgets. For this the parent class of the widget has to be extended. This need to be done once before creation of the first widget from the class. The proper place to do it is the Initialize procedure. The package body of the widget implementation could contain:

The following code snippets illustrate use of Register: The package specification:

My_Class_Record : Ada_GObject_Class;

procedure
Initialize
          (  Widget : not null access My_Widget_Record'Class
          )  is
   ...
   To_Install : constant Boolean :=
                Class_Record.C_Class = Null_GObject_Class;
begin
  
<parent>.Initialize (Widget); -- Parent's initialization
   Initialize_Class_Record
   (  Widget,
      Null_Array,
      My_Class_Record,
      "MyWidgetClass"
   );
   if To_Install then
 
    Install_Style_Property
      (  My_Class_Record.C_Class,
         Gnew_String
         (  Name    => "my-widget-property",
            Nick    => "Text",
            Blurb   => "The text my widget needs",
            Default => "Default text"
      )  );
      ... -- Other style properties
   end if
;
   ... -- Continue initialization
end
Initialize;

Note that Initialize_Class_Record has to be called after initialization of the parent.

The procedure Install_Style_Property from Gtk.Widget installs a style property into a class of widgets, there is an alternative procedure Class_Install_Style_Property_Parser, which does the same but has an additional parameter, the property parser:

procedure Class_Install_Style_Property_Parser
          (  Class : GObject_Class;
             PSpec : Param_Spec;
             Parser : Gtk_RC_Property_Parser
          );

A property parser has the following type:

type GString is record
   Str           : Chars_Ptr;
   Len           : GSize;
   Allocated_Len : GSize;
end record;
pragma Convention (C, GString);
type Gtk_RC_Property_Parser is access function
     (  PSpec          : Param_Spec;
        RC_String      : GString;
        Property_Value : access GValue
     )  return GBoolean;
pragma Convention (C, Gtk_RC_Property_Parser);

It is a function called each time a style property is requested from the pool of hashed properties. Note that it is not used for actual parsing the resource file. The property values are all strings after resource file parsing. Only when requested a corresponding property parser is called, which is basically responsible for conversion of the string to a value. The parameter RC_String is the string to parse. Its field Str is a pointer to a nul-terminated string to parse. The parameter Property_Value is the result. When parsing is successful, it has to be initialized using Init from GLib.Values and then set to the value obtained. In this case the function has to return 1. Otherwise it returns 0 and does not touch Property_Value.

4.2. Querying style properties

Widget style properties might be undefined while widget initialization. In particular it means that querying style properties from the Initialize procedure might fail (to a default property value). To avoid this problem you can catch style-set event and query properties from the handler of. For example:

package Handlers is
   new
Gtk.Handlers.Callback (My_Widget_Record);

procedure Style_Set (Widget : access My_Widget_Record'Class) is
   Value : ... := Style_Get (Widget, "my-widget-property");
begin
   ... -- Make Value have some effect on Widget
end Style_Set;

procedure Initialize
          (  Widget : access My_Widget_Record'Class
          )  is
begin

   ... -- Necessary initialization
   Handlers.Connect
   (  Widget,
      "style-set",
      Handlers.To_Marshaller (Style_Set'Access)
   );
end Initialize;

The general way to query a style property is to use Style_Get_Property from Gtk.Widget. Note that custom types are not transformable. This means that they cannot be accessed without using a custom parser. For some predefined types there are handy wrappers of this procedure:

function Style_Get
         (  Widget        : access Gtk_Widget_Record'Class;
            Property_Name : UTF8_String
         )  return Type;

Here Type can be one of:

When a string is put into a resource file, it is UTF-8 encoded. This feature is platform-independent, thus it can be used for internationalization / localization issues.

The function working with Gdk_Color has an additional parameter:

function Style_Get
         (  Widget        : access Gtk_Widget_Record'Class;
            Property_Name : UTF8_String;
            Default       : Gdk_Color
         )  return Gdk_Color;

The following generic function:

generic
   with function
GTK_Type return GType;
   type
Ada_Type (<>) is private;
   with function
Get (Value : GValue) return Ada_Type;
function
Generic_Style_Get
         (  Widget        : access Gtk_Widget_Record'Class;
            Property_Name : String
         )  return Ada_Type;

can be used for wrapping Style_Get_Property. However, note that boxed types cannot be dealt with this way, because of type conversion issues and missing default in the property specification. The generic formal parameter GTK_Type is the GTK+ type of the value (a function to get it). Ada_Type is the type of values. Get is a function to extract a value from GValue object. Note that the GTK_Type parameter is a function rather than a plain GType value. The reason for this is that the value might be unknown until run-time. This is the case for many GtkAda types, which are constructed at run-time. For such types an attempt to get the actual value for GTK_Type will cause creation of a GTK+ type where it cannot be created. That would result in a critical error.

function Style_Get
         (  Widget        : access Gtk_Widget_Record'Class;
            Property_Name : UTF8_String;
         )  return GValue;

This function returns GValue initialized by the style property value of Widget by its name Property_Name. When the widget does not have the style property the result has the type GType_None. The value must be freed using Unset when no more used.

4.3. Querying enumerations

The generic child package Gtk.Widget.Styles.Generic_Enumeration provides subprograms for dealing with enumeration properties:

generic
   with package
Enumeration_Property is
      new
GLib.Generic_Properties.Generic_Enumeration_Property (<>);
package Gtk.Widget.Styles.Generic_Enumeration is ...

The formal parameter is an instance of the package GLib.Generic_Properties.Generic_Enumeration_Property. An enumeration property can be specified in the CSS file:

...
{
  -<class_name>-<property_name>: <property_value>;

or in the resource file:

style ...
{
  <class_name>::<property_name> = <property_value>

The property value can be given without quotation marks. Differently to the standard parser, one used in this package is case-insensitive, which is more natural for enumerations. When an enumeration style property is specified for a class using the standard parser, that is, when such property is installed using Class_Install_Style_Property, then its values have to be capitalized. The package provides two subprograms:

function Style_Get
         (  Widget        : access Gtk_Widget_Record'Class;
            Property_Name : String
         )  return Enumeration;

This function queries an enumeration style.

procedure Install_Style
          (  Class     : GObject_Class;
             Enum_Spec : Param_Spec
          );

This procedure installs an enumeration property style. The parameter Enum_Spec must be the result of a call to Gnew_Enum of the package Enumeration_Property.

4.4. Other subprograms

function Class_List_Style_Properties (Class : GObject_Class)
   return Param_Spec_Array;

This function enumerates and returns the properties specifications of Class. The result has the type:

type Param_Spec_Array is array (Positive range <>) of Param_Spec;

defined in this package.

procedure Get_Path
          (  Widget   : not null access Gtk_Widget_Record'Class;
             Reversed : Boolean := False
          )  return UTF8_String;
procedure Get_Class_Path
          (  Widget   : not null access Gtk_Widget_Record'Class;
             Reversed : Boolean := False
          )  return UTF8_String;

These two functions are used to get the name of Widget. The name path is reversed when Reversed is true. Get_Class_Path ignores effects of any Set_Name applied.

4.5. Capturing style properties of a widget

It is not always simple to figure out the style properties a widget can have when designing a CSS style sheet. It especially might be the case when dealing with deep hierarchies of widgets.

4.5.1. CSS

The package Gtk.Widget.Styles.CSS_Store provides a way of capturing style properties to ease design of resource files for an application. Note that the resource files are depreciated. The package has the following subprograms declared:

procedure Put_CSS_Styles
          (  File    : File_Type;
             Widget  : not null access Gtk_Widget_Record'Class;
             Recurse : Boolean := True
          );

This procedure enumerates the property styles of Widget and writes them into File in the format of the CSS style sheet. The name of the style rule <class_name>#<widget-name>. The style properties values are supplied with the available information about their type, range, defaults etc. When the parameter Recurse is set to true, the container widgets are traversed for their children. For each child a rule is generated and written into the file before one of the container. The rules are accompanied with a comment indicating the widget place in the widget's hierarchy.

procedure Put_CSS_Styles
          (  Widget  : not null access Gtk_Widget_Record'Class;
             Recurse : Boolean := True
          );

This procedure writes the properties styles onto the standard output.

4.5.2. Resource file

The package Gtk.Widget.Styles.Store provides a way of capturing style properties to ease design of resource files for an application. Note that the resource files are depreciated. The package has the following subprograms declared:

procedure Put_Styles
          (  File    : File_Type;
             Widget  : not null access Gtk_Widget_Record'Class;
             Recurse : Boolean := True
          );

This procedure enumerates the property styles of Widget and writes them into File in the format of the style-statement of GTK 2.x resource file. The name of the style statement is <widget-name>_of_<class_name>. The style properties values are supplied with the available information about their type, range, defaults etc. When the parameter Recurse is set to true, the container widgets are traversed for their children. For each child a style statement is generated and written into the file before one of the container. The style statements are accompanied with a comment indicating the widget place in the widget's hierarchy.

procedure Put_Styles
          (  Widget  : not null access Gtk_Widget_Record'Class;
             Recurse : Boolean := True
          );

This procedure writes the properties styles onto the standard output.


[Back][TOC][Next]

5. Missing stuff

The package Gtk.Missed contains some subprograms currently missing in GtkAda bindings:

procedure Add_Class_Style
          (  Style   : Gtk.RC.Gtk_RC_Style;
             Pattern : UTF8_String
          );
procedure Add_Widget_Class_Style
          (  Style   : Gtk.RC.Gtk_RC_Style;
             Pattern : UTF8_String
          );
procedure Add_Widget_Name_Style
          (  Style   : Gtk.RC.Gtk_RC_Style;
             Pattern : UTF8_String
          );

This procedure add resource styles to look up. They are equivalent to the resource file commands

class <pattern> style <style>
widget_class <pattern> style <style>
widget
<pattern> style <style>

correspondingly. Here <pattern> refers to the parameter Pattern, <style> does to the parameter Style.

function Build_Filename
         (  First_Element  : UTF8_String;
          [ Second_Element : UTF8_String;
          [ Third_Element  : UTF8_String;
          [ Fourth_Element : UTF8_String;
          [ Fifth_Element  : UTF8_String ]]]]
         )  return UTF8_String;

This function creates a filename from two to five elements using the correct separator for filenames. On Windows, this function takes into account that either the backslash (\ or slash (/) can be used as separator in filenames, but otherwise behaves as on Unix. When file pathname separators need to be inserted, the one that last previously occurred in the parameters (reading from left to right) is used. No attempt is made to force the resulting filename to be an absolute path. If the first element is a relative path, the result will be a relative path.

procedure Check (Context : Cairo_Context);

This procedure checks Context for pending errors. If its status indicates an error Status_Error is propagated.

procedure Class_Install_Property
          (  Class_Record  : GObject_Class;
             Prop_Id       : Property_Id;
             Property_Spec : Param_Spec
          );

This procedure is a replacement for Install_Property which takes Ada_GObject_Class instead of GObject_Class.

procedure Dir_Close (Dir : in out GDir);

This procedure closes directory opened by Dir_Open. Dir is set to null. If Dir is already null, the procedure is void. The type of directory object is declared as:

type GDir is new Glib.C_Proxy;

procedure Dir_Open
          (  Path  : UTF8_String;
             Dir   : out GDir;
             Error : out GError
          );

This procedure opens a directory for read. When operation is successful Dir is not null and Error is null. Otherwise Dir is null and Error is not null. When Dir is not null it must be closed using Dir_Close. When Error is not null it must be released using Error_Free.

function Dir_Read_Name (Dir : GDir) return UTF8_String;

This function reads the name of the next entry from the directory Dir opened by Dir_Open. End_Error is propagated when there is no more directory items.

function Dir_Rewind (Dir : GDir);

This procedure resets the given directory. The next call to Dir_Read_Name will return the first entry again.

function Find_Program_In_Path (Program : UTF8_String) return UTF8_String;

This function locates the first executable named Program in the user's path. It is an equivalent to UNIX shell's which.

function File_Test
         (  File_Name : UTF8_String;
            Flags     : GFileTest
         )  return Boolean;

This function returns true if any of the Flags is set:

type GFileTest is new GUInt;
File_Test_Is_Regular    : constant GFileTest := ...;
File_Test_Is_Symlink    : constant GFileTest := ...;
File_Test_Is_Dir        : constant GFileTest := ...;
File_Test_Is_Executable : constant GFileTest := ...;
File_Test_Exists        : constant GFileTest := ...;

function File_Test (File_Name : UTF8_String) return GFileTest;

This function provided for convenience. It tests for status bits and returns them together.

function From_RGBA (Color : Gdk_RGBA) return Gdk_Color;

This function converts RGBA argument to color. The alpha channel is ignored as the result is always opaque.

procedure Freeze_Notify
          (  Object : not null access GObject_Record'Class
          );

This procedure increases the freeze count on object. If the freeze count is non-zero, the emission of notify signals on object is stopped. The signals are queued until the freeze count is decreased to zero. Duplicate notifications are squashed so that at most one notify signal is emitted for each property modified while the object is frozen. This is necessary for accessors that modify multiple properties to prevent premature notification while the object is still being modified.

type Row_Order is (Before, Equal, After);

function
Compare
         (  Model : access Gtk_Tree_Model_Record'Class;
            A     : Gtk_Tree_Path / Gtk_Tree_Iter;
            B     : Gtk_Tree_Path / Gtk_Tree_Iter
         )  return Row_Order;

These four functions compare iterators or paths of a model. The result is Before when A precedes B. It is After if A follows B. Null_Iter and null path always precede anything else. When an iterators is compared it is first converted to a path. No attempt is made to verify if the iterator or path refer to the model specified. For these reasons all possible values of arguments are comparable.

function Delete_Event_Handler
         (  Widget : access Gtk_Widget_Record'Class;
            Event  : Gdk.Event.Gdk_Event
         )  return Boolean;

This procedure is used in the window as a handler of delete-event signal:

Gtk.Window.Gtk_New (Window);
Window.Set_Title ("My application");
Window.On_Delete_Event (Delete_Event_Handler'Access);
Window.On_Destroy (Destroy_Handler'Access);
...
Window.Show_All;
Gtk.Main.Main;

The implementation returns false.

procedure Destroy_Handler (Widget : access Gtk_Widget_Record'Class);

This procedure is used in the window as a handler of destroy signal:

Gtk.Window.Gtk_New (Window);
Window.Set_Title ("My application");
Window.On_Delete_Event (Delete_Event_Handler'Access);
Window.On_Destroy (Destroy_Handler'Access);
...
Window.Show_All;
Gtk.Main.Main;

The implementation calls Gtk.Main.Main_Quit.

procedure Erase (Container : not null access Gtk_Container_Record'Class);

This procedure removes all children from Container.

function Is_In
         (  Container : not null access Gtk_Container_Record'Class;
            Element   : not null access Gtk_Widget_Record'Class
         )  return Boolean;

This function returns true when Element is a member of Container.

function Get_Application_Name return UTF8_String;

This function returns the application name in a human readable form.

function Get_Background_Area
         (  Tree_View : not null access Gtk_Tree_View_Record'Class;
            Path      : Gtk_Tree_Path;
            Column    : Gtk_Tree_View_Column := null
         )  return Gdk_Rectangle;

This function is a replacement for an incorrectly implemented procedure Get_Background_Area from Gtk.Tree_View.

function Get_Basename (File_Name : UTF8_String) return UTF8_String;

This function gets the last component of the filename. If File_Name ends with a directory separator it gets the component before the last slash. If File_Name consists only of directory separators (and on Windows, possibly a drive letter), a single separator is returned. If File_Name is empty, it gets ".".

function Get_Column (Value : GValue) return Gtk_Tree_View_Column;

This function gets a tree view column from GValue. Some tree view event handles receive the column as a parameter in GValues list. The function Nth may then be applied with the corresponding parameter number and this function to the result in order to obtain the column object.

function Get_Column_No
         (  Tree_View : not null access Gtk_Tree_View_Record'Class;
            Column    : not null access Gtk_Tree_View_Column_Record'Class
         )  return GInt;

This function returns the number of a tree view column. The result is zero-based. On error, the result is negative.

function Get_Current_Dir return UTF8_String;

This function returns the current directory.

function Get_Dirname (File_Name : UTF8_String) return UTF8_String;

This function gets the directory components of a file name. If the file name has no directory components "." is returned.

function Get_PRGName return UTF8_String;

This function returns the name of the program.

function Get_Root (File_Name : UTF8_String) return UTF8_String;

This function returns the File_Name part before its root component, i.e. the "/" in UNIX or "C:\" under Windows. Use_Error is propagated when File_Name is not absolute.

function Get_Row_No
         (  Model : Gtk_Tree_Model;
            Iter  : Gtk_Tree_Iter
         )  return GInt;

This function returns a File_Name part after the root component, i.e. after the "/" in UNIX or "C:\" under Windows. Use_Error is propagated when File_Name is not absolute.

function Get_Row_No
         (  Model : Gtk_Tree_Model;
            Path  : Gtk_Tree_Path
         )  return GInt;

This function is similar but uses a path to the row.

procedure Get_Screen_Position
          (  Widget : not null access Gtk_Widget_Record'Class;
             X      : out GInt;
             Y      : out GInt
          );

This procedure gets screen coordinates of a widget. Note that the widget may share its window with other widgets. In other words the coordinates of a widget are not necessarily the coordinates of its window. This procedure takes this into account.

function Get_User_Special_Dir (Directory : User_Directory) return UTF8_String;

This function returns directories associated with the user. The parameter has the type:

type User_Directory is
     (  User_Directory_Desktop,      -- Desktop directory (home)
        User_Directory_Documents,    -- Documents directory
        User_Directory_Download,     -- Downloads directory
        User_Directory_Music,        -- Music directory
        User_Directory_Pictures,     -- Pictures directory
        User_Directory_Public_Share, -- shared directory
        User_Directory_Templates,    -- Templates directory
        User_Directory_Videos        -- Movies directory
     );

procedure Get_Visible_Range
          (  Tree_View  : not null access Gtk_Tree_View_Record'Class;
             Start_Path : out Gtk_Tree_Path;
             End_Path   : out Gtk_Tree_Path
          );

This procedure determines the visible range of rows in a tree view. When successful Start_Path is a path of the first visible row, End_Path is a path to the last one. Otherwise they are null. When not null the caller is responsible to call Path_Free on each corresponding path. Note that Tree_View has to be realized when Get_Visible_Range is caled. The implementation checks it using Realized_Is_Set to prevent application crash and returns both paths as null.

function GType_Icon return GType;

The type of GIcon interfaces.

function Has_Tooltip (Widget : not null access Gtk.Widget.Gtk_Widget_Record'Class)
   return Boolean;

Returns the has-tooltip property of Widget.

function Image (Color : Gdk_Color) return String;

This function returns string representation of color in the form red, green, blue, where red, green, blue are values in the range 0..255.

function Is_A (Derived, Ancestor : GType) return Boolean;

This function is used to check whether Derived inherits from Ancestor.

function Is_Absolute (File_Name : UTF8_String) return Boolean;

This is function returns true if the given File_Name is an absolute file name, i.e. it contains a full path from the root directory such as "/usr/local" on UNIX or "C:\windows" on Windows systems.

function Is_In
         (  Model : Gtk_Tree_Model;
            A     : Gtk_Tree_Path / Gtk_Tree_Iter;
            B     : Gtk_Tree_Path / Gtk_Tree_Iter
         )  return Boolean;

These four functions compare iterators or paths of a model for containment relation. The result is true if A is contained in B. A null iterator or path contain anything. No attempt is made to verify if the iterator or path refer to the model specified. For these reasons all possible values of arguments are comparable. To get meaningful a result the parameters should belong to Model.

function Is_Parent
         (  Model : Gtk_Tree_Model;
            A     : Gtk_Tree_Path / Gtk_Tree_Iter;
            B     : Gtk_Tree_Path / Gtk_Tree_Iter
         )  return Boolean;

These four functions compare iterators or paths of a model for child-parent relation. The result is true if A is the immediate parent of B. A null iterator or path is the parent of the first level nodes. The parameters should belong to Model.

function Is_Sibling
         (  Model : Gtk_Tree_Model;
            A     : Gtk_Tree_Path / Gtk_Tree_Iter;
            B     : Gtk_Tree_Path / Gtk_Tree_Iter
         )  return Boolean;

These four functions compare iterators or paths for being immediate ancestors of the same parent. A null iterator or path considered as the parent of the first level nodes so the result is true when both parameters are Null_Iter or null. Otherwise the parameters should belong to Model.

function Keyval_To_Unicode (Key_Val : Gdk_Key_Type) return GUnichar;

This function returns the Unicode position corresponding to the key value. When there is no one, 0 is returned.

function Keyval_To_Unicode (Key_Val : Gdk_Key_Type) return UTF8_String;

This function is like one above but returns the result encoded as UTF-8 string.

function Remove (File_Name : UTF8_String);

This procedure deletes a file or a directory. Name_Error is propagated when File_Name does not specify an existing file. Use_Error is propagated when file cannot be deleted.

function Rename (Old_File_Name, New_File_Name : UTF8_String);

This procedure renames Old_File_Name to New_File_Name. Name_Error is propagated when Old_File_Name does not specify an existing file or directory. Use_Error is propagated when file cannot be renamed.

function RGB (Red, Green, Blue : GDouble) return Gdk_Color;

This function returns the color composed from the red, blue and green stimuli in the range 0.0..1.0. Values outside the range are saturated to the nearest bound.

procedure Set_Property
          (  Object : not null access
                    
 Glib.Object.GObject_Record'Class;
             Name   : in Glib.Properties.Property_Float;
             Value  : in Glib.Gfloat
          );

This is a replacement for a broken counterpart from GLib.Properties.

procedure Set_Tip
          (  Widget : not null access
                    
 Gtk.Widget.Gtk_Widget_Record'Class
          );

This procedure sets null tooltip text for Widget.

function Skip_Root (File_Name : UTF8_String) return UTF8_String;

This function returns a File_Name part after the root component, i.e. after the "/" in UNIX or "C:\" under Windows. Use_Error is propagated when File_Name is not absolute.

procedure Thaw_Notify
          (  Object : not null access GObject_Record'Class
          );

This procedure reverts the effect of a previous call to Freeze_Notify. The freeze count is decreased on object and when it reaches zero, queued notify signals are emitted. Duplicate notifications for each property are squashed so that at most one notify signal is emitted for each property, in the reverse order in which they have been queued. It is an error to call this function when the freeze count is zero.

function Themed_Icon_New (Icon_Name : UTF8_String) return GObject;

This function returns an icon from the current theme corresponding to Icon_Name. The result when not null must be freed using Unref.

function Themed_Icon_New_With_Default_Fallbacks
         (  Icon_Name : UTF8_String
         )  return GObject;

This function returns an icon from the current theme corresponding to Icon_Name. The function tries names obtained by shortening Icon_Name at '-' characters. The result when not null must be freed using Unref.

function To_RGBA (Color : Gdk_Color) return Gdk_RGBA;

This function converts Color to opaque RGBA value.

function To_String (Status : Cairo_Status) return String;

This function converts status to the corresponding message text.

function Unicode_To_Keyval (WC : GUnichar) return Gdk_Key_Type;

This function returns a key value corresponding to a Unicode code position WC. The result is 100000016 when there is no one.

type Wait_Cursor
     (  Widget : not null access Gtk_Widget_Record'Class
     )  is new Ada.Finalization.Limited_Controlled with private;

When an object of this type exists it changes the cursor to clock for the Widget's window.

generic
   type
User_Data (<>) is private;
   with procedure Destroy (Data : in out User_Data) is null;
package Set_Column_Cell_Data is ...

The package provides allows to attach a user-defined handler of a column of tree view. It has the following declarations:

type Cell_Data_Function is access procedure
     (  Column : not null access Gtk_Tree_View_Column_Record'Class;
        Cell   : not null access Gtk_Cell_Renderer_Record'Class;
        Model  : Gtk_Tree_Model;
        Iter   : Gtk_Tree_Iter;
        Data   : User_Data
     );

This procedure is called in order to set attributes of the renderer Cell for the column Column. Model is the tree model and Iter is an iterator to the row in the model being rendered. Data is the user data as passed by the call:

procedure Set_Cell_Data_Func
          (  Column : not null access Gtk_Tree_View_Column_Record'Class;
             Cell   : not null access Gtk_Cell_Renderer_Record'Class;
             Func   : Cell_Data_Function;
             Data   : User_Data
          );

This procedure sets Func to handle Column for Cell. When Func is null the old function is removed.

5.1. Handling values

The package Glib.Values.Handling contains the following subprograms for dealing with values used in GTK+ in a generic way:

function Copy (Src_Value : GValue) return GValue;

This function creates a copy of Src_Value and returns the copy as the result. The semantics of copying is determined by the type of the value. See g_value_copy for further information.

procedure Copy (Src_Value : GValue; Dest_Value : in out GValue);

This procedure copies Src_Value into Dest_Value. The actual type of Dest_Value may differ from the type of Src_Value, in which case it is changed. For this Dest_Value is first unset and then re-initialized with the type of Src_Value.

function Get_Type (Src_Value : GValue) return GType;

This function returns the GTK+ type of Src_Value.

procedure Set_Object
          (  Value  : in out GValue;
             Object : access GObject_Record'Class
          );

This procedure puts an object into value. The value must have been initialized with the object's type before the call. Usually there is no need to use this procedure especially there is no easy way to extract the object back from the value when its type is unknown in advance. However it might be helpful in the cases when a signal has to be emitted with unusual parameters. The first parameter in the list of GValues is the object of the signal. It can be set using this procedure.

5.2. Controlled strong and weak GTK+ references

GTK+ provides reference counting garbage collections of its objects. It is sometimes tedious to use, so the packages GLib.Object.Strong_References and GLib.Object.Weak_References implement controlled wrappers to the reference counting procedures of its parent package. Two types are provided:

5.2.1. Strong references

generic
   type
Object_Type is new GObject_Record with private;
package GLib.Object.Strong_References is ...

The package formal type is the type of the object.

type Strong_Reference is
   new
Ada.Finalization.Controlled with private;

The following operations are defined:

procedure Adjust   (Reference : in out Strong_Reference);
procedure
Finalize (Reference : in out Strong_Reference);

When overridden, these procedures have to be called from the corresponding bodies.

function Get (Reference : Strong_Reference)
   return access Object_Type'Class;

This function returns a pointer to the object referred or null when the reference is invalid.

procedure Invalidate (Reference : in out Strong_Reference);

This procedure makes Reference invalid. An invalid reference refer to no object. The effect of this procedure might be object destruction if the reference count of the object was 1.

function Is_Valid (Reference : Strong_Reference) return Boolean;

This function returns true is Reference is valid.

function Ref (Object : not null access Object_Type'Class)
   return Strong_Reference;

This function creates a strong reference to Object. The reference count of Object is increased. Upon reference finalization the reference count is decreased.

procedure Set
          (  Reference : in out Strong_Reference;
             Object    : access Object_Type'Class
          );

This procedure assigns another object to the reference. Nothing happens if Object is already referenced by Reference. When Object is null the reference becomes invalid.

5.2.2. Weak references

generic
   type
Object_Type is new GObject_Record with private;
package GLib.Object.Weak_References is ...

The package formal type is the type of the object.

type Weak_Reference is
   new
Ada.Finalization.Controlled with private;

The following operations are defined:

procedure Adjust   (Reference : in out Weak_Reference);
procedure
Finalize (Reference : in out Weak_Reference);

When overridden, these procedure has to be called from the corresponding bodies.

function Get (Reference : Weak_Reference)
   return access Object_Type'Class;

This function returns a pointer to the object referred or null when the reference is invalid.

procedure Invalidate (Reference : in out Weak_Reference);

This procedure makes Reference invalid. An invalid reference refer to no object.

function Is_Valid (Reference : Weak_Reference) return Boolean;

This function returns true is Reference is valid.

procedure Notify (Reference : in out Weak_Reference);

This procedure is called upon object destruction. At the call time the object does not exist and the reference is already invalid. The default implementation does nothing. It can be overridden to provide desired functionality.

function Ref (Object : not null access Object_Type'Class)
   return Weak_Reference;

This function creates a weak reference to Object.

procedure Set
          (  Reference : in out Weak_Reference;
             Object    : not null access Object_Type'Class
          );

This procedure  assigns another object to the reference. Nothing happens if Object is already referenced by Reference.

5.3. Controlled references to signal handlers (closures)

Signal handlers in GTK+ are automatically disconnected upon object finalization. However it is sometimes necessary to disconnect a handler prematurely due to finalization of the data the handler's callback deals with. The packages declared in Gtk.Handlers provide a mechanism for this represented by Object_Connect functions. The parameter Slot_Object of Object_Connect specifies a widget which finalization should disconnect the handler. Using of Object_Connect is sometimes inconvenient and also limited to only GTK+ widgets. The package Gtk.Handlers.References provides a simpler method which can be applied to any Ada type. The package declares the type:

type Handler_Reference is
   new
Ada.Finalization.Controlled with private;

An object of this type can be put into the type on which the handler's callback depends. There can be many instances of Handle_Reference bound to the same handler. When any of these objects gets finalized the handler is disconnected. Same happens when the object emitting the signal is finalized.

function Get (Reference : Handler_Reference) return Handler_ID;

This function returns identification of the handler referenced by Reference. It is same type as the result of Connect function. An unset reference returns Null_Handler_ID in the field ID.

procedure Set
          (  Reference : in out Handler_Reference;
             Handler   : Handler_ID
          );
procedure
Set (Reference : in out Handler_Reference);

This procedure binds Reference to Handler. Typically Handler is the result of a call to Connect function. When the procedure is called without Handler parameter the reference is unset.

Note that Handler_Reference is a non-limited type. Otherwise it were impossible to put a Handler_Reference into a non-limited record. And all widgets of GtkAda are non-limited. The drawback of this choice is that Handler_Reference can be copied. One should be careful with temporal objects of this type, because most certainly creation of such an object and initializing it by an object bound to a handler, will disconnect that handler upon leaving the scope of the temporal object.

The following code snippet illustrates use of references in a typical case when an object connects to a button which life span may extend one of the object:

   type My_Widget_Record is new ... record -- A custom widget
      ...
      Clicked_Handler : Handler_Reference;
   end record;
   type My_Widget is access all My_Widget_Record'Class;
   package Button_Handlers is   -- Handlers of button events
      new
Gtk.Handlers.User_Callback (Gtk_Button_Record, My_Widget);
   ...
           -- A button event handler, the second parameter is the widget
   procedure Clicked (Button : Gtk_Button_Record'Class; My : My_Widget);
   ...
   procedure Initialize (Widget : access My_Widget_Record'Class) is
   begin

      ...
      Set  -- Connection of the handler to an external button
      (  Widget.Clicked_Handler,
         Button_Handlers.Connect
         (  External_Button,
            "clicked",
            Button_Handlers.To_Marshaller (Clicked'Access),
            Widget.all'Unchecked_Access
      )  );
      ...

Here the procedure Clicked handles button clicks of the button External_Button. The button itself does not belong to My_Widget, so when an instance of the widget vanishes a click to the button will cause program crash, because Clicked will be called with a dangling pointer in the second parameter. Therefore upon initialization the identifier of the callback is passed to a Handler_Reference object, which automatically disconnects from the button when My_Widget is destroyed.

5.4. Managing recently used files (GtkRecentManager)

The package Gtk.Recent_Manager_Alt provides a complete set of bindings to the GTK+ facility for managing recently used files (GtkRecentManager).

Note, that GtkAda distribution beginning with 2.18.0 provide bindings to GtkRecentManager. The implementation given in Gtk.Recent_Manager_Alt is less thin. In particular it uses native Ada types for information objects and hides memory management issues.

This feature of GTK+ provides a simple  database to store application data between calls. Usually it is the lists of recently used files. This allows to store user-specific application data in a system-independent way. The package provides two basic types:

Information items:

type Gtk_Recent_Info is new GLib.C_Proxy;
type Gtk_Recent_Info_Array is
   array
(Positive range <>) of Gtk_Recent_Info;

The objects of Gtk_Recent_Info type are reference counted. The procedures Ref and Unref are used to change the reference count. The following operations are defined for Gtk_Recent_Info:

function Exists (Info : Gtk_Recent_Info) return Boolean;

This function checks whether the resource pointed by info still exists. At the moment this check is done only on resources pointing to local files.

function Get_Added (Info : Gtk_Recent_Info) return Time;

This function returns the time when the resource was added to the list. Time_Error is propagated when time is not available.

function Get_Age (Info : Gtk_Recent_Info) return Duration;

This function returns  the duration elapsed since the last update of the resource pointed.

function Get_Application_Info
         (  Info     : Gtk_Recent_Info;
            App_Name : UTF8_String
         )  return Application_Info;

This function returns the data regarding the application that has registered the resource pointed by Info. The result has the following type:

type Application_Info
     (  Registered      : Boolean;
        App_Exec_Length : Natural
     )  is
record

   case Registered is
      when
True =>
         Count     : GUInt;
         Last_Time : Time;
         App_Exec  : UTF8_String (1..App_Exec_Length);
      when False =>
         null;
   end case;
end record;

When the application App_Name has registered Info, the discriminant Registered of the result is true and the fields Count, Registration_Time and App_Exec are the number of times this item was registered, last registration time and the command line correspondingly.

function Get_Applications (Info : Gtk_Recent_Info)
   return Chars_Ptr_Array;

This function returns the list of application names which have registered the resource pointed by Info. It has to be freed using GtkAda.Types.Free.

function Get_Description (Info : Gtk_Recent_Info)
   return UTF8_String;

This function returns the resource description.

function Get_Display_Name (Info : Gtk_Recent_Info)
   return UTF8_String;

This function returns the display name of the resource.

function Get_MIME_Type(Info : Gtk_Recent_Info)
   return UTF8_String;

This function returns the MIME type of the resource.

function Get_Groups (Info : Gtk_Recent_Info)
   return Chars_Ptr_Array;

This function returns the list of groups for which the resource pointed by Info was registered. It has to be freed using GtkAda.Types.Free.

function Get_Icon
         (  Info : Gtk_Recent_Info;
            Size : GInt
         )  return Gdk_Pixbuf;

This function returns the icon of the resource pointed by Info. The parameter Size specified the required icon size in pixels. The returned object has the reference count 1 and should be freed using Unref.

function Get_Modified (Info : Gtk_Recent_Info) return Time;

This function returns the last modification time of the resource pointed by Info. Time_Error is propagated when time is not available.

function Get_Private_Hint (Info : Gtk_Recent_Info) return Boolean;

This function returns the value of the "private" flag. Resources in the recently used list that have this flag set to true should only be displayed by the applications that have registered them.

function Get_Private_Hint (Info : Gtk_Recent_Info) return Boolean;

This function returns the value of the "private" flag. Resources in the recently used list that have this flag set to true should only be displayed by the applications that have registered them.

function Get_Short_Name (Info : Gtk_Recent_Info) return UTF8_String;

This function computes a valid UTF-8 string that can be used as the name of the item in a menu or list. For example, calling this function on an item that refers to "file:///foo/bar.txt" will yield "bar.txt".

function Get_Visited (Info : Gtk_Recent_Info) return Time;

This function returns the last time the resource pointed by Info was visited. Time_Error is propagated when time is not available.

function Has_Application
         (  Info     : Gtk_Recent_Info;
            App_Name : UTF8_String
         )  return Boolean;

This function returns true if the resource pointed by Info was registered by the application App_Name.

function Has_Group
         (  Info  : Gtk_Recent_Info;
            Group : UTF8_String
         )  return Boolean;

This function returns true if the resource pointed by Info was specified for Group.

function Is_Local (Info : Gtk_Recent_Info) return Boolean;

This function returns true if the resource pointed by Info is local according to the scheme of its URI.

function Last_Application (Info : Gtk_Recent_Info) return UTF8_String;

This function returns the name of the last application that has registered the resource pointed by Info.

function Match (Info_A, Info_B : Gtk_Recent_Info) return Boolean;

This function returns true if the arguments point to the same resource.

procedure Ref (Info : Gtk_Recent_Info);

This procedure increases the reference count of Info,

procedure Unref (Info : Gtk_Recent_Info);

This procedure decreases the reference count of Info. This may lead the the object destruction.

Items managers. A GtkRecentManager object provides a facility for adding, removing and looking up recently used files. Each recently used file is identified by its URI, and has meta-data associated to it. The corresponding item has the type Gtk_Recent_Info.

type Gtk_Recent_Manager_Record is
   new
Glib.Object.GObject_Record with null record;
type Gtk_Recent_Manager is
   access all
Gtk_Recent_Manager_Record'Class;

The following operations are defined for the manager objects:

function Add_Full
         (  Manager      : access Gtk_Recent_Manager_Record;
            URI          : UTF8_String;
            Display_Name : UTF8_String;
            Description  : UTF8_String;
            MIME_Type    : UTF8_String := "application/octet-stream";
            App_Name     : UTF8_String := Get_Application_Name;
            App_Exec     : UTF8_String := " " & Get_PRGName & "%u";
            Groups       : Chars_Ptr_Array := Null_Array;
            Is_Private   : Boolean := False
         )  return Boolean;

Adds a new resource, pointed by URI, into the recently used resources list,. URI will be used to identify this resource inside the list. The result is true if a new item was successfully added.

function Add_Item
         (  Manager : not null access Gtk_Recent_Manager_Record;
            URI     : UTF8_String;
         )  return Boolean;

Adds a new resource, pointed by URI, into the recently used resources list. The meta data are derived from URI. The result is true if a new item was successfully added.

function Get_Default return Gtk_Recent_Manager;

This function returns the default manager. It is not created new by the function, so the result need not to be passed to Unref.

function Get_Items
         (  Manager : not null access Gtk_Recent_Manager_Record
         )  return Gtk_Recent_Info_Array;

This function returns the array of items from Manager. For each item from the array Unref has to be called. Note that the result is unfiltered and contains items added from other applications. You will probably wish to filter it using the application name (see Get_Application_Name and Has_Application). Like:

if Has_Application (Item, Get_Application_Name) then
   -- Item belongs to this application
   ...

procedure Gtk_New (Manager : out Gtk_Recent_Manager);

This procedure creates a new manager.

function Has_Item
         (  Manager : not null access Gtk_Recent_Manager_Record;
            URI     : UTF8_String
         )  return Boolean;

This function returns true if Manager has a resource for URI.

procedure Initialize (Manager : not null access Gtk_Recent_Manager_Record'Class);

This procedure has to be called by the derived type from its Initialize.

function Lookup_Item
         (  Manager : not null access Gtk_Recent_Manager_Record;
            URI     : UTF8_String
         )  return Item_Info;

This function searches for an item corresponding to URI. The result has the following type:

type Item_Disposition is (Found, Not_Found, Error);
type Item_Info (Status : Item_Disposition) is record
   case
Status is
      when
Found =>
         Info : Gtk_Recent_Info;
      when Not_Found =>
         null;
      when Error =>
        Error : GError;
   end case;
end record;

When search was successful the discrimnant Status is Found and the field Info describes the resource information. The caller has to call Unref on it. When search failed Status is Not_Found. On errors, Status is Error and the filed Error indicates the reason. Error_Free has to be called on it.

procedure Move_Item
          (  Manager : not null access Gtk_Recent_Manager_Record;
             URI     : UTF8_String;
             New_URI : UTF8_String;
             Error   : out GError
          );

This procedure changes the location of a recently used resource from URI to New_URI. When Error is not null it indicates an error and has to be passed to Error_Free.

procedure Purge_Items
          (  Manager : not null access Gtk_Recent_Manager_Record;
             Error   : out GError;
             Removed : out GInt
          );

This procedure purges every item from the resources list. Removed is the number of items removed. When Error is not null it indicates an error and has to be passed to Error_Free.

procedure Remove_Item
          (  Manager : not null access Gtk_Recent_Manager_Record;
             URI     : UTF8_String;
             Error   : out GError
          );

This procedure removes a recently used resource from the list. When Error is not null it indicates an error and has to be passed to Error_Free.

5.4.1. Key to value mapping

The package Gtk.Recent_Manager_Keys provides simplified means to store and restore values by keys:

procedure Delete
          (  Key     : UTF8_String;
             Manager : Gtk_Recent_Manager := Get_Default
          );

This procedure deletes the key specified by the parameter Key. Nothing happens when there is no such key. Manager is the recent manager to use.

function Restore
         (  Key     : UTF8_String;
            Default : UTF8_String;
            Manager : Gtk_Recent_Manager := Get_Default
         )  return UTF8_String;

This function restores the value previously stored using Store by its key. The parameter Key is the key. When no value for the key is found, Default is returned. Manager is the recent manager to use.

procedure Restore
          (  Key     : UTF8_String;
             Model   : Gtk_List_Store;
             Column  : GInt;
             Max_Row : Positive := 10;
             Manager : Gtk_Recent_Manager := Get_Default
          );

This procedure restores Column of the list store model. The values of the keys are named as key_n where key is the value of  Key, and n is the number 1..Max_Row.  <key>_1 corresponds the first row of the model. The values are set at Column as strings. When the model does not contain a row, it is inserted into the model. Manager is the recent manager to use. The procedure can be used to fill combo box entries contents with recently entered values as follows:

   Combo : Gtk_Combo_Box_Entry;
   List  : Gtk_List_Store;
begin
   ...
  
Gtk_New (List, (1 => GType_String));
   Restore ("Combo_Box_Values", List, 0);
   Gtk_New_With_Model (Combo, List, 0);

The values of a combo box can be stored using the procedure Store.

procedure Store
          (  Key     : UTF8_String;
             Value   : UTF8_String;
             Manager : Gtk_Recent_Manager := Get_Default
          );

This procedure stores Value under the key Key using Manager.

procedure Store
          (  Key     : UTF8_String;
             Model   : Gtk_List_Store;
             Column  : GInt;
             Max_Row : Positive := 10;
             Manager : Gtk_Recent_Manager := Get_Default
          );

This procedure stores Column of the list store model. The values of the keys are named as key_n where key is the value of  Key, and n is the row number. Max_Row rows are stored. Stored column can be restored using Restore. Values entered into the combo box entry and committed as worth to remember should be inserted into the model. Later when the widget is destroyed Store is called to remember its contents.

The package defines an abstract type to enumerate keys:

type Key_Enumerator is
   abstract new
Ada.Finalization.Limited_Controlled with null record;

The type has the class-wide operation:

procedure Enumerate
          (  Enumerator : in out Key_Enumerator'Class;
             Prefix     : UTF8_String;
             Manager    : Gtk_Recent_Manager := Get_Default
          );

This procedure enumerates the keys of Manager which keys begin with Prefix. For each found key Process is called. The operation ends prematurely if Process propagates End_Error.

procedure Process
          (  Enumerator : in out Key_Enumerator;
             Key        : UTF8_String;
             Value      : UTF8_String;
             Info       : Gtk_Recent_Info
          )  is abstract;

This procedure is called for enumerated keys. Enumerator is the parameter passed to Enumerate. Key is the key value beginning with Prefix. Value is the value corresponding to Key. Info is the information item associated with the key. The implementation may propagate End_Error in order to end enumeration prematurely.

5.5. Source view (GtkSourceView)

The set of packages:

provides a complete set of bindings to the GtkSourceView, an extension of the text view widget that supports syntax highlighting. GtkSourceView comes with a large data base of language syntax highlighting description which also includes Ada. It also allows custom syntax highlighting definitions.

Note, that GtkSourceView is presently not a part of GtkAda distribution. In order to use these package you will need to install GtkSourceView developing distribution. For further information see installation.

Source buffer. The package Gtk.Source_Buffer provides binding to extended text buffer object (see GtkSourceBuffer):

type Gtk_Source_Buffer_Record is
   new
Gtk_Text_Buffer_Record with private;
type Gtk_Source_Buffer is access all Gtk_Source_Buffer_Record'Class;

The package defines a new text search constant that can used for text searches in the buffer:

Case_Insensitive : constant Gtk_Text_Search_Flags := ...;

The following operations are defined:

procedure Backward_Iter_To_Source_Mark
          (  Buffer   : not null access Gtk_Source_Buffer_Record;
             Iter     : in out Gtk_Text_Iter;
             Moved    : out Boolean;
           [ Category : UTF8_String ]
          );

This procedure moves Iter to the position of the previous Gtk_Source_Mark of the given category. Moved is true if Iter was moved. If Category is omitted, the previous source mark can be of any category.

procedure Begin_Not_Undoable_Action
          (  Buffer : not null access Gtk_Source_Buffer_Record
          );

This procedure marks the beginning of a not undoable action on the buffer, disabling the undo manager. Typically you would call this function before initially setting the contents of the buffer (e.g. when loading a file in a text editor). You may nest Begin_Not_Undoable_Action / End_Not_Undoable_Action blocks.

function Can_Redo
         (  Buffer : not null access Gtk_Source_Buffer_Record
         )  return Boolean;

This function returns true if the source buffer can redo the last action.

function Can_Undo
         (  Buffer : not null access Gtk_Source_Buffer_Record
         )  return Boolean;

This function returns true if the source buffer can undo the last action.

function Create_Source_Mark
         (  Buffer   : not null access Gtk_Source_Buffer_Record;
            Name     : UTF8_String;
          [ Category : UTF8_String; ]
            Where    : Gtk_Text_Iter
         )  return Gtk_Source_Mark;

This function creates a source mark in the buffer of category. A source mark is a Gtk_Text_Mark, but organized into categories. Depending on the category a pixbuf can be specified that will be displayed along the line of the mark. Like a Gtk_Text_Mark, a Gtk_Source_Mark can be anonymous. Also, the buffer owns the marks so you shouldn't unreference it. Marks always have left gravity and are moved to the beginning of the line when the user deletes the line they were in. Typical uses for a source mark are bookmarks, breakpoints, current executing instruction indication in a source file, etc.

procedure End_Not_Undoable_Action
          (  Buffer : not null access Gtk_Source_Buffer_Record
          );

This procedure marks the end of a not undoable action on the buffer. When the last not undoable block is closed through the call to this procedure, the list of undo actions is cleared and the undo manager is re-enabled.

procedure Ensure_Highlight
          (  Buffer : not null access Gtk_Source_Buffer_Record;
             Start  : Gtk_Text_Iter;
             Stop   : Gtk_Text_Iter
          );

This procedure forces buffer to analyze and highlight the given area synchronously. Note that this is a potentially slow operation and should be used only when you need to make sure that some text not currently visible is highlighted, for instance before printing.

procedure Ensure_Highlight
          (  Buffer : not null access Gtk_Source_Buffer_Record;
             Start  : Gtk_Text_Iter;
             Stop   : Gtk_Text_Iter
          );

This procedure forces buffer to analyze and highlight the given area synchronously. Note that this is a potentially slow operation and should be used only when you need to make sure that some text not currently visible is highlighted, for instance before printing.

procedure Forward_Iter_To_Source_Mark
          (  Buffer   : not null access Gtk_Source_Buffer_Record;
             Iter     : in out Gtk_Text_Iter;
             Moved    : out Boolean;
           [ Category : UTF8_String ]
          );

This procedure moves Iter to the position of the next Gtk_Source_Mark of the given category. Moved is true if Iter was moved. If Category is omitted, the previous source mark can be of any category.

function Get_Highlight_Matching_Brackets
         (  Buffer : not null access Gtk_Source_Buffer_Record
         )  return Boolean;

This function returns true if the source buffer will highlight matching brackets.

function Get_Highlight_Syntax
         (  Buffer : not null access Gtk_Source_Buffer_Record
         )  return Boolean;

This function returns true if if syntax highlighting is activated.

function Get_Language
         (  Buffer : not null access Gtk_Source_Buffer_Record
         )  return Gtk_Source_Language;

This function returns the language associated with the buffer. The returned language object is owned by the buffer. It must not be unref'ed.

function Get_Max_Undo_Levels
         (  Buffer : not null access Gtk_Source_Buffer_Record
         )  return GInt;

This function returns the maximum number of possible undo levels or -1 if no limit is set.

function Get_Source_Marks_At_Line
         (  Buffer   : not null access Gtk_Source_Buffer_Record;
            Line     : GInt;
          [ Category : UTF8_String ]
         )  return Gtk_Source_Marks_Array;

This function returns the array of marks at the line. The objects in the array are owned by the buffer and shall not be unref'ed.

function Get_Source_Marks_At_Iter
         (  Buffer   : not null access Gtk_Source_Buffer_Record;
            Iter     : Gtk_Text_Iter;
          [ Category : UTF8_String ]
         )  return Gtk_Source_Marks_Array;

This function returns the array of marks at the iterator. The objects in the array are owned by the buffer and shall not be unref'ed.

function Get_Style_Scheme
         (  Buffer : not null access Gtk_Source_Buffer_Record
         )  return Gtk_Source_Style_Scheme;

This function returns the style scheme of the buffer. The returned style scheme object is owned by the buffer. It must not be unref'ed.

procedure Gtk_New
          (  Buffer   : out Gtk_Source_Buffer;
             Language : not null access Gtk_Source_Language_Record'Class
          );

This procedure creates a new buffer with a language set for highlighting.

procedure Gtk_New
          (  Buffer : out Gtk_Source_Buffer;
             Table  : Gtk_Text_Tag_Table := null
          );

This procedure creates a new buffer with a text tag table. When table is null a new one is created.

procedure Initialize
          (  Buffer   : not null access Gtk_Source_Buffer_Record'Class;
             Language : not null access Gtk_Source_Language_Record'Class
          );
procedure
Initialize
          (  Buffer : not null access Gtk_Source_Buffer_Record'Class;
             Table  : Gtk_Text_Tag_Table
          );

One of these procedures has to be called from the Initialize of a derived object.

procedure Redo (Buffer : not null access Gtk_Source_Buffer_Record'Class);

This procedure re-does the last undo action.

procedure Remove_Source_Marks
          (  Buffer   : not null access Gtk_Source_Buffer_Record;
             Start    : Gtk_Text_Iter;
             Stop     : Gtk_Text_Iter;
           [ Category : UTF8_String ]
          );

This procedure removes all marks of category between Start and Stop from the buffer. If category is omitted, all marks in the range will be removed.

procedure Set_Highlight_Matching_Brackets
          (  Buffer    : not null access Gtk_Source_Buffer_Record;
             Highlight : Boolean
          );

This procedure controls the bracket match highlighting function in the buffer. If activated, when you position your cursor over a bracket character (a parenthesis, a square bracket, etc.) the matching opening or closing bracket character will be highlighted.

procedure Set_Highlight_Syntax
          (  Buffer    : not null access Gtk_Source_Buffer_Record;
             Highlight : Boolean
          );

If Highlight is true, the text will be highlighted according to the syntax patterns specified in the language set with Set_language. If highlight is false, syntax highlighting is disabled and all the Gtk_Text_Tag objects that have been added by the syntax highlighting engine are removed from the buffer.

procedure Set_Language
          (  Buffer   : not null access Gtk_Source_Buffer_Record;
             Language : Gtk_Source_Language
          );

This procedure associates a Gtk_Source_Language with the source buffer. If language is null and syntax highlighting is enabled (see Set_Highlight_Syntax, the syntax patterns defined in language will be used to highlight the text contained in the buffer. If language is null, the text contained in the buffer is not highlighted.

procedure Set_Max_Undo_Levels
          (  Buffer          : not null access Gtk_Source_Buffer_Record;
             Max_Undo_Levels : GInt := -1
          );

The value -1 of Max_Undo_Levels indicates no limit is set. Otherwise it is the maximal number of undo levels to track.

procedure Set_Style_Scheme
          (  Buffer : not null access Gtk_Source_Buffer_Record;
             Scheme : not null access Gtk_Source_Style_Scheme_Record'Class
          );

This procedure sets style scheme used by the buffer.

procedure Undo (Buffer : not null access Gtk_Source_Buffer_Record);

This procedure undoes the last action, which modified the buffer. Actions are defined as groups of operations between a call to Begin_User_Action and End_User_Action, or sequences of similar edits (inserts or deletes) on the same line.

Source language. The package Gtk.Source_Language provides bindings to GtkSourceLanguage:

type Gtk_Source_Language_Record is
   new
GObject_Record with private;
type Gtk_Source_Language is
   access all
Gtk_Source_Language_Record'Class;

The following operations are defined:

function Get_Globs
         (  Language : not null access Gtk_Source_Language_Record
         )  return Chars_Ptr_Array;

This is just an utility wrapper around Get_Metadata to retrieve the "globs" metadata property and split it into an array. The elements of the result have to be freed using Interfaces.C.Strings.Free or else Gtkada.Types.Free.

function Get_Hidden
         (  Language : not null access Gtk_Source_Language_Record
         )  return Boolean;

This function returns true if the language should be hidden from the user.

function Get_ID
         (  Language : not null access Gtk_Source_Language_Record
         )  return UTF8_String;

This function returns the language ID.

function Get_Metadata
         (  Language : not null access Gtk_Source_Language_Record;
            Name     : UTF8_String
         )  return UTF8_String;

This function returns value of property Name stored in the metadata.

function Get_Mime_Types
         (  Language : not null access Gtk_Source_Language_Record
         )  return Chars_Ptr_Array;

This function returns the mime types associated to this language. This is just an utility wrapper around Get_Metadata to retrieve the "mimetypes" metadata property and split it into an array. The elements of the result have to be freed using Interfaces.C.Strings.Free or else Gtkada.Types.Free.

function Get_Name
         (  Language : not null access Gtk_Source_Language_Record
         )  return UTF8_String;

This function returns the localized name of the language.

function Get_Section
         (  Language : not null access Gtk_Source_Language_Record
         )  return UTF8_String;

This function returns the localized section of the language.

function Get_Style_Fallback
         (  Language : not null access Gtk_Source_Language_Record;
            Style    : UTF8_String
         )  return UTF8_String;

This function returns the ID of the style to use if the specified Style is not present in the current style scheme.

function Get_Style_IDs
         (  Language : not null access Gtk_Source_Language_Record
         )  return Chars_Ptr_Array;

This function returns the identifiers of the styles defined by this language. The elements of the result have to be freed using Interfaces.C.Strings.Free or else Gtkada.Types.Free.

function Get_Style_Name
         (  Language : not null access Gtk_Source_Language_Record;
            Style    : UTF8_String
         )  return Chars_Ptr_Array;

This function returns the style name or empty string.

Source language manager. The package Gtk.Source_Language_Manager provides bindings to GtkSourceLanguageManager. A manager object is used to get source language, usually from some persistent storage.

type Gtk_Source_Language_Manager_Record is
   new
GObject_Record with private;
type Gtk_Source_Language_Manager is
   access all Gtk_Source_Language_Manager_Record'Class;

The following operations are defined:

function Get_Default return Gtk_Source_Language_Manager;

The returned object is owned and shall not be unref'ed.

function Get_Language
         (  Manager  : not null access Gtk_Source_Language_Manager_Record;
            Language : UTF8_String
         )  return Gtk_Source_Language;

The returned object is owned and shall not be unref'ed. For example:

Get_Language (Get_Default, "ada");

function Get_Language_IDs
         (  Manager : not null access Gtk_Source_Language_Manager_Record
         )  return Chars_Ptr_Array;

This function returns an array containing a list of language identifiers. The array elements are owned by the language manager and must not be modified.

function Get_Search_Path
         (  Manager : not null access Gtk_Source_Language_Manager_Record
         )  return Chars_Ptr_Array;

This function returns an array containing a list of language files directories. The array elements are owned by the language manager and must not be modified.

procedure Gtk_New (Manager : out Gtk_Source_Language_Manager);

This procedure creates new manager object.

function Guess_Language
         (  Manager      : not null access Gtk_Source_Language_Manager_Record;
            File_Name    : UTF8_String;
            Content_Type : UTF8_String
         )  return Gtk_Source_Language;
function Guess_Language_By_File_Name
         (  Manager   : not null access Gtk_Source_Language_Manager_Record;
            File_Name : UTF8_String
         )  return Gtk_Source_Language;
function Guess_Language_By_Content
         (  Manager      : not null access Gtk_Source_Language_Manager_Record;
            Content_Type : UTF8_String
         )  return Gtk_Source_Language;

This function guesses language by file name and or content. The returned object is owned and shall not be unref'ed. Either File_Name or Content_Type can be omitted in the function versions named Guess_Language_By_File_Name and Guess_Language_By_Content.

procedure Initialize
          (  Manager : not null access
                     
 Gtk_Source_Language_Manager_Record'Class
          );

This procedure has to be called by derived types from their Initialize.

procedure Set_Search_Path
          (  Manager : not null access Gtk_Source_Language_Manager_Record;
           [ Dirs    : Chars_Ptr_Array ]
          );

This procedure sets the search path to look after language descriptions. When Dirs is absent the search path is set to default. At the moment this function can be called only before the language files are loaded for the first time. In practice to set a custom search path for a manager, you have to call this function right after creating it.

Source mark. The package Gtk.Source_Mark provides bindings to GtkSourceMark:

type Gtk_Source_Mark_Record is
   new
Gtk_Text_Mark_Record with private;
type Gtk_Source_Mark is access all Gtk_Source_Mark_Record'Class;

The arrays of source marks are used in some operations:

type Gtk_Source_Marks_Array is
   array
(Positive range <>) of Gtk_Source_Mark;

The following operations are defined:

function Get_Category
         (  Mark : not null access Gtk_Source_Mark_Record
         )  return UTF8_String;

This function returns the category of Mark.

procedure Gtk_New
          (  Mark     : out Gtk_Source_Mark;
           [ Name     : UTF8_String; ]
             Category : UTF8_String
          );

These procedures create a new mark. The parameter Name can be omitted to create an anonymous mark.

procedure Initialize
          (  Mark     : not null access Gtk_Source_Mark_Record'Class;
           [ Name     : UTF8_String; ]
             Category : UTF8_String
          );

This procedure is called from Initialize of derived objects.

function Next
         (  Mark     : not null access Gtk_Source_Mark_Record;
          [ Category : UTF8_String ]
         )  return Gtk_Source_Mark;

This function returns the next mark in the buffer or null if the mark was not added to a buffer. If there is no next mark, null will be returned. If category is omitted, it looks for marks of any category.

function Prev
         (  Mark     : not null access Gtk_Source_Mark_Record;
          [ Category : UTF8_String ]
         )  return Gtk_Source_Mark;

This function returns the previous mark in the buffer or null if the mark was not added to a buffer. If there is no previous mark, null will be returned. If category is omitted, it looks for marks of any category.

Source mark attributes. The package Gtk.Source_Mark_Attributes provides bindings to GtkSourceMarkAttributes:

type Gtk_Source_Mark_Atributes_Record is
   new
GObject_Record with private;
type Gtk_Source_Mark_Atributes is
   access all
Gtk_Source_Mark_Atributes_Record'Class;

The following operations are defined:

function Get_Background
         (  Attributes : not null access
                         Gtk_Source_Mark_Atributes_Record
         )  return Gdk_RGBA;

This function returns the background color of Attributes.

function Get_GIcon
         (  Attributes : not null access
                         Gtk_Source_Mark_Atributes_Record
         )  return G_Icon;

This function returns the icon of Attributes.

function Get_GIcon
         (  Attributes : not null access
                         Gtk_Source_Mark_Atributes_Record
         )  return G_Icon;

This function returns the icon of Attributes.

function Get_Icon_Name
         (  Attributes : not null access
                         Gtk_Source_Mark_Atributes_Record
         )  return UTF8_String;

This function returns the icon name of Attributes. The result is empty string if no icon name set.

function Get_Pxibuf
         (  Attributes : not null access
                         Gtk_Source_Mark_Atributes_Record
         )  return Gdk_Pixbuf;

This function returns the buffer of the rendered icon of Attributes. The result can be null.

function Get_Stock_ID
         (  Attributes : not null access
                         Gtk_Source_Mark_Atributes_Record
         )  return UTF8_String;

This function returns the icon stock ID of Attributes. The result can be empty string.

function Get_Tooltip_Markup
         (  Attributes : not null access
                         Gtk_Source_Mark_Atributes_Record
            Mark : not null access Gtk_Source_Mark_Record
         )  return UTF8_String;

This function returns the tooltip text which may contain markup.

function Get_Tooltip_Text
         (  Attributes : not null access
                         Gtk_Source_Mark_Atributes_Record
            Mark : not null access Gtk_Source_Mark_Record
         )  return UTF8_String;

This function return the tooltip text.

procedure Gtk_New
          (  Attributes : out Gtk_Source_Mark_Atributes
          );

This procedure create a new object of attributes.

procedure Initialize
          (  Attributes : not null access
                        
 Gtk_Source_Mark_Atributes_Record'Class;
          );

This procedure is called from Initialize of derived objects.

function Render_Icon
         (  Attributes : not null access
                         Gtk_Source_Mark_Atributes_Record;
            Widget : not null access Gtk_Widget_Record'Class;
            Size   : GInt
         )  return Gdk_Pixbuf;

This function renders an icon of given size. The base of the icon is set by the last call to one of Set_Pixbuf, Set_GIcon, Set_Stock_ID. Size cannot be lower than 1.

procedure Set_Background
          (  Attributes : not null access
                          Gtk_Source_Mark_Atributes_Record;
             Background : Gdk_RGBA
          );

This procedure sets the background color.

procedure Set_GIcon
          (  Attributes : not null access
                          Gtk_Source_Mark_Atributes_Record;
             Icon       : G_Icon
          );

This procedure sets the icon.

procedure Set_Icon_Name
          (  Attributes : not null access
                          Gtk_Source_Mark_Atributes_Record;
             Icon_Name  : UTF8_String
          );

This procedure sets the icon name.

procedure Set_Pixbuf
          (  Attributes : not null access
                          Gtk_Source_Mark_Atributes_Record;
             Pixbuf     : not null access Gdk_Pixbuf_Record'Class
          );

This procedure sets the icon.

procedure Set_Stock_ID
          (  Attributes : not null access
                          Gtk_Source_Mark_Atributes_Record;
             Stock_ID   : UTF8_String
          );

This procedure sets the icon from stock ID.

Source style. The package Gtk.Source_Style provides bindings to GtkSourceStyle:

type Gtk_Source_Style_Record is new GObject_Record with private;
type Gtk_Source_Style is access all Gtk_Source_Style_Record'Class;

The following operations are defined:

function Style_Copy
         (  Style : not null access Gtk_Source_Style_Record
         )  return Gtk_Source_Style;

This function creates a copy of Style. The result shall be unref'ed when no more used.

Source style scheme. The package Gtk.Source_Style_Scheme provides bindings to GtkSourceStyleScheme:

type Gtk_Source_Style_Scheme_Record is
   new
GObject_Record with private;
type Gtk_Source_Style_Scheme is
   access all
Gtk_Source_Style_Scheme_Record'Class;

The following operations are defined:

function Get_Authors
         (  Scheme : not null access Gtk_Source_Style_Scheme_Record
         )  return Chars_Ptr_Array;

This function returns authors of the style scheme. Elements of the result are owned by the style scheme. They shall not modified or freed.

function Get_Description
         (  Scheme : not null access Gtk_Source_Style_Scheme_Record
         )  return UTF8_String;

This function returns scheme description or empty string if none.

function Get_Filename
         (  Scheme : not null access Gtk_Source_Style_Scheme_Record
         )  return UTF8_String;

This function returns the file name parsed to create the scheme or empty string if none.

function Get_ID
         (  Scheme : not null access Gtk_Source_Style_Scheme_Record
         )  return UTF8_String;

This function returns identifier of the style scheme.

function Get_Name
         (  Scheme : not null access Gtk_Source_Style_Scheme_Record
         )  return UTF8_String;

This function returns name of the style scheme.

function Get_Style
         (  Scheme : not null access Gtk_Source_Style_Scheme_Record;
            Style  : UTF8_String
         )  return Gtk_Source_Style;

This function returns the style corresponding to Style or null.

Source style scheme manager. The package Gtk.Source_Style_Scheme_Manager provides bindings to GtkSourceStyleSchemeManager:

type Gtk_Source_Style_Scheme_Manager_Record is
   new
GObject_Record with private;
type Gtk_Source_Style_Scheme_Manager is
   access all
Gtk_Source_Style_Scheme_Manager_Record'Class;

The following operations are defined:

function Get_Default return Gtk_Source_Style_Scheme_Manager;

This function returns the default style scheme manager. It does not create a new object, so its result shall not be unref'ed.

procedure Append_Search_Path
          (  Manager : not null access Gtk_Source_Style_Scheme_Manager_Record;
             Path    : UTF8_String
          );

This procedure appends Path to the list of directories where the manager looks for style scheme files.

procedure Force_Rescan
          (  Manager : not null access Gtk_Source_Style_Scheme_Manager_Record
          );

This procedure marks any currently cached information about the available style schemes as invalid. All the available style schemes will be reloaded next time the manager is accessed.

function Get_Scheme
         (  Manager : not null access
                    
 Gtk_Source_Style_Scheme_Manager_Record;
            Scheme  : UTF8_String
         )  return Gtk_Source_Style_Scheme;

This function returns style scheme by identifier. The returned value is owned by manager and must not be unref'ed.

function Get_Scheme_IDs
         (  Manager : not null access
                    
 Gtk_Source_Style_Scheme_Manager_Record
         )  return Chars_Ptr_Array;

This function returns an array of string containing the identifiers of the available style schemes or Null_Ptr if no style scheme is available. The array elements are owned by the manager and must not be freed.

function Get_Search_Path
         (  Manager : not null access
                    
 Gtk_Source_Style_Scheme_Manager_Record
         )  return Chars_Ptr_Array;

This function returns an array of C-strings containing the path items. The array elements are owned by the manager and must not be freed.

procedure Gtk_New (Manager : out Gtk_Source_Style_Scheme_Manager);

This procedure creates new manager object..

procedure Initialize
          (  Manager : not null access
                     
 Gtk_Source_Style_Scheme_Manager_Record'Class
          );

This procedure is to be called from Initialize of derived objects.

procedure Prepend_Search_Path
          (  Manager : not null access Gtk_Source_Style_Scheme_Manager_Record;
             Path    : UTF8_String
          );

This procedure prepends Path to the list of directories where the manager looks for style scheme files.

procedure Set_Search_Path
          (  Manager : not null access Gtk_Source_Style_Scheme_Manager_Record;
           [ Dirs    : Chars_Ptr_Array ]
          );

This procedure sets the list of directories where the manager looks for style scheme files. When Dirs is absent the search path is reset to default.

Source view widget. The package Gtk.Source_View provides bindings to GtkSourceView:

type Gtk_Source_View_Record is
   new
Gtk_Text_View_Record with private;
type Gtk_Source_View is access all Gtk_Source_View_Record'Class;

The following types are defined:

type Gtk_Source_Smart_Home_End_Type is
     (  Home_End_Disabled,
        Home_End_Before,
        Home_End_After,
        Home_End_Always
     );

This type controls how HOME and END keys are treated when pressed.

type Gtk_Source_Draw_Spaces_Flags is mod 2**4;
Draw_Spaces_Space    : constant Gtk_Source_Draw_Spaces_Flags := 2**0;
Draw_Spaces_Tab      : constant Gtk_Source_Draw_Spaces_Flags := 2**1;
Draw_Spaces_New_line : constant Gtk_Source_Draw_Spaces_Flags := 2**2;
Draw_Spaces_NBSP     : constant Gtk_Source_Draw_Spaces_Flags := 2**3;
Draw_Spaces_ALL      : constant Gtk_Source_Draw_Spaces_Flags :=
                          Gtk_Source_Draw_Spaces_Flags'Last;

This type defines whether to draw categories of blank characters.

type Category_Background_Color (Has_Color : Boolean) is record
   case
Has_Color is
      when
True  => Color : Gdk_Color;
      when False => null;
   end case;
end record;

This object is returned when a color is returned. The discriminant Has_Color is false when no color is used.

The following operations are defined in the package:

function Get_Auto_Indent
         (  Widget : not null access Gtk_Source_View_Record
         )  return Boolean;

This function returns true if auto indentation is enabled.

function Get_Draw_Spaces
         (  Widget : not null access Gtk_Source_View_Record
         )  return Gtk_Source_Draw_Spaces_Flags;

This function returns the flags used for drawing spaces.

function Get_Highlight_Current_Line
         (  Widget : not null access Gtk_Source_View_Record
         )  return Boolean;

This function returns  true if the current line is highlighted.

function Get_Indent_On_Tab
         (  Widget : not null access Gtk_Source_View_Record
         )  return Boolean;

This function returns true if the selection is indented when tab is pressed.

function Get_Indent_Width
         (  Widget : not null access Gtk_Source_View_Record
         )  return GInt;

This function returns the number of spaces to use for each step of indent.

function Get_Insert_Spaces_Instead_Of_Tabs
         (  Widget : not null access Gtk_Source_View_Record
         )  return Boolean;

This function returns true if spaces are inserted instead of tabs.

function Get_Mark_Attributes
         (  Widget   : not null access Gtk_Source_View_Record;
            Category : UTF8_String;
            Priority : GInt
         )  return Gtk_Source_Mark_Atributes;

This function returns the attributes for the category and priority. The object is owned and should not be unref-ed.

function Get_Mark_Category_Background
         (  Widget   : nor null access Gtk_Source_View_Record;
            Category : UTF8_String
         )  return Category_Background_Color;

This function returns the background color of Category as Category_Background_Color object.

function Get_Mark_Category_Pixbuf
         (  Widget   : not null access Gtk_Source_View_Record;
            Category : UTF8_String
         )  return Gdk_Pixbuf;

This function returns the pixbuf of a category of marks or Null_Pixbuf if none.

function Get_Mark_Category_Priority
         (  Widget   : not null access Gtk_Source_View_Record;
            Category : UTF8_String
         )  return GInt;

This function returns the priority of a category of marks.

function Get_Right_Margin_Position
         (  Widget : not null access Gtk_Source_View_Record
         )  return GUInt;

This function returns the position of the right margin (width in characters).

function Get_Show_Line_Marks
         (  Widget : not null access Gtk_Source_View_Record
         )  return Boolean;

This function returns true if line marks are shown.

function Get_Show_Line_Numbers
         (  Widget : not null access Gtk_Source_View_Record
         )  return Boolean;

This function returns true if line numbers are shown.

function Get_Show_Right_Margin
         (  Widget : not null access Gtk_Source_View_Record
         )  return Boolean;

This function returns true if the right margin is shown.

function Get_Smart_Home_End
         (  Widget : not null access Gtk_Source_View_Record
         )  return Gtk_Source_Smart_Home_End_Type;

This function returns the flags controlling treatment of HOME and END key presses.

function Get_Tab_Width
         (  Widget : not null access Gtk_Source_View_Record
         )  return GUInt;

This function returns the tab width in characters.

procedure Gtk_New
          (  Widget : out Gtk_Source_View;
             Buffer : Gtk_Source_Buffer := null
          );

This procedure creates a new widget. When Buffer is null a new buffer is created. Otherwise the widget uses the buffer specified. Note that the same buffer can be shared by several widgets.

procedure Initialize
          (  Widget : not null access Gtk_Source_View_Record'Class;
             Buffer : Gtk_Source_Buffer
          );

This procedure is called by each derived object from its Initialize.

procedure Set_Auto_Indent
          (  Widget : not null access Gtk_Source_View_Record;
             Enable : Boolean
          );

If Enable is true auto indentation of text is enabled.

procedure Set_Draw_Spaces
          (  Widget : not null access Gtk_Source_View_Record;
             Flags  : Gtk_Source_Draw_Spaces_Flags
          );

This procedure sets if and how bank characters should be visualized. Specifying flags as 0 will disable display of blank characters.

procedure Set_Highlight_Current_Line
          (  Widget : not null access Gtk_Source_View_Record;
             Show   : Boolean
          );

This procedure sets whether to highlight the current line.

procedure Set_Indent_On_Tab
          (  Widget : not null access Gtk_Source_View_Record;
             Enable : Boolean
          );

This procedure controls indentation mode. If enabled, when the tab key is pressed and there is a selection, the selected text is indented of one level instead of being replaced with the tab characters. Shift + Tab unindents the selection.

procedure Set_Indent_Width
          (  Widget : not null access Gtk_Source_View_Record;
             Width  : GInt := -1
          );

This procedure sets the number of spaces to use for each step of indent. If Width is -1, the value of the "tab-width" property will be used.

procedure Set_Insert_Spaces_Instead_Of_Tabs
          (  Widget : not null access Gtk_Source_View_Record;
             Enable : Boolean
          );

This procedure controls whether to insert spaces instead of tabs.

procedure Set_Mark_Attributes
          (  Widget     : not null access Gtk_Source_View_Record;
             Category   : UTF8_String;
             Attributes : not null access
                          Gtk_Source_Mark_Atributes;
             Priority   : GInt
          );

This procedure sets attributes for the category and priority.

procedure Set_Mark_Category_Background
          (  Widget   : not null access Gtk_Source_View_Record;
             Category : UTF8_String;
           [ Color    : Gdk_Color ]
          );

This procedure sets the background color of the marks of Category. When Color is omitted, it the background color is unset for the given category of marks.

procedure Set_Mark_Category_Pixbuf
          (  Widget   : not null access Gtk_Source_View_Record;
             Category : UTF8_String;
             Pixbuf   : Gdk_Pixbuf := Null_Pixbuf
          );

This procedure associates a given pixbuf with a given mark category. If pixbuf is Null_Pixbuf, the pixbuf is unset.

procedure Set_Mark_Category_Priority
          (  Widget   : not null access Gtk_Source_View_Record;
             Category : UTF8_String;
             Priority : GInt
          );

This procedure sets the priority of a category of marks. When there are multiple marks on the same line, marks of categories with higher priorities will be drawn on top.

procedure Set_Right_Margin_Position
          (  Widget   : not null access Gtk_Source_View_Record;
             Position : GUInt
          );

This procedure sets the position of the right margin (width in characters).

procedure Set_Show_Line_Marks
          (  Widget : not null access Gtk_Source_View_Record;
             Show   : Boolean
          );

This procedure sets whether line marks should be displayed.

procedure Set_Show_Line_Numbers
          (  Widget : not null access Gtk_Source_View_Record;
             Show   : Boolean
          );

This procedure sets whether line numbers should be displayed.

procedure Set_Show_Right_Margin
          (  Widget : not null access Gtk_Source_View_Record;
             Show   : Boolean
          );

This procedure sets whether the right margin should be displayed.

procedure Set_Smart_Home_End
          (  Widget         : not null access Gtk_Source_View_Record;
             Smart_Home_End : Gtk_Source_Smart_Home_End_Type
          );

This procedure sets  the desired movement of the cursor when HOME and END keys are pressed.

procedure Set_Tab_Width
          (  Widget : not null access Gtk_Source_View_Record;
             Width  : GUInt
          );

This procedure sets the width of tabulation in characters.

5.6. Platform-specific content typing (GContentType)

The package GIO.Content_Type provides bindings to the platform-specific content typing. Content typing is a way to classify files according to their content. The operating system usually supports some means to determine the file content, like file name extension etc..GContentType is a way to interface it.

The package provides the following subprograms:

function Can_Be_Executable (Instance : UTF8_String) return Boolean;

This function checks if a content type Instance can be executable. Note that for instance things like text files can be executables (i.e. scripts and batch files).

function Equals (Type_1, Type_2 : UTF8_String) return Boolean;

This function returns true if two content types are same or equivalent.

function From_MIME_Type (MIME : UTF8_String) return UTF8_String;

This function tries to find a content type based on the MIME type specified by the parameter MIME. The result is empty string if it fails.

function Get_Description (Instance : UTF8_String) return UTF8_String;

This function gets the human readable description of a content type Instance. The description may look like Ada spec file.

function Get_Icon (Instance : UTF8_String) return GObject;

This function returns the icon for the content type. Icons have type GType_Icon. Icons can be rendered by Gtk_Cell_Renderer_Pixbuf. Call Unref when icon is no more used.

function Get_MIME_Type (Instance : UTF8_String) return UTF8_String;

This function gets the MIME type by content type. The result empty string if the function fails.

function Guess (File_Name : UTF8_String) return UTF8_String;

This function gets the content type of the file specified by its path File_Name. The result is an empty string if the function fails.

function Is_A (Instance, Supertype : UTF8_String) return Boolean;

This function returns true if the contents specified by Instance are subsets of the contents specified by Supertype.

function Is_Unknown (Instance : UTF8_String) return Boolean;

This function returns true if Instance is an unknown content type.

5.7. Mounts (GMount)

The package GIO.Mount provides bindings to GMount, user-visible mounts. Mount is a file system made accessible. Mounts can be mounted and unmounted:

type GMount_Record is new GObject_Record with null record;
type GMount is access all GMount_Record'Class;

The package provides the following subprograms:

function Can_Eject
         (  Mount : not null access GMount_Record
         )  return Boolean;

This function returns true if Mount can be ejected.

function Can_Unmount
         (  Mount : not null access GMount_Record
         )  return Boolean;

This function returns true if Mount can be unmounted.

function Get_Icon
         (  Mount : not null access GMount_Record
         )  return GObject;

This function returns the icon corresponding to Mount or null. Icons have type GType_Icon. Icons can be rendered by Gtk_Cell_Renderer_Pixbuf. Call Unref when icon is no more used.

function Get_Name
         (  Mount : not null access GMount_Record
         )  return UTF8_String;

This function returns the name of Mount.

function Get_Root
         (  Mount : not null access GMount_Record
         )  return UTF8_String;

This function returns the root path of Mount. The path is not necessary the system root. If Mount is a network share, then the result is the mount point.

function Get_UUID
         (  Mount : not null access GMount_Record
         )  return UTF8_String;

This function sets the UUID for the mount. The reference is typically based on the file system UUID for the mount in question and should be considered an opaque string.

package Mount_List is new Glib.Glist.Generic_List (GMount);

This instance provides lists of mounts. Each element of the list must be freed using Unref (applied to Get_Data). Then the list as a whole must be freed using Free.

5.8. Volumes (GVolume)

The package GIO.Volume provides bindings to GVolume, objects that can be mounted.

type GVolume_Record is new GObject_Record with null record;
type GVolume is access all GVolume_Record'Class;

The package provides the following subprograms:

function Get_Icon
         (  Volume : not null access GVolume_Record
         )  return GObject;

This function returns the icon corresponding to Volume or null. Icons have type GType_Icon. Icons can be rendered by Gtk_Cell_Renderer_Pixbuf. Call Unref when icon is no more used.

function Get_Name
         (  Volume : not null access GMount_Record
         )  return UTF8_String;;

This function returns the name of Volume.

function Get_Volume
         (  Mount : not null access GMount_Record'Class
         )  return GVolume;

This function returns the volume mounted on Mount. When the result is not null it must be freed using Unref when icon is no more used.

function Should_Automount
         (  Volume : not null access GVolume_Record
         )  return Boolean;

This function returns true if Volume should be mounted automatically.

package Volume_List is new Glib.Glist.Generic_List (GVolume);

This instance provides lists of volumes. Each element of the list must be freed using Unref (applied to Get_Data). Then the list as a whole must be freed using Free.

5.9. Drives (GDrive)

The package GIO.Drive provides bindings to GDrive, objects representing a piece of hardware connected to the machine. It's generally only created for removable hardware or hardware with removable media.

type GDrive_Record is new GObject_Record with null record;
type GDrive is access all GDrive_Record'Class;

The package provides the following subprograms:

function Can_Eject (Drive : not null access GDrive_Record) return Boolean;

This function returns true if Drive can be ejected.

function Get_Drive
         (  Volume : not null access GVolume_Record'Class
         )  return GDrive;
function Get_Drive
         (  Mount : not null access GMount_Record'Class
         )  return GDrive;

These functions return the drive of a Volume or Mount. The result can be null. When not Unref must be called when the object is no more used.

function Get_Icon
         (  Drive : not null access GDrive_Record
         )  return GObject;

This function returns the icon corresponding to Drive or null. Icons have type GType_Icon. Icons can be rendered by Gtk_Cell_Renderer_Pixbuf. Call Unref when icon is no more used.

function Get_Name
         (  Drive : not null access GDrive_Record
         )  return UTF8_String;;

This function returns the name of Drive.

function Get_Volumes
         (  Drive : not null access GDrive_Record
         )  return Volume_List.GList;

This function returns the list of volumes on Drive. Each element of the list must be freed using Unref (applied to Get_Data). Then the list as a whole must be freed using Free.

function Has_Media
         (  Drive : not null access GDrive_Record
         )  return Boolean;

This function returns true if Drive has media. Note that the OS may not be polling the drive for media changes; see Is_Media_Check_Automatic for more details.

function Has_Volumes
         (  Drive : not null access GDrive_Record
         )  return Boolean;

This function returns true if Drive contains volumes.

function Is_Media_Check_Automatic
         (  Drive : not null access GDrive_Record
         ) return Boolean;

This function returns true if Drive is capable of automatically detecting media changes.

function Is_Media_Removable
         (  Drive : not null access GDrive_Record
         )  return Boolean;

This function returns true if Drive supports removable media.

package Drive_List is new Glib.Glist.Generic_List (GDrive);

This instance provides lists of volumes. Each element of the list must be freed using Unref (applied to Get_Data). Then the list as a whole must be freed using Free.

5.10. Volume monitor (GVolumeMonitor)

The package GIO.Volume_Monitor provides bindings to GVolumeMonitor, objects listing devices and volumes on the computer.

type GVolume_Monitor_Record is new GObject_Record with null record;
type GVolume_Monitor is access all GVolume_Monitor_Record'Class;

The package provides the following subprograms:

function Get return GVolume_Monitor;

This function returns the default volume monitor. Unref must be called when the object is no more used.

function Get_Connected_Drives
         (  Monitor : not null access GVolume_Monitor_Record
         )  return Drive_List.GList;

This function returns connected drives. Each element of the list must be freed using Unref (applied to Get_Data). Then the list as a whole must be freed using Free.

function Get_Mounts
         (  Monitor : not null access GVolume_Monitor_Record
         )  return Mount_List.GList;

This function returns list of mounts. Each element of the list must be freed using Unref (applied to Get_Data). Then the list as a whole must be freed using Free.

function Get_Mount_For_UUID
         (  Monitor : not null access GVolume_Monitor_Record;
            UUID    : UTF8_String
         )  return GMount;

This function returns a mount by its UUID. When not null it must be freed using Unref.

function Get_Volumes
         (  Monitor : not null access GVolume_Monitor_Record
         )  return Volume_List.GList;

This function returns the list of volumes. Each element of the list must be freed using Unref (applied to Get_Data). Then the list as a whole must be freed using Free.

function Get_Volume_For_UUID
         (  Monitor : not null access GVolume_Monitor_Record;
            UUID    : UTF8_String
         )  return GVolume;

This function returns a volume by its UUID. When not null it must be freed using Unref.

5.11. Generic signal handlers

The package Gtk.Handlers.Generic_Callback provides signal handlers, which differently to the handlers provided by the parent package, deal with the signal parameters and the return value as GValues:

generic
   type Object_Type is new GObject_Record with private;
   type User_Type is private;
package Gtk.Handlers.Generic_Callback is ...

The formal parameters are:

The package declares the callback procedure type as:

type Handler is access procedure
     (  Object    : not null access Object_Type'Class;
        Arguments : GValue_Array;
        Result    : in out GValue;
        Data      : User_Type
     );

The parameter Object is the object for which the signal was emitted. Arguments is an array of the signal parameters. Result is the result value. Result is initialized with the expected type. This type is GType_None when no result is expected. The implementation should set the returned value into Result, if any. Data is the user value specified in Connect:

procedure Connect
          (  Object   : not null access Object_Type'Class;
             Name     : GLib.Signal_Name;
             Callback : Handler;
             Data     : User_Type;
             After    : Boolean := False
          );
function Connect
         (  Object   : not null access Object_Type'Class;
            Name     : GLib.Signal_Name;
            Callback : Handler;
            Data     : User_Type;
            After    : Boolean := False
         )  return Handler_ID;

These subprograms are used to connect Callback to the signal Name of Object. The value Data is passed to Callback. Constraint_Error is propagated when Name does not specify a signal of Object.

5.12. Stock items backward compatibility

Starting with GTK+ 3.10 stock items are considered deprecated. The functionality is threatened to be removed and warning messages generated run time. There is no substitute for the functionality offered, in particular for the "stock-id" property of the pixbuf cell renderer and Add_Button of dialog. The package Gtk.Missed provides replacements for deprecated operations:

procedure Add_Button_From_Stock
          (  Dialog    : not null access Gtk_Dialog_Record'Class;
             Response  : Gtk_Response_Type;
             Label     : UTF8_String      := "";
             Icon      : UTF8_String      := "";
             Icon_Left : Boolean          := True;
             Size      : Gtk_Icon_Size    := Icon_Size_Button;
             Spacing   : GUInt            := 3;
             Tip       : UTF8_String      := "";
             Relief    : Gtk_Relief_Style := Relief_Normal
          );
function Add_Button_From_Stock
         (  Dialog    : not null access Gtk_Dialog_Record'Class;
            Response  : Gtk_Response_Type;
            Label     : UTF8_String      := "";
            Icon      : UTF8_String      := "";
            Icon_Left : Boolean          := True;
            Size      : Gtk_Icon_Size    := Icon_Size_Button;
            Spacing   : GUInt            := 3;
            Tip       : UTF8_String      := "";
            Relief    : Gtk_Relief_Style := Relief_Normal
         )  return Gtk_Button;

These subprograms replace Add_Button. The add a new button to Dialog. Response is the response returned by the dialog's Run when the button is pressed. Label is the text used for the button. If can use mnemonics e.g. "_OK". Icon is the image name, e.g. "gtk-ok". Icon_Left is true when the image to be on the left, when present. Size is the image size. Spacing is the spacing between the label and image. Tip is the tooltip text. Relief is the button shape.

procedure Add_Named
          (  Name : UTF8_String;
             Icon : Gdk_Pixbuf
          );

This procedure is a replacement to Add_Static. It is used in combination with Add_Stock_Attribute, which first searches for the icons registered by this procedure and only then for themed icons. Name is the icon name, case sensitive. Icon the icon. You can add several icons of different sizes under the same name.

procedure Add_Stock_Attribute
          (  Cell_Layout : not null access
                           Gtk_Tree_View_Column_Record'Class;
             Cell        : not null access
                           Gtk_Cell_Renderer_Pixbuf_Record'Class;
             Column      : GInt
          );

This procedure is an equivalent to Add_Attribute (Cell_Layout, Cell, "stock-id", Column), which is deprecated now. It uses "icon-name" instead and adds a cell data function which first searches for the icons added using Add_Named and only then for the themed ones.

5.13. RSVG bindings

The package RSVG and its child RSVG.Handle provide bindings to the GNOME SVG Library (RSVG), a library for rendering SVG and SVGZ files. The package RSVG.Handle declares the following types:

type Create_Result (Success : Boolean := False) is record
   case
Success is
      when
True =>
         Handle : RSVG_Handle;
      when False =>
         Error : GError;
   end case;
end record;

This type is used for the results of SVG object creation that may fail. When the operation was not successful the component Error is the corresponding error. It must be freed by calling to Error_Free. When it was successful then the component Handle is the new SVG object. Note that SVG objects are not widgets. It means that they are created with reference count 1 and must be freed using Unref.

type Dimension_Data is record
   Width  : int;
   Height : int;
   EM     : GDouble;
   EX     : GDouble;
end record;

This type is used for dimensions of an SVG object.

type IO_Result (Success : Boolean := False) is record
   case
Success is
      when
True =>
         null;
      when False =>
         Error : GError;
   end case;
end record;

This type is used for the results of I/O operations that may fail. When the operation was not successful the component Error is the corresponding error. It must be freed by calling to Error_Free.

type Position_Data is record
   X : int;
   Y : int;
end record;

This type is used for positions of an SVG object element.

type RSVG_Handle_Record is
   new
GLib.Object.GObject_Record with null record;
type RSVG_Handle is
   access all
RSVG_Handle_Record'Class;

The object of this type is an SVG object ready to be rendered. The following operations are defined on the type:

function Close
         (  Handle : not null access RSVG_Handle_Record
         )  return IO_Result;

This function closes handle to indicate that loading the image is complete. This will return IO_Result with Success set to true if the loader closed successfully. Note that handle is not freed until Unref is called.

function Get_Base_URI
         (  Handle : not null access RSVG_Handle_Record
         )  return String;

This function gets the base URI for Handle. It can be empty string.

function Get_Dimensions
         (  Handle : not null access RSVG_Handle_Record
         )  return Dimension_Data;

This function gets size of the SVG object Handle. The result has the type Dimension_Data.

function Get_Dimensions_Sub
         (  Handle : not null access RSVG_Handle_Record;
            ID     : String
         )  return Dimension_Data;

This function gets size of an element of the SVG object Handle. The element is specified by the parameter ID. For example, ID "#layer1" specifies element "layer1". The result has the type Dimension_Data.

function Get_Pixbuf
         (  Handle : not null access RSVG_Handle_Record
         )  return Gdk_Pixbuf;

This function returns the pixbuf loaded by Handle. The caller of this function must use Unref to free the result if not Null_Pixbuf, If insufficient data has been read to create the pixbuf, or an error occurred in loading, then Null_Pixbuf will be returned. Note that the pixbuf may not be complete until Close has been called.

function Get_Pixbuf_Sub
         (  Handle : not null access RSVG_Handle_Record;
            ID     : String
         )  return Gdk_Pixbuf;

This function returns the pixbuf loaded by Handle for the element specified by the parameter ID. For example, ID "#layer1" specifies element "layer1".  The caller of this function must use Unref to free the result, if not Null_Pixbuf. If insufficient data has been read to create the pixbuf, or an error occurred in loading, then Null_Pixbuf will be returned. Note that the pixbuf may not be complete until Close has been called.

function Get_Position_Sub
         (  Handle : not null access RSVG_Handle_Record;
            ID     : String
         )  return Dimension_Data;

This function gets position of an element of the SVG object Handle. The element is specified by the parameter ID. For example, ID "#layer1" specifies element "layer1". The result has the type Position_Data.

function Get_Type return GType;

This function returns the type of SVG object.

procedure Gtk_New (Handle : out RSVG_Handle);

This procedure creates a new SVG object. The result must be freed with Unref. This handle can be used for dynamically loading an image. You need to feed it data using Write, then call Close when done. Afterwards, you can render it using Cairo or get a Gdk_Pixbuf from it. When finished, free with Unref. No more than one image can be loaded with one handle.

function Gtk_New_From_Data
         (  Data : Stream_Element_Array
         )  return Create_Result;

This function creates a new SVG object from Data. The result is of Create_Result.

function Gtk_New_From_File
         (  File_Name : String
         )  return Create_Result;

This function creates a new SVG object from a file specified by its name File_Name. The result is of Create_Result.

procedure Gtk_New_With_Flags (Handle : out RSVG_Handle; Flags : Handle_Flags);

This procedure creates a new SVG object. The parameter Flags specified additional flags:

type Handle_Flags is mod 2**2;
pragma Convention (C, Handle_Flags);
Handle_Flags_None           : constant := 0;
Handle_Flag_Unlimited       : constant := 1;
Handle_Flag_Keep_Image_Data : constant := 2;

The result must be freed with Unref. This handle can be used for dynamically loading an image. You need to feed it data using Write, then call Close when done. Afterwards, you can render it using Cairo or get a Gdk_Pixbuf from it. When finished, free with Unref. No more than one image can be loaded with one handle.

procedure Initialize
          (  Handle : not null access RSVG_Handle_Record'Class
          );
procedure
Initialize
          (  Handle : not null access RSVG_Handle_Record'Class;
             Flags  : Handle_Flags
          );
procedure Initialize
          (  Handle : not null access RSVG_Handle_Record'Class;
             Data   : Stream_Element_Array;
             Error  : out IO_Result
          );
procedure
Initialize
          (  Handle    : not null access RSVG_Handle_Record'Class;
             File_Name : UTF8_String;
             Error     : out IO_Result
          );

One of these procedures must be used to initialize any type derived from RSVG_Handle_Record. The last two procedures may fail which is indicated by the Error parameter of IO_Result type. In the case of failure the object is left uninitialized an must be freed or else initialized by some other call.

function Render_Cairo
         (  Handle  : not null access RSVG_Handle_Record;
            Context : Cairo_Context
         )  return Boolean;

This function draws Handle object on the context specified by the parameter Context. On errors the result is false.

function Render_Cairo_Sub
         (  Handle  : not null access RSVG_Handle_Record;
            Context : Cairo_Context;
            ID      : String
         )  return Boolean;

This function draws element ID of the Handle object on the context specified by the parameter Context. On errors the result is false.

procedure Set_Base_URI
          (  Handle : not null access RSVG_Handle_Record;
             URI    : String
          );

This procedure sets the base URI for the SVG Handle. This can only be called before Write has been called.

procedure Set_DPI
          (  Handle : not null access RSVG_Handle_Record;
             DPI    : double
          );

This procedure sets the DPI for the outgoing pixbuf. Common values are 75, 90, and 300 DPI. Passing a number <= 0 to DPI will reset the DPI to whatever the default value happens to be.

procedure Set_DPI_X_Y
          (  Handle : not null access RSVG_Handle_Record;
             X      : double;
             Y      : double
          );

This procedure sets the DPI for the outgoing pixbuf. Common values are 75, 90, and 300 DPI. Passing a number <= 0 to DPI will reset the DPI to whatever the default value happens to be.

function Write
         (  Handle : not null access RSVG_Handle_Record;
            Buffer : Stream_Element_Array
         )  return IO_Result;

This function loads the bytes of the image. This will return IO_Result with Success set true if the data was loaded successful, and false if an error occurred. In the latter case, the loader will be closed, and will not accept further writes. The error will be set to an error from the RsvgError domain. Errors from GIOErrorEnum are also possible.

5.14. Time_Zone

The package GLib.Time_Zone provides bindings to Glib time zone operations.It declares the following types:

type GTime_Type is
     (  G_TIME_TYPE_STANDARD,
        G_TIME_TYPE_DAYLIGHT,
        G_TIME_TYPE_UNIVERSAL
     );

This type defines types of time.

type GTime_Zone (<>) is limited private;

This type is an opaque object kept by GLib that represent a time zone.

function Adjust_Time
         (  TZ         : GTime_Zone;
            Time_Type  : GTime_Type;
            Time_Stamp : GInt64
         )  return GInt;
function Adjust_Time
         (  TZ         : GTime_Zone;
            Time_Stamp : Time
         )  return GInt;

This function searches for a time zone interval corresponding to Time_Stamp. When integer Time_Stamp is the number of seconds from January 1, 1970. The time can be adjusted if necessary. The result is negative when no interval found.

function Find_Interval
         (  TZ         : GTime_Zone;
            Time_Type  : GTime_Type;
            Time_Stamp : GInt64
         )  return GInt;
function Find_Interval
         (  TZ         : GTime_Zone;
            Time_Stamp : Time
         )  return GInt;

This function searches for a time zone interval corresponding to Time_Stamp. When integer Time_Stamp is the number of seconds from January 1, 1970. The result is negative when no interval found.

function Get_Abbreviation
         (  TZ       : GTime_Zone;
            Interval : GInt
         )  return UTF8_String;

This function returns abbreviation of the time corresponding to the interval. Note that the result is what expected, e.g. something like CET. It is OS-dependent and might be something like W.Standard European Time under Windows.

function Get_Identifier
         (  TZ : GTime_Zone
         )  return UTF8_String;

This function returns the time zone description. The description is same as in Gtk_New.

function Get_Offset
         (  TZ       : GTime_Zone;
            Interval : GInt
         )  return Duration;

This function returns the UTC offset of the time corresponding to the interval.

function Gtk_New (Identifier : String) return access GTime_Zone;

This function creates a time zone corresponding to the description. If successful the object must be released by calling Unref.

function Gtk_New_Local return access GTime_Zone;

This function creates a time zone corresponding to the local time used by the OS. If successful the object must be released by calling Unref.

function Gtk_New_Offset
         (  Offset : Duration
         )  return access GTime_Zone;

This function creates a time zone corresponding to the UTC offset specified by Offset. If successful the object must be released by calling Unref.

function Gtk_New_UTC return access GTime_Zone;

This function creates a time zone corresponding to the UTC time. If successful the object must be released by calling Unref.

function Is_DST
         (  TZ       : GTime_Zone;
            Interval : GInt
         )  return Boolean;

This function returns true if the time corresponding to the interval is daylight saving time.

procedure Ref (TZ : GTime_Zone);

This procedure increases the reference count of the time zone object.

procedure Unref (TZ : GTime_Zone);

This procedure decreases the reference count of the time zone object.


[Back][TOC][Next]

6. Handles as GTK+ values

The reference counted objects of simple components can be stored into GTK+ values (GValue object) and passed around to all GTK+ subprograms. For example, they can be put into a tree view model. This way custom Ada objects can be designed for use with GTK+. The generic package Glib.Values.Handle can be instantiated for this purpose:

generic
   Type_Name : in String;
   type Object_Type (<>) is abstract new Object.Entity with private;
   type Object_Type_Ptr  is access Object_Type'Class;
   type Handle_Type (<>) is private;
   with function Ptr (Refernece : Handle_Type)
      return Object_Type_Ptr is <>;
   with function Ref (Object : Object_Type_Ptr)
      return Handle_Type is <>;
package GLib.Values.Handle is ...

The formal parameters are:

The package creates GTK+ type to reference Object_Type'Class. When a GValue object of this type is set to an instance of Object_Type'Class, it acts as a counted reference to it. This prevents the target object from destruction until GValue is not reset to another object or destroyed by Unset. When a GValue is copied the reference count of the target object is increased.

function Get_Type return GType;

This function returns the GTK+ type of values.

function Get_Handle (Value : GValue) return Handle_Type;

This function returns a handle to the object stored in Value. Constraint_Error is propagated when Value is of wrong type.

function Get_Ptr (Value : GValue) return Object_Type_Ptr;

This function returns a pointer to the object stored in Value. The result is null when Value is of wrong type. The pointer can be safely used as long as Value is not reset. This function is intended for a lower level use, and should be avoided in favor of Get_Handle.

procedure Set_Handle
          (  Value     : in out GValue;
             Reference : Handle_Type
          );

This procedure sets Value to the object referenced by Reference. Prior the call Value must be initialized using Init (Value, Get_Type). Constraint_Error is propagated when Value is not properly initialized.

procedure Set_Ptr
          (  Value : in out GValue;
             Ptr   : Object_Type_Ptr
          );

This procedure sets Value to the object  referenced by Ptr. Prior the call Value must be initialized using Init (Value, Get_Type). Constraint_Error is propagated when Value is not properly initialized.


[Back][TOC][Next]

7. Unit selection widget and dialogs

The units of measurements for Ada contains a GTK+ widget and dialog boxes for a comfortable input of measurement units:

unit selection

The widget is provided by the generic package Measures_Gtk_Edit. The dialogs are provided by the child package Measures_Gtk_Edit.Dialogs.


[Back][TOC][Next]

8. Improved HLS color model

The package Gdk_Color.IHLS implements an improved hue-luminance-saturation color model as described in A 3D-polar Coordinate Colour Representation Suitable for Image Analysis by Allan Hanbury and Jean Serra. This color model is closer to human eye perception than HLS and HSV color spaces, yet not so numerically demanding as CIE L*a*b is.

In the IHLS space each color is represented by:

The package defines the following data types:

type Gdk_Hue is new GUInt16;

The value 0 corresponds to the primary Red, the value Gdk_Hue'Modulus/3 does to the primary Green, the value 2*Gdk_Hue'Modulus/3 does to the primary Blue. Gdk_Hue is a modular type which values are wrapped around.

type Gdk_Luminance is new GUInt16;

Higher values of Gdk_Luminance correspond to lighter colors. The type of luminance is chosen conform to the types of the RGB stimuli of Gdk_Color. The luminance is directly evaluated from the stimuli as 0.2126·R + 0.7152· G + 0.0722· B (as it is recommended by International Commission on Illumination).

subtype Gdk_Red_Luminance   is Gdk_Luminance ...;
subtype
Gdk_Green_Luminance is Gdk_Luminance ...;
subtype
Gdk_Blue_Luminance  is Gdk_Luminance ...;

These subtypes define the ranges of the luminance, which the primary colors Red, Green and Blue may take values from. Higher luminance values would lead to color distortion due to truncation of the corresponding stimulus value. Impure and mixed colors may have higher luminance than the primary ones. No value of any hue has the full luminance. The maximal range of luminance available for any combination of hue and saturation is Gdk_Blue_Luminance'Range, which is only 7% of the whole range. Only White has 100% luminance.

type Gdk_Saturation is new GUInt16;

The value 0 corresponds to gray colors, the value Gdk_Staturation'Last corresponds to pure (monochrome) colors. Saturation type is conform to the types of RGB components of Gdk_Color. The saturation is defined through the stimuli as max (R, G, B) - min (R, G, B).

type Gdk_Stimulus is new Float;

The value 0 corresponds to no stimulus. The value 216-1 corresponds to the maximal possible stimulus.

type Gdk_IHLS_Color is record
   Hue        : Gdk_Hue;
   Luminance  : Gdk_Luminance;
   Saturation : Gdk_Saturation;
end record
;

The package Gdk_Color.IHLS provides the following subprograms for dealing with the colors:

function Average (List : Gdk_Color_Array) return Gdk_Color;

Thus function averages the colors of List so that the luminance of the result will be equal to the averaged luminance. Constraint_Error is propagated when List is empty.

function Darken
         (  Color : Gdk_IHLS_Color;
            By    : Gdk_Luminance
         )  return Gdk_IHLS_Color;
function
Darken
         (  Color : Gdk_Color;
            By    : Gdk_Luminance
         )  return Gdk_Color;

These functions darken a color specified by the parameter Color by the luminance defined by the value of the parameter By. The parameter Color can be of either color model. When the value of By exceeds one of Color, the result will have zero luminance (Black).

function Lighten
         (  Color : Gdk_IHLS_Color;
            By    : Gdk_Luminance
         )  return Gdk_IHLS_Color;
function
Lighten
         (  Color    : Gdk_Color;
            By       : Gdk_Luminance;
            Impurify : Boolean := True
         )  return Gdk_Color;

These functions lighten a color specified by the parameter Color by the luminance defined by the value of the parameter By. The result will have the maximal available luminance in the IHLS space. The hue is preserved. For the variant with Color specified in RGB (Gdk_Color), the result luminance might be sufficiently lesser, due to the limitations imposed by the RGB color space. In such cases the parameter Impurify controls if the luminance can be increased at the cost of purity of the result. See the function To_RGB for further information.

function Impurify
         (  Color : Gdk_IHLS_Color;
            By    : Gdk_Saturation
         )  return Gdk_IHLS_Color;
function
Impurify
         (  Color : Gdk_Color;
            By    : Gdk_Saturation
         )  return Gdk_Color;

These functions impurify a color specified by the parameter Color by the saturation defined by the value of the parameter By. When the value of By exceeds one of Color, the result will have zero saturation (Grey).

function Purify
         (  Color : Gdk_IHLS_Color;
            By    : Gdk_Saturation
         )  return Gdk_IHLS_Color;
function
Purify
         (  Color : Gdk_Color;
            By    : Gdk_Saturation
         )  return Gdk_Color;

These functions purify a color specified by the parameter Color by the saturation defined by the value of the parameter By. The result will have maximal available saturation for the hue of Color, which is not always a monochrome color for the variant returning Gdk_Color. Purification of an RGB color (Gdk_Color) may eventually lead to decreasing its luminance as explained below.

function To_RGB
         (  Color    : Gdk_IHLS_Color;
            Impurify : Boolean := True
         )  return Gdk_Color;

This function converts Color to the RGB color space. Note that some colors of the IHLS space do not have counterparts in RGB. In particular pure blue colors have maximal luminance of only about 7% of the whole range  A higher luminance would require a blue stimulus exceeding the maximal possible value of. The parameter Impurify determines the behavior in such cases. When the parameter Impurify is false, the function keeps saturation of the result at the cost of luminance. I.e. the result will appear darker than Color. When Impurify is true, the function will keep luminance making result more impure. I.e. very light colors will appear as white. The procedure To_RGB can be used instead to get the values of the stimuli regardless their ranges for any IHLS color.

procedure To_RGB
          (  Color : Gdk_IHLS_Color;
             Red   : out Gdk_Stimulus;
             Green : out Gdk_Stimulus;
             Blue  : out Gdk_Stimulus
          );

This procedure evaluates the RGB stimuli of Color. The results might be non-presentable as Gdk_Color, e.g. some stimuli could exceed 216-1.

function To_RGB (Stimulus : Gdk_Stimulus) return UInt16;

This function converts Stimulus to a GDK compatible value. It is truncated as necessary.

function To_RGB
          (  Red   : Gdk_Stimulus;
             Green : Gdk_Stimulus;
             Blue  : Gdk_Stimulus
          )  return Gdk_Color;

This function returns the RGB color corresponding to the stimuli. The result has the same hue, but its luminance and to a lesser degree its saturation might be diminished in order to obtain a visible color.

function To_IHLS (Color : Gdk_Color) return Gdk_IHLS_Color;

This function converts Color to the IHLS color space.

function Val
         (  First : Gdk_IHLS_Color;
            Pos   : Natural;
            Cycle : Color_Cycle := 3
         )  return Gdk_IHLS_Color;

This function is used to generate a sequence of distinct colors having same saturation and luminance. The colors of the sequence are ordered by the position starting from 0. The first color of the sequence is First. Each next color up to Color_Cycle-1 is obtained by incrementing the hue of First by Gdk_Hue'Modulus/Color_Cycle. The next Color_Cycle colors are obtained by incrementing the hues of the previously generated colors by Gdk_Hue'Modulus/Color_Cycle2. Then they are incremented again by Gdk_Hue'Modulus/Color_Cycle2, and so on up to the color Color_Cycle2-1. The next Color_Cycle3 colors are generated using the hue step Gdk_Hue'Modulus/Color_Cycle3, and so on. The colors in the sequence do not repeat. They are chosen to maximize the hue distance between subsequent colors. Such sequences are useful for assigning colors to plotted curves. The subtype Color_Cycle is declared as:

subtype Color_Cycle is Positive range 2..Positive'Last


[Back][TOC][Next]

9. Buttons

9.1. Buttons with icons

The package Gtk.Image_Button provides a simplified way of creation buttons which icons. It provides the image button widget:

type Gtk_Image_Button_Record is new Gtk_Button_Record with private;
type
Gtk_Image_Button is access all Gtk_Image_Button_Record'Class;

The following procedures are provided:

function Get_Box
         (  Button : not null access Gtk_Image_Button_Record
         )  return Gtk_Box;

This function returns the button box.

function Get_Label
         (  Button : not null access Gtk_Image_Button_Record
         )  return Gtk_Label;

This function returns the button label.

procedure Gtk_New
          (  Button : out Gtk_Image_Button;
             Image  : not null access Gtk_Widget_Record'Class;
             Label  : UTF8_String := ""
          );

This is the button factory. It creates a new button. The parameter Button is the result. The parameter Image is the image used as the button icon. Label is the button text.

procedure Gtk_New
          (  Button   : out Gtk_Image_Button;
             Stock_Id : String;
             Size     : Gtk_Icon_Size;
             Label    : UTF8_String := ""
          );

This is an alternative button factory. The image is specified by its stock id (Stock_Id) and desired size (Size).

procedure Initialize
          (  Button : not null access Gtk_Image_Button_Record'Class;
             Image  : not null access Gtk_Widget_Record'Class;
             Label  : UTF8_String := ""
          );

This procedure to be called by any descendant of Gtk_Image_Button_Record.

9.2. Buttons controlled by style properties

The generic package Gtk.Generic_Style_Button eases creation of buttons customized by the resource file. The button appearance is thus fully controlled by its style properties:

generic
   Class_Name : UTF8_String;
   Label      : UTF8_String      := "";
   Icon       : UTF8_String      := "";
   Icon_Left  : Boolean          := True;
   Size       : Gtk_Icon_Size    := Icon_Size_Small_Toolbar;
   Spacing    : GUInt            := 3;
   Tip        : UTF8_String      := "";
   Relief     : Gtk_Relief_Style := Relief_Normal;
package Gtk.Generic_Style_Button is ...

The generic parameters of the package are:

Note that the package has to be instantiated at the library level. It defines the type of the button in the standard GtkAda way:

type Gtk_Style_Button_Record is new Gtk_Button_Record with private;
type
Gtk_Style_Button is access all Gtk_Style_Button_Record'Class;

The following procedures are provided:

function Get_Box
         (  Button : not null access Gtk_Style_Button_Record
         )  return Gtk_Box;

This function returns the button box.

function Get_Label
         (  Button : not null access Gtk_Style_Button_Record
         )  return Gtk_Label;

This function returns the button label.

procedure Gtk_New (Button : out Gtk_Style_Button);

This is the button factory. It creates a new button. The parameter Button is the result.

procedure Initialize (Button : not null access Gtk_Style_Button_Record'Class);

This procedure to be called by any descendant of Gtk_Style_Button_Record.

The style properties of Gtk_Style_Button:

Name Type Default Description
icon-id String Icon The stock image used as the icon for the button
icon-left Boolean Icon_Left When true, the icon appears left of the label
icon-size Gtk_Icon_Size Size The icon size
label String Label The button label text
relief-style Gtk_Relief_Style Relief_Normal The button relief style
spacing GUInt Spacing The spacing between icon and label
tip String Tip The tooltip text

The following snippet illustrates how button style properties can be set in a CSS file:

CustomButton {
-CustomButton-label: "Button";
-CustomButton-tip: "Some UTF-8 text";
-CustomButton-icon-left: 0;
-CustomButton-icon-id: "gtk-about";
}

Here CustomButton is the Class_Name used during instantiation of Gtk.Generic_Style_Button. It prefixes the style properties names. The full name path of an button instance depends on its container, which allows different styles assigned to distinct instances of the button. See GTK+ CSS files for further information.


[Back][TOC][Next]

10. Spawning processes

The package GLib.Spawn provides bindings to GTK+ process spawning facilities. The following types are defined in the package:

type GSpawnFlags is new GUInt;
Spawn_Leave_Descriptors_Open : constant GSpawnFlags := ...;
Spawn_Do_Not_Reap_Child      : constant GSpawnFlags := ...;
Spawn_Search_Path            : constant GSpawnFlags := ...;
Spawn_Stdout_To_Dev_Null     : constant GSpawnFlags := ...;
Spawn_Stderr_To_Dev_Null     : constant GSpawnFlags := ...;
Spawn_Child_Inherits_Stdin   : constant GSpawnFlags := ...;
Spawn_File_And_ArgV_Zero     : constant GSpawnFlags := ...;

The type defines process spawning flags:

type GPID is new Interfaces.C.Int;

This is the type identifying the process, when started asynchronously.

type GSpawnChildSetupFunc is access procedure (Data : Address);

The procedure passed in order to perform initialization of the child process.

type Chars_Ptr_Array is
   array
(Positive range <>) of aliased Chars_Ptr;
package Chars_Ptr_Lists is
   new
Interfaces.C.Pointers
       (  Index              => Positive,
          Element            => Chars_Ptr,
          Element_Array      => Chars_Ptr_Array,
          Default_Terminator => Null_Ptr
       );

The package provides a pointer to null-terminated arrays of strings passed as parameters to the subprograms spawning process.

type Async_Result
     (  Running   : Boolean := False;
        Pipelined : Boolean := False
     )  is record
   case
Running is
      when
True =>
         PID : GPID;
         case Pipelined is
            when
True =>
               Standard_Input  : GInt;
               Standard_Output : GInt;
               Standard_Error  : GInt;
            when False =>
               null;
         end case;
      when False =>
         Error : GError;
   end case;
end record;

Objects of this type are returned by procedures that spawn the process asynchronously. The caller is responsible to finalize its fields, when present:

type Sync_Result (Executed : Boolean := False) is record
   case
Executed is
      when
True =>
         Exit_Status     : GInt;
         Standard_Output : Chars_Ptr;
         Standard_Error  : Chars_Ptr;
      when False =>
         Error : GError;
   end case;
end record;

Objects of this type are returned by procedures that spawn the process synchronously. The caller is responsible to finalize its fields, when present:

function Async
         ([ Working_Directory : UTF8_String; ]
            ArgV              : Chars_Ptr_Lists.Pointer;
            EnvP              : Chars_Ptr_Lists.Pointer := null;
            Flags             : GSpawnFlags;
            Child_Setup       : GSpawnChildSetupFunc := null;
            Data              : Address := Null_Address
         )  return Async_Result;

This procedure spawns a process asynchronously, that is the caller is not blocked. Optional parameter Working_Directory specifies the directory to run the process in. ArgV is the list arguments. The first argument specifies the process name. Optional parameter EnvP is the list of process environment variables. When null the environment of the current process is used. Flags is the process spawning flags. Child_Setup is an object used to initialize the child process. The result is of the type Async_Result.

function Async_With_Pipes
         ([ Working_Directory : UTF8_String; ]
            ArgV              : Chars_Ptr_Lists.Pointer;
            EnvP              : Chars_Ptr_Lists.Pointer := null;
            Flags             : GSpawnFlags;
            Child_Setup       : GSpawnChildSetupFunc := null;
            Data              : Address := Null_Address
         )  return Async_Result;

This procedure is similar to Async except that it additionally open pipes to the process' standard input, output and error. Note that this function is very complicated in use. Consider use of Asynchronous_Process instead.

procedure Child_Watch_Add
          (  PID  : GPid;
             Func : Child_Watch_Func;
             Data : Address
         );

This procedure sets Func as a call-back upon process exit. The process is indicated by PID. Data is passed to Func as a parameter.

procedure Close_PID (PID : GPID);

On some platforms, notably Windows, the GPId type represents a resource which must be closed to prevent resource leaking. Close_PID is provided for this purpose. It should be used on all platforms, even though it doesn't do anything under UNIX.

function Command_Line_Async (Command_Line : UTF8_String)
   return
GError;

This procedure spawns a process asynchronously. Command_Line is the command line. When the result is not null, it indicates a spawning error and has to be freed using Error_Free.

function  Command_Line_Sync (Command_Line : UTF8_String)
   return Sync_Result;

This procedure spawns a process synchronously, that is the caller is blocked until completion of the spawned process. Command_Line is the command line. The result is of the type Sync_Result.

function Sync
         ([ Working_Directory : UTF8_String; ]
            ArgV              : Chars_Ptr_Lists.Pointer;
            EnvP              : Chars_Ptr_Lists.Pointer := null;
            Flags             : GSpawnFlags;
            Child_Setup       : GSpawnChildSetupFunc := null;
            User_Data         : Address := Null_Address
         )  return Sync_Result;

This procedure spawns a process synchronously, that is the caller is blocked until completion of the spawned process. Optional parameter Working_Directory specifies the directory to run the process in. ArgV is the list arguments. The first argument specifies the process name. Optional parameter EnvP is the list of process environment variables. Flags is the process spawning flags. Child_Setup is an object used to initialize the child process. The result is of the type Sync_Result.

Notes
  1. This package requires GTK+ (and GLib) properly installed;
  2. Under Windows in order to work, it requires an additional executable program gspawn-win32-helper.exe. When GTK+ is not installed, the helper can still be present as a part of an installation of some third-party software that uses GTK+. For example, it is contained in the GIMP distribution. In such case making the binaries' directory of GIMP to appear in the system path would be sufficient to make process spawning work without installation of GTK+.
  3. The present Windows distribution of GtkAda and GNAT GPS do not include gspawn-win32-helper.exe, though they contain the GTK+ DLLs. Make sure that the path to the directory containing the helper program and the DLLs precedes GtkAda and GNAT GPS binary directories in the PATH variable. Alternatively, you can put a copy of gspawn-win32-helper.exe in the corresponding directory. The rule is that gspawn-win32-helper.exe must be in the same directory as the GTK+ DLLs.

10.1. Spawning process with pipes

The package GLib.Spawn.Asynchronous provides as a higher-level binding than Async_With_Pipes. Since a correct use of the function is very difficult, especially with regard to deadlocking. The typical use of the function in GLib applications is built around single-threaded model of GLib. Ada natively supports  tasking and the provided binding takes an advantage of this allowing concurrent access to the pipes of the asynchronous process. The notification of the process completion is processed in a way that prevents premature closing of the output and error pipes, which might contain data after the process exit. The notification of exit is postponed until all pipes are closed in proper state. The notification is done at the context of the main GTK+ task.

type Process_State is
     (  Process_Running,
        Process_Completed,
        Process_Failed_To_Start
     );

Values of this enumeration type describe the state of the process associated with object of:

type Asynchronous_Process is
   new
Ada.Finalization.Limited_Controlled with private;

The following primitive operations are defined:

procedure Finalize (Process : in out Asynchronous_Process);

When overridden this procedure has to be called from the custom implementation of.

procedure Completed
          (  Process : in out Asynchronous_Process;
             Status  : GInt
          );

This procedure is called on the context of the main GTK+ task upon process exit, when all pipes are already closed. The parameter Status is the process's exist status. The default implementation does nothing.

procedure Error
          (  Process : in out Asynchronous_Process;
             Data    : UTF8_String
          );

This procedure is called to accept a new portion of the process's output into the standard error. Note that this procedure is called from an independent task. Use Gtk.Main.Router facilities if you want to call GTK+ operations from Error. The default implementation does nothing.

procedure Failed
          (  Process : in out Asynchronous_Process;
             Error   : GError
          );

This procedure is called when the process has failed to start. Error indicates the error. It is called from Run, i.e. on the context of the main GTK+ task.

function Get_Error (Process : Asynchronous_Process) return GError;

This function returns the error caused process spawn failure or null.

function Get_State
         (  Process : Asynchronous_Process
         )  return Process_State;

This function returns the process state.

function Get_Exit_Status
         (  Process : Asynchronous_Process
         )  return GInt;

This function returns the exit status of last process execution.

procedure Input
          (  Process : in out Asynchronous_Process;
             Data    : out UTF8_String;
             Count   : out Natural
          );

This procedure is called to get  a new portion of the process's input. The implementation puts it into Data and sets Count to the number of characters put. Count is set to 0 to indicate end of input. This is the default implementation. Note that this procedure is called from an independent task. Use Gtk.Main.Router facilities if you want to call GTK+ operations from Input.

procedure Output
          (  Process : in out Asynchronous_Process;
             Data    : UTF8_String
          );

This procedure is called to accept a new portion of the process's output into the standard output. Note that this procedure is called from an independent task. Use Gtk.Main.Router facilities if you want to call GTK+ operations from Output. The default implementation does nothing.

procedure Run
          (  Process           : in out Asynchronous_Process;
             Name              : UTF8_String;
           [ Working_Directory : UTF8_String; ]
             ArgV              : Chars_Ptr_Array / GList;
           [ EnvP              : Chars_Ptr_Array / GList ]
          );

These procedures are called to spawn the process. The parameter Name indicates the process name. The parameter Working_Directory is optional. When missing the directory of the process is used. ArgV is the list of the arguments starting from the first one. Unlikely to Async_With_Pipes ArgV does not contain the process name. The list is either null-terminated or else a list of strings (see also Gtk.Enums.String_Lists). The optional parameter EnvP is the environment. When omitted the environment of the current process is used. The exception Use_Error is propagated when a process associated with Process is not yet completed. Note that Run has to be used only on the context of the main GTK+ task.

procedure Wait
          (  Process  : in out Asynchronous_Process;
             Time_Out : Duration := Duration'Last
          );

This procedure is called to wait for process completion. Time_Error is propagated when Time_Out is expired. This procedure can be used from any task.

10.2. Text-buffered pipes

The package GLib.Spawn.Text_Bufferred provides an extension of Asynchronous_Process that binds the process standard input, output, and error to Gtk_Text_Buffer:

type Text_Bufferred_Process is new Asynchronous_Process with private;

It has the following operations defined:

procedure Finalize (Process : in out Text_Bufferred_Process);

This procedure is to be called when overridden.

procedure Insert
          (  Process : in out Text_Bufferred_Process;
             Buffer  : access Gtk_Text_Buffer_Record'Class;
             Error   : Boolean;
             Text    : UTF8_String
          );

This procedure is called to put contents into a text buffer. Buffer is the text buffer. Error is true when Buffer is associated with the standard error channel of the process. Otherwise it is the output channel. It can be overridden in order to provide text tags etc. The procedure is called on the context of the main GTK+ task.

procedure Run
          (  Process           : in out Text_Bufferred_Process;
             Name              : UTF8_String;
           [ Working_Directory : UTF8_String; ]
             ArgV              : Chars_Ptr_Array / GList;
           [ EnvP              : Chars_Ptr_Array / GList; ]
             Input             : Gtk_Text_Buffer := null;
             Output            : Gtk_Text_Buffer := null;
             Error             : Gtk_Text_Buffer := null
          );

This procedure calls the process passing the source of Input text buffer to the standard input and putting the standard output and error into Output and Error, correspondingly. Note that Run has to be used only on the context of the main GTK+ task.


[Back][TOC][Next]

11. Helper compilation units

11.1. Constant lists of strings

The package Gtk.Enums.String_Lists provides a simplified way of creation constant lists of strings. When a temporal object of Gtk.Enums.String_Lists.GList is needed it can be created this way:

with Gtk.Enums.String_Lists; use Gtk.Enums.String_Lists;
   ...
begin
   ...
   some_operation (..., +"A"/"B"/"C", ...);

Here the combo box is filled with the strings  "A", "B", "C". The package defines a controlled type

type Controlled_String_List (<>) is limited private;

with the operations:

function Get_GList (List : Controlled_String_List) return String_List.GList;

This function is used to get GList object as in the example above. Note that the result can be used no longer the parameter List leaves the scope. It is recommended not to use it otherwise than for passing it as a parameter to another subprogram like Set_Popdown_Strings.

function "+" (List : Controlled_String_List) return String_List.GList
   renames Get_GList;

This is an alias for Get_GList.

function "/" (Left : Controlled_String_List; Right : UTF8_String)
   return Controlled_String_List;
function
"/" (Left, Right : UTF8_String)
   return Controlled_String_List;

The operator "/" is used for list concatenation and list construction out of two strings.

11.2. Wildcard patterns

The package Gtk.Enums.Strings_List.Wildcards provides tools for matching UTF-8 encoded strings against simple wildcard patterns. A pattern is a list of UTF-8 encoded strings from Gtk.Enums.Strings_List.GList. An empty list matches anything. Otherwise, each string of the list is treated as an alternative. A text is matched when it is by at least one of the alternatives. An alternative can contain any number of wildcard characters (*) which match any, possibly empty, sequence of UTF-8 characters. Other UTF-8 characters are matched as-is. A typical example of a pattern could be:

*.ads
*.adb

consisting of two alternatives for matching Ada-source files.

Note, this package requires Strings_Edit library.

The following subprograms are defined in the package:

function Match
         (  Text    : UTF8_String;
            Pattern : Controlled_String_List
         )  return Boolean;
function Match
         (  Text    : UTF8_String;
            Pattern : String_List.GList
         )  return Boolean;

These functions return true when Text is matched by Pattern.

Any : constant String_List.GList := String_List.Null_List;

This constant defines a pattern that matches anything.

11.3. Object's reference count

function GLib.Object.Ref_Count
         (  Object : access GObject_Record'Class
         )  return GUInt;

This function returns the reference count of a GTK+ object. Procedures Ref, Unref and packing into containers influence the count. When count reaches 0, the object is collected.

Notes. References in GTK+ are quite confusing. Objects are created with the count set to 1, but this does not mean that an explicit Unref should be used to remove them. That depends on the object type. There are two categories of:

When you create an owned object and then put it into a container, you have to call Unref on the object. This will bring its reference count back to 1, so that only the container would own the object. When you create an unowned object it will also have the reference count set to 1. But this count will be flagged as floating. The effect is that when the object gets explicitly referenced, it is said the floating reference sinks, i.e. it is simply dropped. Therefore to call Unref on it would be a critical error. In short, when a new unowned object is put into a container you don't call Unref on it. All objects derived from Gtk.Widget are created floating.

procedure GLib.Object.Checked_Destroy
          (  Object : not null access Gtk_Widget_Record'Class
          );

This procedure can be used instead of the procedure Destroy. It acts same when the object is not floating. Otherwise the floating reference is first removed.

11.4. Enumeration combo box widget

generic
   type
Enum_Type is (<>);
package Gtk.Generic_Enum_Combo_Box is ...

This generic package provides a combo box widget which choices are values of the enumeration type used in an instantiation. The package provides:

type Gtk_Enum_Combo_Box_Record is
   new
Gtk.Combo_Box.Gtk_Combo_Box_Record with null record;
type
Gtk_Enum_Combo_Box is access all Gtk_Enum_Combo_Box_Record'Class;

The widget object type and a pointer to it.

procedure Gtk_New
          (  Combo : out Gtk_Enum_Combo_Box;
             Style : in Gtk.Missed.Enum_Style_Type := Mixed_Case;
             Replace_Underscore_By_Space : in Boolean := False
          );

This procedure creates a new widget. The parameter Style (of the type Enum_Style_Type, declared in the package Gtk.Missed) controls the appearance of the literals:

The parameter Replace_Underscore_By_Space controls whether the underscore character is replaced by space.

procedure Initialize
          (  Combo : access Gtk_Enum_Combo_Box_Record'Class;
             Style : in Gtk.Missed.Enum_Style_Type := Gtk.Missed.Mixed_Case;
             Replace_Underscore_By_Space : in Boolean := False);
          );

This procedure shall be called from the Initialize of the derived widget in order to initialize the object.

procedure Set_Active_Value
          (  Combo : access Gtk_Enum_Combo_Box_Record;
             Value : in Enum_Type
          );

This procedure changes the item selected in the box.

function Get_Active_Value
         (  Combo : access Gtk_Enum_Combo_Box_Record
         )  return Enum_Type;

This function returns the currently selected item in the box. The exception Gtk.Missed.No_Selection is propagated when nothing is selected.

11.5. Resizing custom drawn widgets

Starting with the version 3.0 the method of widget resizing was changed. There is no signal emitted when the widget is about to be resized. The signal configure-event effectively cannot be caught. One technique to handle custom widget size changes is querying its actual size from the handler of the draw event. Normally when the widget is resized it is also redrawn and thus it is enough to call Get_Allocated_Width and Get_Allocated_Height or alternatively Get_Allocation in order to determine the actual size and then render the widget accordingly.

In some cases the problem is that the widget size is wrong. When a descendant of Gtk_Fixed or Get_Drawable gets shrunken as a child of a container, its allocation size is not decreased. To handle this problem one should override the "virtual" operations of the widget responsible for reporting that the widget can be shrunken. The following code snippet illustrates the approach.

Class : Ada_GObject_Class; -- My widget class object

procedure
Initialize
          (  Widget : not null access My_Widget_Record'Class
          )  is
   Properties_To_Install : Boolean := Class = Uninitialized_Class;
begin
   <parent-type-package>.Initialize (Widget, ...);
   Initialize_Class_Record
   (  Widget,
      Null_Array, -- Signals
      Class,
      "My_Widget"
   );
   if Properties_To_Install then
      ... -- Install properties if needed
   end if;
   --
   -- Set handlers respond to sizing requests
   --

   Set_Default_Get_Preferred_Width_Handler
   (  Class,
      Preferred_Width'Access
   );
   Set_Default_Get_Preferred_Height_Handler
   (  Class,
      Preferred_Height'Access
   );
   ...
end
Initialize;

The handlers to deal with the widget size are defined as follows:

procedure Preferred_Height
          (  Widget       : Address;
             Minimum_Size : out GInt;
             Natural_Size : out GInt
          );
pragma
Convention (C, Preferred_Size);

procedure
Preferred_Size
          (  Widget       : Address;
             Minimum_Size : out GInt;
             Natural_Size : out GInt
          )  is
   Stub : My_Widget_Record;
   This : My_Widget;   -- Pointer to Ada object
begin
   This := My_Widget (Get_User_Data (Widget, Stub));
  
Minimum_Size := 1 -- Down to one pixel
   Natural_Size := ... -- Use This to calculate natural height
end
Preferred_Height;


[Back][TOC][Next]

12. Installation

For CentOS, Debian, Fedora, Ubuntu Linux distributions there are pre-compiled packages, see the links on the top of the page.

12.1. Using the source distribution

The software does not require special installation. The archive's content can be put in a directory and used as-is. For users of GNAT compiler the software provides gpr project files, which can be used in the Gnat Programming Studio (GPS).

The packages that binds source view widget require an installation of GtkSourceView. Note that the standard GtkAda distribution does not contain GtkSourceView libraries. You will need to download and install them manually. Normally

Project files Provides Use in custom project
gtkada_contributions GtkAda contributions with "gtkada_contributions.gpr";
gtkada_contributions-rsvg GtkAda contributions with RSVG support with "gtkada_contributions-rsvg.gpr";
gtkada_contributions-source_view GtkAda contributions with source view packages with "gtkada_contributions-source_view.gpr";
components-gtk GtkAda contributions with Simple Components for Ada with "components-gtk.gpr";
components-odbc-gtk GtkAda contributions with Simple Components for Ada and native ODBC bindings with "components-odbc-gtk.gpr";

[Back][TOC][Next]

13. Changes log

The following versions were tested with the compilers:

and the GtkAda versions:

Changes (18 December 2023) to the version 3.31:

Changes (5 August 2022) to the version 3.30:

Changes (16 April 2022) to the version 3.29:

Changes (6 November 2021) to the version 3.28:

Changes (13 December 2020) to the version 3.27:

Changes (10 December 2019) to the version 3.26:

Changes (7 December 2019) to the version 3.25:

Changes (5 August 2019) to the version 3.24:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes (13 May 2019) to the version 3.23:

Changes (5 Aug 2018) to the version 3.22:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes (3 May 2018) to the version 3.21:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes (3 May 2018) to the version 3.21:

Changes (10 February 2018) to the version 3.20:

Changes (28 January 2018) to the version 3.19:

Changes (4 January 2018) to the version 3.18:

Changes (21 February 2017) to the version 3.17:

Changes (20 November 2016) to the version 3.16:

Changes (25 July 2016) to the version 3.15:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes (3 March 2016) to the version 3.14:

Changes (10 October 2015) to the version 3.13:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes (24 August 2015) to the version 3.11:

Changes (29 June 2015) to the version 3.11:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes (2 April 2015) to the version 3.10:

Changes  (24 November 2014) to the version 3.9:

Changes  (24 July 2014) to the version 3.8:

Changes  (1 June 2014) to the version 2.14:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes  (10 August 2012) to the version 2.13:

Changes to the version 2.12:

Changes to the version 2.11:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes to the version 2.10:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes to the version 2.9:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes to the version 2.8:

Changes to the version 2.7:

Changes to the version 2.6:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes to the version 2.5:

Changes to the version 2.4:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes to the version 2.3:

Changes to the version 2.2:

Changes to the version 2.1:

The following versions were tested with the compilers:

and the GtkAda versions:

Necessary notes. GtkAda GPL 2.10.0.has not yet been officially released for Windows platform. An unofficial release of can be found at www.ada-ru.org/win_bin_en thanks to Maxim Reznik, who compiled it from sources. For Linux GtkAda GPL 2.10.0 is officially available in sources and can be routinely compiled from.

Changes to the version 2.0:

Changes to the version 1.8:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes to the version 1.7:

Changes to the version 1.6:

Changes to the version 1.5:

The following versions were tested with the compilers:

and the GtkAda versions:

Changes to the version 1.4:

Changes to the version 1.3:

The following versions were tested with the compilers:

and the GtkAda:

Changes to the version 1.2:

Changes to the version 1.1:

Changes to the version 1.0:

The following versions were tested with the compilers:

and the GtkAda:

The version 1.0.


[Back][TOC]

14. Table of Contents

1 Tasking with GTK+
    1.1. Example
    1.2. Debugging tools
    1.3. GNAT-specific debugging tools
    1.4. Translation of addresses into the source lines
    1.5. Source navigation
    1.6. Debugging GTK+ programs
2 GTK+ tree view
    2.1. Abstract custom model
       2.1.1. Custommodel example
    2.2. Generic sortable model
    2.3. Custom cell renderer
    2.4. Editable renderers
    2.5. Fixed-point renderer
    2.6. Columned model
    2.7. Extension model
    2.8. Abstract browser model and widgets
       2.8.1. Abstract caching store
       2.8.2. Directory tree veiw
       2.8.3. Directory items view
    2.9. Files directory cache and a browsing widget
       2.9.1. Files directory cache
       2.9.2. Files directory browsing widget
       2.9.3. Wildcard browsing widget
    2.10. Persistent storage cache and browsing widget
       2.10.1. Paths, URI, Credentials
       2.10.2. Cache
       2.10.3. Persistent storage tree view
       2.10.4. Persistent storage objects view
       2.10.5. Persistent storage browsing widget
       2.10.6. User credentials input
       2.10.7. User credentials input for GNADE
3 Embeddable images
    3.1. Building xpm2gtkada from the source
    3.2. Usage of xpm2gtkada
    3.3. Memory-mapped images
4 Style properties
    4.1. Installing style properties
    4.2. Querying style properties
    4.3. Querying enumerations
    4.4. Other subprograms
    4.5. Capturing style properties of a widget
5 Missing stuff
    5.1. Handling GTK+ values
    5.2. Controlled strong and weak GTK+ references
    5.3. Controlled references to signal handlers (closures)
    5.4. Managing recently used files (GtkRecentManager)
       5.4.1. Key to value mapping
    5.5. Source view (GtkSourceView)
    5.6. Platform-specific content typing (GContentType)
    5.7. Mounts (GMount)
    5.8. Volumes (GVolume)
    5.9. Drives (GDrive)
    5.10. Volume monitor (GVolumeMonitor)
    5.11. Generic signal handlers
    5.12. Stock items backward compatibility
    5.13. RSVG bindings
    5.14. Time zone
6 Handles as GTK+ values
7 Unit selection widget and dialogs
8 Improved HLS color model
9 Buttons
    9.1. Buttons with icons
    9.2. Buttons controlled by style properties
10 Spawning processes
    10.1. Spawning process with pipes
    10.2. Text-buffered pipes
11 Helper compilation units
    11.1. Constant lists of strings
    11.2. Wildcard patterns
    11.3. Object's reference count
    11.4. Enumeration combo box
    11.5. Resizing custom drawn widgets
12 Installation
    12.1. Using the source distribution
13 Changes log
14 Table of contents