1--  -*- ada -*-
2define(`HTMLNAME',`terminal_interface-curses__ads.htm')dnl
3include(M4MACRO)------------------------------------------------------------------------------
4--                                                                          --
5--                           GNAT ncurses Binding                           --
6--                                                                          --
7--                         Terminal_Interface.Curses                        --
8--                                                                          --
9--                                 S P E C                                  --
10--                                                                          --
11------------------------------------------------------------------------------
12-- Copyright (c) 1998-2006,2007 Free Software Foundation, Inc.              --
13--                                                                          --
14-- Permission is hereby granted, free of charge, to any person obtaining a  --
15-- copy of this software and associated documentation files (the            --
16-- "Software"), to deal in the Software without restriction, including      --
17-- without limitation the rights to use, copy, modify, merge, publish,      --
18-- distribute, distribute with modifications, sublicense, and/or sell       --
19-- copies of the Software, and to permit persons to whom the Software is    --
20-- furnished to do so, subject to the following conditions:                 --
21--                                                                          --
22-- The above copyright notice and this permission notice shall be included  --
23-- in all copies or substantial portions of the Software.                   --
24--                                                                          --
25-- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS  --
26-- OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF               --
27-- MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.   --
28-- IN NO EVENT SHALL THE ABOVE COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM,   --
29-- DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR    --
30-- OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR    --
31-- THE USE OR OTHER DEALINGS IN THE SOFTWARE.                               --
32--                                                                          --
33-- Except as contained in this notice, the name(s) of the above copyright   --
34-- holders shall not be used in advertising or otherwise to promote the     --
35-- sale, use or other dealings in this Software without prior written       --
36-- authorization.                                                           --
37------------------------------------------------------------------------------
38--  Author:  Juergen Pfeifer, 1996
39--  Version Control:
40--  $Revision: 1.41 $
41--  $Date: 2007/05/05 20:33:52 $
42--  Binding Version 01.00
43------------------------------------------------------------------------------
44include(`Base_Defs')
45with System.Storage_Elements;
46with Interfaces.C;   --  We need this for some assertions.
47
48package Terminal_Interface.Curses is
49   pragma Preelaborate (Terminal_Interface.Curses);
50include(`Linker_Options')
51include(`Version_Info')
52   type Window is private;
53   Null_Window : constant Window;
54
55   type Line_Position   is new Natural; --  line coordinate
56   type Column_Position is new Natural; --  column coordinate
57
58   subtype Line_Count   is Line_Position   range 1 .. Line_Position'Last;
59   --  Type to count lines. We do not allow null windows, so must be positive
60   subtype Column_Count is Column_Position range 1 .. Column_Position'Last;
61   --  Type to count columns. We do not allow null windows, so must be positive
62
63   type Key_Code is new Integer;
64   --  That is anything including real characters, special keys and logical
65   --  request codes.
66
67   --  FIXME: The "-1" should be Curses_Err
68   subtype Real_Key_Code is Key_Code range -1 .. M4_KEY_MAX;
69   --  This are the codes that potentially represent a real keystroke.
70   --  Not all codes may be possible on a specific terminal. To check the
71   --  availability of a special key, the Has_Key function is provided.
72
73   subtype Special_Key_Code is Real_Key_Code
74     range M4_SPECIAL_FIRST .. Real_Key_Code'Last;
75   --  Type for a function- or special key number
76
77   subtype Normal_Key_Code is Real_Key_Code range
78     Character'Pos (Character'First) .. Character'Pos (Character'Last);
79   --  This are the codes for regular (incl. non-graphical) characters.
80
81   --  Constants for function- and special keys
82   --
83   Key_None                       : constant Special_Key_Code := M4_SPECIAL_FIRST;
84include(`Key_Definitions')
85   Key_Max                        : constant Special_Key_Code
86     := Special_Key_Code'Last;
87
88   subtype User_Key_Code is Key_Code
89     range (Key_Max + 129) .. Key_Code'Last;
90   --  This is reserved for user defined key codes. The range between Key_Max
91   --  and the first user code is reserved for subsystems like menu and forms.
92
93   --  For those who like to use the original key names we produce them were
94   --  they differ from the original. Please note that they may differ in
95   --  lower/upper case.
96include(`Old_Keys')dnl
97
98------------------------------------------------------------------------------
99
100   type Color_Number is range -1 .. Integer (Interfaces.C.short'Last);
101   for Color_Number'Size use Interfaces.C.short'Size;
102   --  (n)curses uses a short for the color index
103   --  The model is, that a Color_Number is an index into an array of
104   --  (potentially) definable colors. Some of those indices are
105   --  predefined (see below), although they may not really exist.
106
107include(`Color_Defs')
108   type RGB_Value is range 0 .. Integer (Interfaces.C.short'Last);
109   for RGB_Value'Size use Interfaces.C.short'Size;
110   --  Some system may allow to redefine a color by setting RGB values.
111
112   type Color_Pair is range 0 .. 255;
113   for Color_Pair'Size use 8;
114   subtype Redefinable_Color_Pair is Color_Pair range 1 .. 255;
115   --  (n)curses reserves 1 Byte for the color-pair number. Color Pair 0
116   --  is fixed (Black & White). A color pair is simply a combination of
117   --  two colors described by Color_Numbers, one for the foreground and
118   --  the other for the background
119
120include(`Character_Attribute_Set_Rep')
121   --  (n)curses uses all but the lowest 16 Bits for Attributes.
122
123   Normal_Video : constant Character_Attribute_Set := (others => False);
124
125   type Attributed_Character is
126      record
127         Attr  : Character_Attribute_Set;
128         Color : Color_Pair;
129         Ch    : Character;
130      end record;
131   pragma Convention (C, Attributed_Character);
132   --  This is the counterpart for the chtype in C.
133
134include(`AC_Rep')
135   Default_Character : constant Attributed_Character
136     := (Ch    => Character'First,
137         Color => Color_Pair'First,
138         Attr  => (others => False));  --  preelaboratable Normal_Video
139
140   type Attributed_String is array (Positive range <>) of Attributed_Character;
141   pragma Pack (Attributed_String);
142   --  In this binding we allow strings of attributed characters.
143
144   ------------------
145   --  Exceptions  --
146   ------------------
147   Curses_Exception     : exception;
148   Wrong_Curses_Version : exception;
149
150   --  Those exceptions are raised by the ETI (Extended Terminal Interface)
151   --  subpackets for Menu and Forms handling.
152   --
153   Eti_System_Error    : exception;
154   Eti_Bad_Argument    : exception;
155   Eti_Posted          : exception;
156   Eti_Connected       : exception;
157   Eti_Bad_State       : exception;
158   Eti_No_Room         : exception;
159   Eti_Not_Posted      : exception;
160   Eti_Unknown_Command : exception;
161   Eti_No_Match        : exception;
162   Eti_Not_Selectable  : exception;
163   Eti_Not_Connected   : exception;
164   Eti_Request_Denied  : exception;
165   Eti_Invalid_Field   : exception;
166   Eti_Current         : exception;
167
168   --------------------------------------------------------------------------
169   --  External C variables
170   --  Conceptually even in C this are kind of constants, but they are
171   --  initialized and sometimes changed by the library routines at runtime
172   --  depending on the type of terminal. I believe the best way to model
173   --  this is to use functions.
174   --------------------------------------------------------------------------
175
176   function Lines            return Line_Count;
177   pragma Inline (Lines);
178
179   function Columns          return Column_Count;
180   pragma Inline (Columns);
181
182   function Tab_Size         return Natural;
183   pragma Inline (Tab_Size);
184
185   function Number_Of_Colors return Natural;
186   pragma Inline (Number_Of_Colors);
187
188   function Number_Of_Color_Pairs return Natural;
189   pragma Inline (Number_Of_Color_Pairs);
190
191include(`ACS_Map')dnl
192
193   --  MANPAGE(`curs_initscr.3x')
194   --  | Not implemented: newterm, set_term, delscreen
195
196   --  ANCHOR(`stdscr',`Standard_Window')
197   function Standard_Window return Window;
198   --  AKA
199   pragma Inline (Standard_Window);
200
201   --  ANCHOR(`curscr',`Current_Window')
202   function Current_Window return Window;
203   --  AKA
204   pragma Inline (Current_Window);
205
206   --  ANCHOR(`initscr()',`Init_Screen')
207   procedure Init_Screen;
208
209   --  ANCHOR(`initscr()',`Init_Windows')
210   procedure Init_Windows renames Init_Screen;
211   --  AKA
212   pragma Inline (Init_Screen);
213   --  pragma Inline (Init_Windows);
214
215   --  ANCHOR(`endwin()',`End_Windows')
216   procedure End_Windows;
217   --  AKA
218   procedure End_Screen renames End_Windows;
219   pragma Inline (End_Windows);
220   --  pragma Inline (End_Screen);
221
222   --  ANCHOR(`isendwin()',`Is_End_Window')
223   function Is_End_Window return Boolean;
224   --  AKA
225   pragma Inline (Is_End_Window);
226
227   --  MANPAGE(`curs_move.3x')
228
229   --  ANCHOR(`wmove()',`Move_Cursor')
230   procedure Move_Cursor (Win    : in Window := Standard_Window;
231                          Line   : in Line_Position;
232                          Column : in Column_Position);
233   --  AKA
234   --  ALIAS(`move()')
235   pragma Inline (Move_Cursor);
236
237   --  MANPAGE(`curs_addch.3x')
238
239   --  ANCHOR(`waddch()',`Add')
240   procedure Add (Win :  in Window := Standard_Window;
241                  Ch  :  in Attributed_Character);
242   --  AKA
243   --  ALIAS(`addch()')
244
245   procedure Add (Win :  in Window := Standard_Window;
246                  Ch  :  in Character);
247   --  Add a single character at the current logical cursor position to
248   --  the window. Use the current windows attributes.
249
250   --  ANCHOR(`mvwaddch()',`Add')
251   procedure Add
252     (Win    : in Window := Standard_Window;
253      Line   : in Line_Position;
254      Column : in Column_Position;
255      Ch     : in Attributed_Character);
256   --  AKA
257   --  ALIAS(`mvaddch()')
258
259   procedure Add
260     (Win    : in Window := Standard_Window;
261      Line   : in Line_Position;
262      Column : in Column_Position;
263      Ch     : in Character);
264   --  Move to the position and add a single character into the window
265   --  There are more Add routines, so the Inline pragma follows later
266
267   --  ANCHOR(`wechochar()',`Add_With_Immediate_Echo')
268   procedure Add_With_Immediate_Echo
269     (Win : in Window := Standard_Window;
270      Ch  : in Attributed_Character);
271   --  AKA
272   --  ALIAS(`echochar()')
273
274   procedure Add_With_Immediate_Echo
275     (Win : in Window := Standard_Window;
276      Ch  : in Character);
277   --  Add a character and do an immediate refresh of the screen.
278   pragma Inline (Add_With_Immediate_Echo);
279
280   --  MANPAGE(`curs_window.3x')
281   --  Not Implemented: wcursyncup
282
283   --  ANCHOR(`newwin()',`Create')
284   function Create
285     (Number_Of_Lines       : Line_Count;
286      Number_Of_Columns     : Column_Count;
287      First_Line_Position   : Line_Position;
288      First_Column_Position : Column_Position) return Window;
289   --  Not Implemented: Default Number_Of_Lines, Number_Of_Columns
290   --  the C version lets them be 0, see the man page.
291   --  AKA
292   pragma Inline (Create);
293
294   function New_Window
295     (Number_Of_Lines       : Line_Count;
296      Number_Of_Columns     : Column_Count;
297      First_Line_Position   : Line_Position;
298      First_Column_Position : Column_Position) return Window
299     renames Create;
300   --  pragma Inline (New_Window);
301
302   --  ANCHOR(`delwin()',`Delete')
303   procedure Delete (Win : in out Window);
304   --  AKA
305   --  Reset Win to Null_Window
306   pragma Inline (Delete);
307
308   --  ANCHOR(`subwin()',`Sub_Window')
309   function Sub_Window
310     (Win                   : Window := Standard_Window;
311      Number_Of_Lines       : Line_Count;
312      Number_Of_Columns     : Column_Count;
313      First_Line_Position   : Line_Position;
314      First_Column_Position : Column_Position) return Window;
315   --  AKA
316   pragma Inline (Sub_Window);
317
318   --  ANCHOR(`derwin()',`Derived_Window')
319   function Derived_Window
320     (Win                   : Window := Standard_Window;
321      Number_Of_Lines       : Line_Count;
322      Number_Of_Columns     : Column_Count;
323      First_Line_Position   : Line_Position;
324      First_Column_Position : Column_Position) return Window;
325   --  AKA
326   pragma Inline (Derived_Window);
327
328   --  ANCHOR(`dupwin()',`Duplicate')
329   function Duplicate (Win : Window) return Window;
330   --  AKA
331   pragma Inline (Duplicate);
332
333   --  ANCHOR(`mvwin()',`Move_Window')
334   procedure Move_Window (Win    : in Window;
335                          Line   : in Line_Position;
336                          Column : in Column_Position);
337   --  AKA
338   pragma Inline (Move_Window);
339
340   --  ANCHOR(`mvderwin()',`Move_Derived_Window')
341   procedure Move_Derived_Window (Win    : in Window;
342                                  Line   : in Line_Position;
343                                  Column : in Column_Position);
344   --  AKA
345   pragma Inline (Move_Derived_Window);
346
347   --  ANCHOR(`wsyncup()',`Synchronize_Upwards')
348   procedure Synchronize_Upwards (Win : in Window);
349   --  AKA
350   pragma Import (C, Synchronize_Upwards, "wsyncup");
351
352   --  ANCHOR(`wsyncdown()',`Synchronize_Downwards')
353   procedure Synchronize_Downwards (Win : in Window);
354   --  AKA
355   pragma Import (C, Synchronize_Downwards, "wsyncdown");
356
357   --  ANCHOR(`syncok()',`Set_Synch_Mode')
358   procedure Set_Synch_Mode (Win  : in Window := Standard_Window;
359                             Mode : in Boolean := False);
360   --  AKA
361   pragma Inline (Set_Synch_Mode);
362
363   --  MANPAGE(`curs_addstr.3x')
364
365   --  ANCHOR(`waddnstr()',`Add')
366   procedure Add (Win : in Window := Standard_Window;
367                  Str : in String;
368                  Len : in Integer := -1);
369   --  AKA
370   --  ALIAS(`waddstr()')
371   --  ALIAS(`addnstr()')
372   --  ALIAS(`addstr()')
373
374   --  ANCHOR(`mvwaddnstr()',`Add')
375   procedure Add (Win    : in Window := Standard_Window;
376                  Line   : in Line_Position;
377                  Column : in Column_Position;
378                  Str    : in String;
379                  Len    : in Integer := -1);
380   --  AKA
381   --  ALIAS(`mvwaddstr()')
382   --  ALIAS(`mvaddnstr()')
383   --  ALIAS(`mvaddstr()')
384
385   --  MANPAGE(`curs_addchstr.3x')
386
387   --  ANCHOR(`waddchnstr()',`Add')
388   procedure Add (Win : in Window := Standard_Window;
389                  Str : in Attributed_String;
390                  Len : in Integer := -1);
391   --  AKA
392   --  ALIAS(`waddchstr()')
393   --  ALIAS(`addchnstr()')
394   --  ALIAS(`addchstr()')
395
396   --  ANCHOR(`mvwaddchnstr()',`Add')
397   procedure Add (Win    : in Window := Standard_Window;
398                  Line   : in Line_Position;
399                  Column : in Column_Position;
400                  Str    : in Attributed_String;
401                  Len    : in Integer := -1);
402   --  AKA
403   --  ALIAS(`mvwaddchstr()')
404   --  ALIAS(`mvaddchnstr()')
405   --  ALIAS(`mvaddchstr()')
406   pragma Inline (Add);
407
408   --  MANPAGE(`curs_border.3x')
409   --  | Not implemented: mvhline,  mvwhline, mvvline, mvwvline
410   --  | use Move_Cursor then Horizontal_Line or Vertical_Line
411
412   --  ANCHOR(`wborder()',`Border')
413   procedure Border
414     (Win                       : in Window := Standard_Window;
415      Left_Side_Symbol          : in Attributed_Character := Default_Character;
416      Right_Side_Symbol         : in Attributed_Character := Default_Character;
417      Top_Side_Symbol           : in Attributed_Character := Default_Character;
418      Bottom_Side_Symbol        : in Attributed_Character := Default_Character;
419      Upper_Left_Corner_Symbol  : in Attributed_Character := Default_Character;
420      Upper_Right_Corner_Symbol : in Attributed_Character := Default_Character;
421      Lower_Left_Corner_Symbol  : in Attributed_Character := Default_Character;
422      Lower_Right_Corner_Symbol : in Attributed_Character := Default_Character
423     );
424   --  AKA
425   --  ALIAS(`border()')
426   pragma Inline (Border);
427
428   --  ANCHOR(`box()',`Box')
429   procedure Box
430     (Win               : in Window := Standard_Window;
431      Vertical_Symbol   : in Attributed_Character := Default_Character;
432      Horizontal_Symbol : in Attributed_Character := Default_Character);
433   --  AKA
434   pragma Inline (Box);
435
436   --  ANCHOR(`whline()',`Horizontal_Line')
437   procedure Horizontal_Line
438     (Win         : in Window := Standard_Window;
439      Line_Size   : in Natural;
440      Line_Symbol : in Attributed_Character := Default_Character);
441   --  AKA
442   --  ALIAS(`hline()')
443   pragma Inline (Horizontal_Line);
444
445   --  ANCHOR(`wvline()',`Vertical_Line')
446   procedure Vertical_Line
447     (Win         : in Window := Standard_Window;
448      Line_Size   : in Natural;
449      Line_Symbol : in Attributed_Character := Default_Character);
450   --  AKA
451   --  ALIAS(`vline()')
452   pragma Inline (Vertical_Line);
453
454   --  MANPAGE(`curs_getch.3x')
455   --  Not implemented: mvgetch, mvwgetch
456
457   --  ANCHOR(`wgetch()',`Get_Keystroke')
458   function Get_Keystroke (Win : Window := Standard_Window)
459                           return Real_Key_Code;
460   --  AKA
461   --  ALIAS(`getch()')
462   --  Get a character from the keyboard and echo it - if enabled - to the
463   --  window.
464   --  If for any reason (i.e. a timeout) we couldn't get a character the
465   --  returned keycode is Key_None.
466   pragma Inline (Get_Keystroke);
467
468   --  ANCHOR(`ungetch()',`Undo_Keystroke')
469   procedure Undo_Keystroke (Key : in Real_Key_Code);
470   --  AKA
471   pragma Inline (Undo_Keystroke);
472
473   --  ANCHOR(`has_key()',`Has_Key')
474   function Has_Key (Key : Special_Key_Code) return Boolean;
475   --  AKA
476   pragma Inline (Has_Key);
477
478   --  |
479   --  | Some helper functions
480   --  |
481   function Is_Function_Key (Key : Special_Key_Code) return Boolean;
482   --  Return True if the Key is a function key (i.e. one of F0 .. F63)
483   pragma Inline (Is_Function_Key);
484
485   subtype Function_Key_Number is Integer range 0 .. 63;
486   --  (n)curses allows for 64 function keys.
487
488   function Function_Key (Key : Real_Key_Code) return Function_Key_Number;
489   --  Return the number of the function key. If the code is not a
490   --  function key, a CONSTRAINT_ERROR will be raised.
491   pragma Inline (Function_Key);
492
493   function Function_Key_Code (Key : Function_Key_Number) return Real_Key_Code;
494   --  Return the key code for a given function-key number.
495   pragma Inline (Function_Key_Code);
496
497   --  MANPAGE(`curs_attr.3x')
498   --  | Not implemented attr_off,  wattr_off,
499   --  |  attr_on, wattr_on, attr_set, wattr_set
500
501   --  PAIR_NUMBER
502   --  PAIR_NUMBER(c) is the same as c.Color
503
504   --  ANCHOR(`standout()',`Standout')
505   procedure Standout (Win : Window  := Standard_Window;
506                       On  : Boolean := True);
507   --  ALIAS(`wstandout()')
508   --  ALIAS(`wstandend()')
509
510   --  ANCHOR(`wattron()',`Switch_Character_Attribute')
511   procedure Switch_Character_Attribute
512     (Win  : in Window := Standard_Window;
513      Attr : in Character_Attribute_Set := Normal_Video;
514      On   : in Boolean := True); --  if False we switch Off.
515   --  Switches those Attributes set to true in the list.
516   --  AKA
517   --  ALIAS(`wattroff()')
518   --  ALIAS(`attron()')
519   --  ALIAS(`attroff()')
520
521   --  ANCHOR(`wattrset()',`Set_Character_Attributes')
522   procedure Set_Character_Attributes
523     (Win   : in Window := Standard_Window;
524      Attr  : in Character_Attribute_Set := Normal_Video;
525      Color : in Color_Pair := Color_Pair'First);
526   --  AKA
527   --  ALIAS(`attrset()')
528   pragma Inline (Set_Character_Attributes);
529
530   --  ANCHOR(`wattr_get()',`Get_Character_Attributes')
531   function Get_Character_Attribute
532     (Win : in Window := Standard_Window) return Character_Attribute_Set;
533   --  AKA
534   --  ALIAS(`attr_get()')
535
536   --  ANCHOR(`wattr_get()',`Get_Character_Attribute')
537   function Get_Character_Attribute
538     (Win : in Window := Standard_Window) return Color_Pair;
539   --  AKA
540   pragma Inline (Get_Character_Attribute);
541
542   --  ANCHOR(`wcolor_set()',`Set_Color')
543   procedure Set_Color (Win  : in Window := Standard_Window;
544                        Pair : in Color_Pair);
545   --  AKA
546   --  ALIAS(`color_set()')
547   pragma Inline (Set_Color);
548
549   --  ANCHOR(`wchgat()',`Change_Attributes')
550   procedure Change_Attributes
551     (Win   : in Window := Standard_Window;
552      Count : in Integer := -1;
553      Attr  : in Character_Attribute_Set := Normal_Video;
554      Color : in Color_Pair := Color_Pair'First);
555   --  AKA
556   --  ALIAS(`chgat()')
557
558   --  ANCHOR(`mvwchgat()',`Change_Attributes')
559   procedure Change_Attributes
560     (Win    : in Window := Standard_Window;
561      Line   : in Line_Position := Line_Position'First;
562      Column : in Column_Position := Column_Position'First;
563      Count  : in Integer := -1;
564      Attr   : in Character_Attribute_Set := Normal_Video;
565      Color  : in Color_Pair := Color_Pair'First);
566   --  AKA
567   --  ALIAS(`mvchgat()')
568   pragma Inline (Change_Attributes);
569
570   --  MANPAGE(`curs_beep.3x')
571
572   --  ANCHOR(`beep()',`Beep')
573   procedure Beep;
574   --  AKA
575   pragma Inline (Beep);
576
577   --  ANCHOR(`flash()',`Flash_Screen')
578   procedure Flash_Screen;
579   --  AKA
580   pragma Inline (Flash_Screen);
581
582   --  MANPAGE(`curs_inopts.3x')
583
584   --  | Not implemented : typeahead
585   --
586   --  ANCHOR(`cbreak()',`Set_Cbreak_Mode')
587   procedure Set_Cbreak_Mode (SwitchOn : in Boolean := True);
588   --  AKA
589   --  ALIAS(`nocbreak()')
590   pragma Inline (Set_Cbreak_Mode);
591
592   --  ANCHOR(`raw()',`Set_Raw_Mode')
593   procedure Set_Raw_Mode (SwitchOn : in Boolean := True);
594   --  AKA
595   --  ALIAS(`noraw()')
596   pragma Inline (Set_Raw_Mode);
597
598   --  ANCHOR(`echo()',`Set_Echo_Mode')
599   procedure Set_Echo_Mode (SwitchOn : in Boolean := True);
600   --  AKA
601   --  ALIAS(`noecho()')
602   pragma Inline (Set_Echo_Mode);
603
604   --  ANCHOR(`meta()',`Set_Meta_Mode')
605   procedure Set_Meta_Mode (Win      : in Window := Standard_Window;
606                            SwitchOn : in Boolean := True);
607   --  AKA
608   pragma Inline (Set_Meta_Mode);
609
610   --  ANCHOR(`keypad()',`Set_KeyPad_Mode')
611   procedure Set_KeyPad_Mode (Win      : in Window := Standard_Window;
612                              SwitchOn : in Boolean := True);
613   --  AKA
614   pragma Inline (Set_KeyPad_Mode);
615
616   function Get_KeyPad_Mode (Win : in Window := Standard_Window)
617                             return Boolean;
618   --  This has no pendant in C. There you've to look into the WINDOWS
619   --  structure to get the value. Bad practice, not repeated in Ada.
620
621   type Half_Delay_Amount is range 1 .. 255;
622
623   --  ANCHOR(`halfdelay()',`Half_Delay')
624   procedure Half_Delay (Amount : in Half_Delay_Amount);
625   --  AKA
626   pragma Inline (Half_Delay);
627
628   --  ANCHOR(`intrflush()',`Set_Flush_On_Interrupt_Mode')
629   procedure Set_Flush_On_Interrupt_Mode
630     (Win  : in Window := Standard_Window;
631      Mode : in Boolean := True);
632   --  AKA
633   pragma Inline (Set_Flush_On_Interrupt_Mode);
634
635   --  ANCHOR(`qiflush()',`Set_Queue_Interrupt_Mode')
636   procedure Set_Queue_Interrupt_Mode
637     (Win   : in Window := Standard_Window;
638      Flush : in Boolean := True);
639   --  AKA
640   --  ALIAS(`noqiflush()')
641   pragma Inline (Set_Queue_Interrupt_Mode);
642
643   --  ANCHOR(`nodelay()',`Set_NoDelay_Mode')
644   procedure Set_NoDelay_Mode
645     (Win  : in Window := Standard_Window;
646      Mode : in Boolean := False);
647   --  AKA
648   pragma Inline (Set_NoDelay_Mode);
649
650   type Timeout_Mode is (Blocking, Non_Blocking, Delayed);
651
652   --  ANCHOR(`wtimeout()',`Set_Timeout_Mode')
653   procedure Set_Timeout_Mode (Win    : in Window := Standard_Window;
654                               Mode   : in Timeout_Mode;
655                               Amount : in Natural); --  in Milliseconds
656   --  AKA
657   --  ALIAS(`timeout()')
658   --  Instead of overloading the semantic of the sign of amount, we
659   --  introduce the Timeout_Mode parameter. This should improve
660   --  readability. For Blocking and Non_Blocking, the Amount is not
661   --  evaluated.
662   --  We don't inline this procedure.
663
664   --  ANCHOR(`notimeout()',`Set_Escape_Time_Mode')
665   procedure Set_Escape_Timer_Mode
666     (Win       : in Window := Standard_Window;
667      Timer_Off : in Boolean := False);
668   --  AKA
669   pragma Inline (Set_Escape_Timer_Mode);
670
671   --  MANPAGE(`curs_outopts.3x')
672
673   --  ANCHOR(`nl()',`Set_NL_Mode')
674   procedure Set_NL_Mode (SwitchOn : in Boolean := True);
675   --  AKA
676   --  ALIAS(`nonl()')
677   pragma Inline (Set_NL_Mode);
678
679   --  ANCHOR(`clearok()',`Clear_On_Next_Update')
680   procedure Clear_On_Next_Update
681     (Win      : in Window := Standard_Window;
682      Do_Clear : in Boolean := True);
683   --  AKA
684   pragma Inline (Clear_On_Next_Update);
685
686   --  ANCHOR(`idlok()',`Use_Insert_Delete_Line')
687   procedure Use_Insert_Delete_Line
688     (Win    : in Window := Standard_Window;
689      Do_Idl : in Boolean := True);
690   --  AKA
691   pragma Inline (Use_Insert_Delete_Line);
692
693   --  ANCHOR(`idcok()',`Use_Insert_Delete_Character')
694   procedure Use_Insert_Delete_Character
695     (Win    : in Window := Standard_Window;
696      Do_Idc : in Boolean := True);
697   --  AKA
698   pragma Inline (Use_Insert_Delete_Character);
699
700   --  ANCHOR(`leaveok()',`Leave_Cursor_After_Update')
701   procedure Leave_Cursor_After_Update
702     (Win      : in Window := Standard_Window;
703      Do_Leave : in Boolean := True);
704   --  AKA
705   pragma Inline (Leave_Cursor_After_Update);
706
707   --  ANCHOR(`immedok()',`Immediate_Update_Mode')
708   procedure Immediate_Update_Mode
709     (Win  : in Window := Standard_Window;
710      Mode : in Boolean := False);
711   --  AKA
712   pragma Inline (Immediate_Update_Mode);
713
714   --  ANCHOR(`scrollok()',`Allow_Scrolling')
715   procedure Allow_Scrolling
716     (Win  : in Window := Standard_Window;
717      Mode : in Boolean := False);
718   --  AKA
719   pragma Inline (Allow_Scrolling);
720
721   function Scrolling_Allowed (Win : Window := Standard_Window) return Boolean;
722   --  There is no such function in the C interface.
723   pragma Inline (Scrolling_Allowed);
724
725   --  ANCHOR(`wsetscrreg()',`Set_Scroll_Region')
726   procedure Set_Scroll_Region
727     (Win         : in Window := Standard_Window;
728      Top_Line    : in Line_Position;
729      Bottom_Line : in Line_Position);
730   --  AKA
731   --  ALIAS(`setscrreg()')
732   pragma Inline (Set_Scroll_Region);
733
734   --  MANPAGE(`curs_refresh.3x')
735
736   --  ANCHOR(`doupdate()',`Update_Screen')
737   procedure Update_Screen;
738   --  AKA
739   pragma Inline (Update_Screen);
740
741   --  ANCHOR(`wrefresh()',`Refresh')
742   procedure Refresh (Win : in Window := Standard_Window);
743   --  AKA
744   --  There is an overloaded Refresh for Pads.
745   --  The Inline pragma appears there
746   --  ALIAS(`refresh()')
747
748   --  ANCHOR(`wnoutrefresh()',`Refresh_Without_Update')
749   procedure Refresh_Without_Update
750     (Win : in Window := Standard_Window);
751   --  AKA
752   --  There is an overloaded Refresh_Without_Update for Pads.
753   --  The Inline pragma appears there
754
755   --  ANCHOR(`redrawwin()',`Redraw')
756   procedure Redraw (Win : in Window := Standard_Window);
757   --  AKA
758
759   --  ANCHOR(`wredrawln()',`Redraw')
760   procedure Redraw (Win        : in Window := Standard_Window;
761                     Begin_Line : in Line_Position;
762                     Line_Count : in Positive);
763   --  AKA
764   pragma Inline (Redraw);
765
766   --  MANPAGE(`curs_clear.3x')
767
768   --  ANCHOR(`werase()',`Erase')
769   procedure Erase (Win : in Window := Standard_Window);
770   --  AKA
771   --  ALIAS(`erase()')
772   pragma Inline (Erase);
773
774   --  ANCHOR(`wclear()',`Clear')
775   procedure Clear
776     (Win : in Window := Standard_Window);
777   --  AKA
778   --  ALIAS(`clear()')
779   pragma Inline (Clear);
780
781   --  ANCHOR(`wclrtobot()',`Clear_To_End_Of_Screen')
782   procedure Clear_To_End_Of_Screen
783     (Win : in Window := Standard_Window);
784   --  AKA
785   --  ALIAS(`clrtobot()')
786   pragma Inline (Clear_To_End_Of_Screen);
787
788   --  ANCHOR(`wclrtoeol()',`Clear_To_End_Of_Line')
789   procedure Clear_To_End_Of_Line
790     (Win : in Window := Standard_Window);
791   --  AKA
792   --  ALIAS(`clrtoeol()')
793   pragma Inline (Clear_To_End_Of_Line);
794
795   --  MANPAGE(`curs_bkgd.3x')
796
797   --  ANCHOR(`wbkgdset()',`Set_Background')
798   --  TODO: we could have Set_Background(Window; Character_Attribute_Set)
799   --  because in C it is common to see bkgdset(A_BOLD) or
800   --  bkgdset(COLOR_PAIR(n))
801   procedure Set_Background
802     (Win : in Window := Standard_Window;
803      Ch  : in Attributed_Character);
804   --  AKA
805   --  ALIAS(`bkgdset()')
806   pragma Inline (Set_Background);
807
808   --  ANCHOR(`wbkgd()',`Change_Background')
809   procedure Change_Background
810     (Win : in Window := Standard_Window;
811      Ch  : in Attributed_Character);
812   --  AKA
813   --  ALIAS(`bkgd()')
814   pragma Inline (Change_Background);
815
816   --  ANCHOR(`wbkgdget()',`Get_Background')
817   --  ? wbkgdget is not listed in curs_bkgd, getbkgd is thpough.
818   function Get_Background (Win : Window := Standard_Window)
819     return Attributed_Character;
820   --  AKA
821   --  ALIAS(`bkgdget()')
822   pragma Inline (Get_Background);
823
824   --  MANPAGE(`curs_touch.3x')
825
826   --  ANCHOR(`untouchwin()',`Untouch')
827   procedure Untouch (Win : in Window := Standard_Window);
828   --  AKA
829   pragma Inline (Untouch);
830
831   --  ANCHOR(`touchwin()',`Touch')
832   procedure Touch (Win : in Window := Standard_Window);
833   --  AKA
834
835   --  ANCHOR(`touchline()',`Touch')
836   procedure Touch (Win   : in Window := Standard_Window;
837                    Start : in Line_Position;
838                    Count : in Positive);
839   --  AKA
840   pragma Inline (Touch);
841
842   --  ANCHOR(`wtouchln()',`Change_Line_Status')
843   procedure Change_Lines_Status (Win   : in Window := Standard_Window;
844                                  Start : in Line_Position;
845                                  Count : in Positive;
846                                  State : in Boolean);
847   --  AKA
848   pragma Inline (Change_Lines_Status);
849
850   --  ANCHOR(`is_linetouched()',`Is_Touched')
851   function Is_Touched (Win  : Window := Standard_Window;
852                        Line : Line_Position) return Boolean;
853   --  AKA
854
855   --  ANCHOR(`is_wintouched()',`Is_Touched')
856   function Is_Touched (Win : Window := Standard_Window) return Boolean;
857   --  AKA
858   pragma Inline (Is_Touched);
859
860   --  MANPAGE(`curs_overlay.3x')
861
862   --  ANCHOR(`copywin()',`Copy')
863   procedure Copy
864     (Source_Window            : in Window;
865      Destination_Window       : in Window;
866      Source_Top_Row           : in Line_Position;
867      Source_Left_Column       : in Column_Position;
868      Destination_Top_Row      : in Line_Position;
869      Destination_Left_Column  : in Column_Position;
870      Destination_Bottom_Row   : in Line_Position;
871      Destination_Right_Column : in Column_Position;
872      Non_Destructive_Mode     : in Boolean := True);
873   --  AKA
874   pragma Inline (Copy);
875
876   --  ANCHOR(`overwrite()',`Overwrite')
877   procedure Overwrite (Source_Window      : in Window;
878                        Destination_Window : in Window);
879   --  AKA
880   pragma Inline (Overwrite);
881
882   --  ANCHOR(`overlay()',`Overlay')
883   procedure Overlay (Source_Window      : in Window;
884                      Destination_Window : in Window);
885   --  AKA
886   pragma Inline (Overlay);
887
888   --  MANPAGE(`curs_deleteln.3x')
889
890   --  ANCHOR(`winsdelln()',`Insert_Delete_Lines')
891   procedure Insert_Delete_Lines
892     (Win   : in Window  := Standard_Window;
893      Lines : in Integer := 1); --  default is to insert one line above
894   --  AKA
895   --  ALIAS(`insdelln()')
896   pragma Inline (Insert_Delete_Lines);
897
898   --  ANCHOR(`wdeleteln()',`Delete_Line')
899   procedure Delete_Line (Win : in Window := Standard_Window);
900   --  AKA
901   --  ALIAS(`deleteln()')
902   pragma Inline (Delete_Line);
903
904   --  ANCHOR(`winsertln()',`Insert_Line')
905   procedure Insert_Line (Win : in Window := Standard_Window);
906   --  AKA
907   --  ALIAS(`insertln()')
908   pragma Inline (Insert_Line);
909
910   --  MANPAGE(`curs_getyx.3x')
911
912   --  ANCHOR(`getmaxyx()',`Get_Size')
913   procedure Get_Size
914     (Win               : in Window := Standard_Window;
915      Number_Of_Lines   : out Line_Count;
916      Number_Of_Columns : out Column_Count);
917   --  AKA
918   pragma Inline (Get_Size);
919
920   --  ANCHOR(`getbegyx()',`Get_Window_Position')
921   procedure Get_Window_Position
922     (Win             : in Window := Standard_Window;
923      Top_Left_Line   : out Line_Position;
924      Top_Left_Column : out Column_Position);
925   --  AKA
926   pragma Inline (Get_Window_Position);
927
928   --  ANCHOR(`getyx()',`Get_Cursor_Position')
929   procedure Get_Cursor_Position
930     (Win    : in  Window := Standard_Window;
931      Line   : out Line_Position;
932      Column : out Column_Position);
933   --  AKA
934   pragma Inline (Get_Cursor_Position);
935
936   --  ANCHOR(`getparyx()',`Get_Origin_Relative_To_Parent')
937   procedure Get_Origin_Relative_To_Parent
938     (Win                : in  Window;
939      Top_Left_Line      : out Line_Position;
940      Top_Left_Column    : out Column_Position;
941      Is_Not_A_Subwindow : out Boolean);
942   --  AKA
943   --  Instead of placing -1 in the coordinates as return, we use a boolean
944   --  to return the info that the window has no parent.
945   pragma Inline (Get_Origin_Relative_To_Parent);
946
947   --  MANPAGE(`curs_pad.3x')
948
949   --  ANCHOR(`newpad()',`New_Pad')
950   function New_Pad (Lines   : Line_Count;
951                     Columns : Column_Count) return Window;
952   --  AKA
953   pragma Inline (New_Pad);
954
955   --  ANCHOR(`subpad()',`Sub_Pad')
956   function Sub_Pad
957     (Pad                   : Window;
958      Number_Of_Lines       : Line_Count;
959      Number_Of_Columns     : Column_Count;
960      First_Line_Position   : Line_Position;
961      First_Column_Position : Column_Position) return Window;
962   --  AKA
963   pragma Inline (Sub_Pad);
964
965   --  ANCHOR(`prefresh()',`Refresh')
966   procedure Refresh
967     (Pad                      : in Window;
968      Source_Top_Row           : in Line_Position;
969      Source_Left_Column       : in Column_Position;
970      Destination_Top_Row      : in Line_Position;
971      Destination_Left_Column  : in Column_Position;
972      Destination_Bottom_Row   : in Line_Position;
973      Destination_Right_Column : in Column_Position);
974   --  AKA
975   pragma Inline (Refresh);
976
977   --  ANCHOR(`pnoutrefresh()',`Refresh_Without_Update')
978   procedure Refresh_Without_Update
979     (Pad                      : in Window;
980      Source_Top_Row           : in Line_Position;
981      Source_Left_Column       : in Column_Position;
982      Destination_Top_Row      : in Line_Position;
983      Destination_Left_Column  : in Column_Position;
984      Destination_Bottom_Row   : in Line_Position;
985      Destination_Right_Column : in Column_Position);
986   --  AKA
987   pragma Inline (Refresh_Without_Update);
988
989   --  ANCHOR(`pechochar()',`Add_Character_To_Pad_And_Echo_It')
990   procedure Add_Character_To_Pad_And_Echo_It
991     (Pad : in Window;
992      Ch  : in Attributed_Character);
993   --  AKA
994
995   procedure Add_Character_To_Pad_And_Echo_It
996     (Pad : in Window;
997      Ch  : in Character);
998   pragma Inline (Add_Character_To_Pad_And_Echo_It);
999
1000   --  MANPAGE(`curs_scroll.3x')
1001
1002   --  ANCHOR(`wscrl()',`Scroll')
1003   procedure Scroll (Win    : in Window  := Standard_Window;
1004                     Amount : in Integer := 1);
1005   --  AKA
1006   --  ALIAS(`scroll()')
1007   --  ALIAS(`scrl()')
1008   pragma Inline (Scroll);
1009
1010   --  MANPAGE(`curs_delch.3x')
1011
1012   --  ANCHOR(`wdelch()',`Delete_Character')
1013   procedure Delete_Character (Win : in Window := Standard_Window);
1014   --  AKA
1015   --  ALIAS(`delch()')
1016
1017   --  ANCHOR(`mvwdelch()',`Delete_Character')
1018   procedure Delete_Character
1019     (Win    : in Window := Standard_Window;
1020      Line   : in Line_Position;
1021      Column : in Column_Position);
1022   --  AKA
1023   --  ALIAS(`mvdelch()')
1024   pragma Inline (Delete_Character);
1025
1026   --  MANPAGE(`curs_inch.3x')
1027
1028   --  ANCHOR(`winch()',`Peek')
1029   function Peek (Win : Window := Standard_Window)
1030     return Attributed_Character;
1031   --  ALIAS(`inch()')
1032   --  AKA
1033
1034   --  ANCHOR(`mvwinch()',`Peek')
1035   function Peek
1036     (Win    : Window := Standard_Window;
1037      Line   : Line_Position;
1038      Column : Column_Position) return Attributed_Character;
1039   --  AKA
1040   --  ALIAS(`mvinch()')
1041   --  More Peek's follow, pragma Inline appears later.
1042
1043   --  MANPAGE(`curs_insch.3x')
1044
1045   --  ANCHOR(`winsch()',`Insert')
1046   procedure Insert (Win : in Window := Standard_Window;
1047                     Ch  : in Attributed_Character);
1048   --  AKA
1049   --  ALIAS(`insch()')
1050
1051   --  ANCHOR(`mvwinsch()',`Insert')
1052   procedure Insert (Win    : in Window := Standard_Window;
1053                     Line   : in Line_Position;
1054                     Column : in Column_Position;
1055                     Ch     : in Attributed_Character);
1056   --  AKA
1057   --  ALIAS(`mvinsch()')
1058
1059   --  MANPAGE(`curs_insstr.3x')
1060
1061   --  ANCHOR(`winsnstr()',`Insert')
1062   procedure Insert (Win : in Window := Standard_Window;
1063                     Str : in String;
1064                     Len : in Integer := -1);
1065   --  AKA
1066   --  ALIAS(`winsstr()')
1067   --  ALIAS(`insnstr()')
1068   --  ALIAS(`insstr()')
1069
1070   --  ANCHOR(`mvwinsnstr()',`Insert')
1071   procedure Insert (Win    : in Window := Standard_Window;
1072                     Line   : in Line_Position;
1073                     Column : in Column_Position;
1074                     Str    : in String;
1075                     Len    : in Integer := -1);
1076   --  AKA
1077   --  ALIAS(`mvwinsstr()')
1078   --  ALIAS(`mvinsnstr()')
1079   --  ALIAS(`mvinsstr()')
1080   pragma Inline (Insert);
1081
1082   --  MANPAGE(`curs_instr.3x')
1083
1084   --  ANCHOR(`winnstr()',`Peek')
1085   procedure Peek (Win : in  Window := Standard_Window;
1086                   Str : out String;
1087                   Len : in  Integer := -1);
1088   --  AKA
1089   --  ALIAS(`winstr()')
1090   --  ALIAS(`innstr()')
1091   --  ALIAS(`instr()')
1092
1093   --  ANCHOR(`mvwinnstr()',`Peek')
1094   procedure Peek (Win    : in  Window := Standard_Window;
1095                   Line   : in  Line_Position;
1096                   Column : in  Column_Position;
1097                   Str    : out String;
1098                   Len    : in  Integer := -1);
1099   --  AKA
1100   --  ALIAS(`mvwinstr()')
1101   --  ALIAS(`mvinnstr()')
1102   --  ALIAS(`mvinstr()')
1103
1104   --  MANPAGE(`curs_inchstr.3x')
1105
1106   --  ANCHOR(`winchnstr()',`Peek')
1107   procedure Peek (Win : in  Window := Standard_Window;
1108                   Str : out Attributed_String;
1109                   Len : in  Integer := -1);
1110   --  AKA
1111   --  ALIAS(`winchstr()')
1112   --  ALIAS(`inchnstr()')
1113   --  ALIAS(`inchstr()')
1114
1115   --  ANCHOR(`mvwinchnstr()',`Peek')
1116   procedure Peek (Win    : in  Window := Standard_Window;
1117                   Line   : in  Line_Position;
1118                   Column : in  Column_Position;
1119                   Str    : out Attributed_String;
1120                   Len    : in  Integer := -1);
1121   --  AKA
1122   --  ALIAS(`mvwinchstr()')
1123   --  ALIAS(`mvinchnstr()')
1124   --  ALIAS(`mvinchstr()')
1125   --  We don't inline the Peek procedures
1126
1127   --  MANPAGE(`curs_getstr.3x')
1128
1129   --  ANCHOR(`wgetnstr()',`Get')
1130   procedure Get (Win : in  Window := Standard_Window;
1131                  Str : out String;
1132                  Len : in  Integer := -1);
1133   --  AKA
1134   --  ALIAS(`wgetstr()')
1135   --  ALIAS(`getnstr()')
1136   --  ALIAS(`getstr()')
1137   --  actually getstr is not supported because that results in buffer
1138   --  overflows.
1139
1140   --  ANCHOR(`mvwgetnstr()',`Get')
1141   procedure Get (Win    : in  Window := Standard_Window;
1142                  Line   : in  Line_Position;
1143                  Column : in  Column_Position;
1144                  Str    : out String;
1145                  Len    : in  Integer := -1);
1146   --  AKA
1147   --  ALIAS(`mvwgetstr()')
1148   --  ALIAS(`mvgetnstr()')
1149   --  ALIAS(`mvgetstr()')
1150   --  Get is not inlined
1151
1152   --  MANPAGE(`curs_slk.3x')
1153
1154   --  Not Implemented: slk_attr_on, slk_attr_off, slk_attr_set
1155
1156   type Soft_Label_Key_Format is (Three_Two_Three,
1157                                  Four_Four,
1158                                  PC_Style,              --  ncurses specific
1159                                  PC_Style_With_Index);  --  "
1160   type Label_Number is new Positive range 1 .. 12;
1161   type Label_Justification is (Left, Centered, Right);
1162
1163   --  ANCHOR(`slk_init()',`Init_Soft_Label_Keys')
1164   procedure Init_Soft_Label_Keys
1165     (Format : in Soft_Label_Key_Format := Three_Two_Three);
1166   --  AKA
1167   pragma Inline (Init_Soft_Label_Keys);
1168
1169   --  ANCHOR(`slk_set()',`Set_Soft_Label_Key')
1170   procedure Set_Soft_Label_Key (Label : in Label_Number;
1171                                 Text  : in String;
1172                                 Fmt   : in Label_Justification := Left);
1173   --  AKA
1174   --  We don't inline this procedure
1175
1176   --  ANCHOR(`slk_refresh()',`Refresh_Soft_Label_Key')
1177   procedure Refresh_Soft_Label_Keys;
1178   --  AKA
1179   pragma Inline (Refresh_Soft_Label_Keys);
1180
1181   --  ANCHOR(`slk_noutrefresh()',`Refresh_Soft_Label_Keys_Without_Update')
1182   procedure Refresh_Soft_Label_Keys_Without_Update;
1183   --  AKA
1184   pragma Inline (Refresh_Soft_Label_Keys_Without_Update);
1185
1186   --  ANCHOR(`slk_label()',`Get_Soft_Label_Key')
1187   procedure Get_Soft_Label_Key (Label : in Label_Number;
1188                                 Text  : out String);
1189   --  AKA
1190
1191   --  ANCHOR(`slk_label()',`Get_Soft_Label_Key')
1192   function Get_Soft_Label_Key (Label : in Label_Number) return String;
1193   --  AKA
1194   --  Same as function
1195   pragma Inline (Get_Soft_Label_Key);
1196
1197   --  ANCHOR(`slk_clear()',`Clear_Soft_Label_Keys')
1198   procedure Clear_Soft_Label_Keys;
1199   --  AKA
1200   pragma Inline (Clear_Soft_Label_Keys);
1201
1202   --  ANCHOR(`slk_restore()',`Restore_Soft_Label_Keys')
1203   procedure Restore_Soft_Label_Keys;
1204   --  AKA
1205   pragma Inline (Restore_Soft_Label_Keys);
1206
1207   --  ANCHOR(`slk_touch()',`Touch_Soft_Label_Keys')
1208   procedure Touch_Soft_Label_Keys;
1209   --  AKA
1210   pragma Inline (Touch_Soft_Label_Keys);
1211
1212   --  ANCHOR(`slk_attron()',`Switch_Soft_Label_Key_Attributes')
1213   procedure Switch_Soft_Label_Key_Attributes
1214     (Attr : in Character_Attribute_Set;
1215      On   : in Boolean := True);
1216   --  AKA
1217   --  ALIAS(`slk_attroff()')
1218   pragma Inline (Switch_Soft_Label_Key_Attributes);
1219
1220   --  ANCHOR(`slk_attrset()',`Set_Soft_Label_Key_Attributes')
1221   procedure Set_Soft_Label_Key_Attributes
1222     (Attr  : in Character_Attribute_Set := Normal_Video;
1223      Color : in Color_Pair := Color_Pair'First);
1224   --  AKA
1225   pragma Inline (Set_Soft_Label_Key_Attributes);
1226
1227   --  ANCHOR(`slk_attr()',`Get_Soft_Label_Key_Attributes')
1228   function Get_Soft_Label_Key_Attributes return Character_Attribute_Set;
1229   --  AKA
1230
1231   --  ANCHOR(`slk_attr()',`Get_Soft_Label_Key_Attributes')
1232   function Get_Soft_Label_Key_Attributes return Color_Pair;
1233   --  AKA
1234   pragma Inline (Get_Soft_Label_Key_Attributes);
1235
1236   --  ANCHOR(`slk_color()',`Set_Soft_Label_Key_Color')
1237   procedure Set_Soft_Label_Key_Color (Pair : in Color_Pair);
1238   --  AKA
1239   pragma Inline (Set_Soft_Label_Key_Color);
1240
1241   --  MANPAGE(`keybound.3x')
1242   --  Not Implemented: keybound
1243
1244   --  MANPAGE(`keyok.3x')
1245
1246   --  ANCHOR(`keyok()',`Enable_Key')
1247   procedure Enable_Key (Key    : in Special_Key_Code;
1248                         Enable : in Boolean := True);
1249   --  AKA
1250   pragma Inline (Enable_Key);
1251
1252   --  MANPAGE(`define_key.3x')
1253
1254   --  ANCHOR(`define_key()',`Define_Key')
1255   procedure Define_Key (Definition : in String;
1256                         Key        : in Special_Key_Code);
1257   --  AKA
1258   pragma Inline (Define_Key);
1259
1260   --  MANPAGE(`curs_util.3x')
1261
1262   --  | Not implemented : filter, use_env
1263   --  | putwin, getwin are in the child package PutWin
1264   --
1265
1266   --  ANCHOR(`keyname()',`Key_Name')
1267   procedure Key_Name (Key  : in  Real_Key_Code;
1268                       Name : out String);
1269   --  AKA
1270   --  The external name for a real keystroke.
1271
1272   --  ANCHOR(`keyname()',`Key_Name')
1273   function Key_Name (Key  : in  Real_Key_Code) return String;
1274   --  AKA
1275   --  Same as function
1276   --  We don't inline this routine
1277
1278   --  ANCHOR(`unctrl()',`Un_Control')
1279   procedure Un_Control (Ch  : in Attributed_Character;
1280                         Str : out String);
1281   --  AKA
1282
1283   --  ANCHOR(`unctrl()',`Un_Control')
1284   function Un_Control (Ch  : in Attributed_Character) return String;
1285   --  AKA
1286   --  Same as function
1287   pragma Inline (Un_Control);
1288
1289   --  ANCHOR(`delay_output()',`Delay_Output')
1290   procedure Delay_Output (Msecs : in Natural);
1291   --  AKA
1292   pragma Inline (Delay_Output);
1293
1294   --  ANCHOR(`flushinp()',`Flush_Input')
1295   procedure Flush_Input;
1296   --  AKA
1297   pragma Inline (Flush_Input);
1298
1299   --  MANPAGE(`curs_termattrs.3x')
1300
1301   --  ANCHOR(`baudrate()',`Baudrate')
1302   function Baudrate return Natural;
1303   --  AKA
1304   pragma Inline (Baudrate);
1305
1306   --  ANCHOR(`erasechar()',`Erase_Character')
1307   function Erase_Character return Character;
1308   --  AKA
1309   pragma Inline (Erase_Character);
1310
1311   --  ANCHOR(`killchar()',`Kill_Character')
1312   function Kill_Character return Character;
1313   --  AKA
1314   pragma Inline (Kill_Character);
1315
1316   --  ANCHOR(`has_ic()',`Has_Insert_Character')
1317   function Has_Insert_Character return Boolean;
1318   --  AKA
1319   pragma Inline (Has_Insert_Character);
1320
1321   --  ANCHOR(`has_il()',`Has_Insert_Line')
1322   function Has_Insert_Line return Boolean;
1323   --  AKA
1324   pragma Inline (Has_Insert_Line);
1325
1326   --  ANCHOR(`termattrs()',`Supported_Attributes')
1327   function Supported_Attributes return Character_Attribute_Set;
1328   --  AKA
1329   pragma Inline (Supported_Attributes);
1330
1331   --  ANCHOR(`longname()',`Long_Name')
1332   procedure Long_Name (Name : out String);
1333   --  AKA
1334
1335   --  ANCHOR(`longname()',`Long_Name')
1336   function Long_Name return String;
1337   --  AKA
1338   --  Same as function
1339   pragma Inline (Long_Name);
1340
1341   --  ANCHOR(`termname()',`Terminal_Name')
1342   procedure Terminal_Name (Name : out String);
1343   --  AKA
1344
1345   --  ANCHOR(`termname()',`Terminal_Name')
1346   function Terminal_Name return String;
1347   --  AKA
1348   --  Same as function
1349   pragma Inline (Terminal_Name);
1350
1351   --  MANPAGE(`curs_color.3x')
1352
1353   --  COLOR_PAIR
1354   --  COLOR_PAIR(n) in C is the same as
1355   --  Attributed_Character(Ch => Nul, Color => n, Attr => Normal_Video)
1356   --  In C you often see something like c = c | COLOR_PAIR(n);
1357   --  This is equivalent to c.Color := n;
1358
1359   --  ANCHOR(`start_color()',`Start_Color')
1360   procedure Start_Color;
1361   --  AKA
1362   pragma Import (C, Start_Color, "start_color");
1363
1364   --  ANCHOR(`init_pair()',`Init_Pair')
1365   procedure Init_Pair (Pair : in Redefinable_Color_Pair;
1366                        Fore : in Color_Number;
1367                        Back : in Color_Number);
1368   --  AKA
1369   pragma Inline (Init_Pair);
1370
1371   --  ANCHOR(`pair_content()',`Pair_Content')
1372   procedure Pair_Content (Pair : in Color_Pair;
1373                           Fore : out Color_Number;
1374                           Back : out Color_Number);
1375   --  AKA
1376   pragma Inline (Pair_Content);
1377
1378   --  ANCHOR(`has_colors()',`Has_Colors')
1379   function Has_Colors return Boolean;
1380   --  AKA
1381   pragma Inline (Has_Colors);
1382
1383   --  ANCHOR(`init_color()',`Init_Color')
1384   procedure Init_Color (Color : in Color_Number;
1385                         Red   : in RGB_Value;
1386                         Green : in RGB_Value;
1387                         Blue  : in RGB_Value);
1388   --  AKA
1389   pragma Inline (Init_Color);
1390
1391   --  ANCHOR(`can_change_color()',`Can_Change_Color')
1392   function Can_Change_Color return Boolean;
1393   --  AKA
1394   pragma Inline (Can_Change_Color);
1395
1396   --  ANCHOR(`color_content()',`Color_Content')
1397   procedure Color_Content (Color : in  Color_Number;
1398                            Red   : out RGB_Value;
1399                            Green : out RGB_Value;
1400                            Blue  : out RGB_Value);
1401   --  AKA
1402   pragma Inline (Color_Content);
1403
1404   --  MANPAGE(`curs_kernel.3x')
1405   --  | Not implemented: getsyx, setsyx
1406   --
1407   type Curses_Mode is (Curses, Shell);
1408
1409   --  ANCHOR(`def_prog_mode()',`Save_Curses_Mode')
1410   procedure Save_Curses_Mode (Mode : in Curses_Mode);
1411   --  AKA
1412   --  ALIAS(`def_shell_mode()')
1413   pragma Inline (Save_Curses_Mode);
1414
1415   --  ANCHOR(`reset_prog_mode()',`Reset_Curses_Mode')
1416   procedure Reset_Curses_Mode (Mode : in Curses_Mode);
1417   --  AKA
1418   --  ALIAS(`reset_shell_mode()')
1419   pragma Inline (Reset_Curses_Mode);
1420
1421   --  ANCHOR(`savetty()',`Save_Terminal_State')
1422   procedure Save_Terminal_State;
1423   --  AKA
1424   pragma Inline (Save_Terminal_State);
1425
1426   --  ANCHOR(`resetty();',`Reset_Terminal_State')
1427   procedure Reset_Terminal_State;
1428   --  AKA
1429   pragma Inline (Reset_Terminal_State);
1430
1431   type Stdscr_Init_Proc is access
1432      function (Win     : Window;
1433                Columns : Column_Count) return Integer;
1434   pragma Convention (C, Stdscr_Init_Proc);
1435   --  N.B.: the return value is actually ignored, but it seems to be
1436   --        a good practice to return 0 if you think all went fine
1437   --        and -1 otherwise.
1438
1439   --  ANCHOR(`ripoffline()',`Rip_Off_Lines')
1440   procedure Rip_Off_Lines (Lines : in Integer;
1441                            Proc  : in Stdscr_Init_Proc);
1442   --  AKA
1443   --  N.B.: to be more precise, this uses a ncurses specific enhancement of
1444   --        ripoffline(), in which the Lines argument absolute value is the
1445   --        number of lines to be ripped of. The official ripoffline() only
1446   --        uses the sign of Lines to rip of a single line from bottom or top.
1447   pragma Inline (Rip_Off_Lines);
1448
1449   type Cursor_Visibility is (Invisible, Normal, Very_Visible);
1450
1451   --  ANCHOR(`curs_set()',`Set_Cursor_Visibility')
1452   procedure Set_Cursor_Visibility (Visibility : in out Cursor_Visibility);
1453   --  AKA
1454   pragma Inline (Set_Cursor_Visibility);
1455
1456   --  ANCHOR(`napms()',`Nap_Milli_Seconds')
1457   procedure Nap_Milli_Seconds (Ms : in Natural);
1458   --  AKA
1459   pragma Inline (Nap_Milli_Seconds);
1460
1461   --  |=====================================================================
1462   --  | Some useful helpers.
1463   --  |=====================================================================
1464   type Transform_Direction is (From_Screen, To_Screen);
1465   procedure Transform_Coordinates
1466     (W      : in Window := Standard_Window;
1467      Line   : in out Line_Position;
1468      Column : in out Column_Position;
1469      Dir    : in Transform_Direction := From_Screen);
1470   --  This procedure transforms screen coordinates into coordinates relative
1471   --  to the window and vice versa, depending on the Dir parameter.
1472   --  Screen coordinates are the position informations on the physical device.
1473   --  An Curses_Exception will be raised if Line and Column are not in the
1474   --  Window or if you pass the Null_Window as argument.
1475   --  We don't inline this procedure
1476
1477   --  MANPAGE(`default_colors.3x')
1478
1479   --  ANCHOR(`use_default_colors()',`Use_Default_Colors')
1480   procedure Use_Default_Colors;
1481   --  AKA
1482   pragma Inline (Use_Default_Colors);
1483
1484   --  ANCHOR(`assume_default_colors()',`Assume_Default_Colors')
1485   procedure Assume_Default_Colors (Fore : Color_Number := Default_Color;
1486                                    Back : Color_Number := Default_Color);
1487   --  AKA
1488   pragma Inline (Assume_Default_Colors);
1489
1490   --  MANPAGE(`curs_extend.3x')
1491
1492   --  ANCHOR(`curses_version()',`Curses_Version')
1493   function Curses_Version return String;
1494   --  AKA
1495
1496   --  ANCHOR(`use_extended_names()',`Use_Extended_Names')
1497   --  The returnvalue is the previous setting of the flag
1498   function Use_Extended_Names (Enable : Boolean) return Boolean;
1499   --  AKA
1500
1501   --  MANPAGE(`curs_trace.3x')
1502
1503   --  ANCHOR(`_nc_freeall()',`Curses_Free_All')
1504   procedure Curses_Free_All;
1505   --  AKA
1506
1507   --  MANPAGE(`curs_scr_dump.3x')
1508
1509   --  ANCHOR(`scr_dump()',`Screen_Dump_To_File')
1510   procedure Screen_Dump_To_File (Filename : in String);
1511   --  AKA
1512
1513   --  ANCHOR(`scr_restore()',`Screen_Restore_From_File')
1514   procedure Screen_Restore_From_File (Filename : in String);
1515   --  AKA
1516
1517   --  ANCHOR(`scr_init()',`Screen_Init_From_File')
1518   procedure Screen_Init_From_File (Filename : in String);
1519   --  AKA
1520
1521   --  ANCHOR(`scr_set()',`Screen_Set_File')
1522   procedure Screen_Set_File (Filename : in String);
1523   --  AKA
1524
1525   --  MANPAGE(`curs_print.3x')
1526   --  Not implemented:  mcprint
1527
1528   --  MANPAGE(`curs_printw.3x')
1529   --  Not implemented: printw,  wprintw, mvprintw, mvwprintw, vwprintw,
1530   --                   vw_printw
1531   --  Please use the Ada style Text_IO child packages for formatted
1532   --  printing. It doesn't make a lot of sense to map the printf style
1533   --  C functions to Ada.
1534
1535   --  MANPAGE(`curs_scanw.3x')
1536   --  Not implemented: scanw, wscanw, mvscanw, mvwscanw, vwscanw, vw_scanw
1537
1538   --  MANPAGE(`resizeterm.3x')
1539   --  Not Implemented: resizeterm
1540
1541   --  MANPAGE(`wresize.3x')
1542
1543   --  ANCHOR(`wresize()',`Resize')
1544   procedure Resize (Win               : Window := Standard_Window;
1545                     Number_Of_Lines   : Line_Count;
1546                     Number_Of_Columns : Column_Count);
1547   --  AKA
1548
1549private
1550   type Window is new System.Storage_Elements.Integer_Address;
1551   Null_Window : constant Window := 0;
1552
1553   --  The next constants are generated and may be different on your
1554   --  architecture.
1555   --
1556include(`Window_Offsets')dnl
1557   Curses_Bool_False : constant Curses_Bool := 0;
1558
1559end Terminal_Interface.Curses;
1560