1----------------------------------------------------------------------
2--  Rules.Unsafe_Paired_Calls - Package body                        --
3--                                                                  --
4--  This module is (c) Adalog 2004-2016.                            --
5--  The Ada Controller is  free software; you can  redistribute  it --
6--  and/or modify it under terms of the GNU General Public  License --
7--  as published by the Free Software Foundation; either version 2, --
8--  or (at your option) any later version. This unit is distributed --
9--  in the hope  that it will be useful,  but WITHOUT ANY WARRANTY; --
10--  without even the implied warranty of MERCHANTABILITY or FITNESS --
11--  FOR A  PARTICULAR PURPOSE.  See the GNU  General Public License --
12--  for more details.   You should have received a  copy of the GNU --
13--  General Public License distributed  with this program; see file --
14--  COPYING.   If not, write  to the  Free Software  Foundation, 59 --
15--  Temple Place - Suite 330, Boston, MA 02111-1307, USA.           --
16--                                                                  --
17--  As  a special  exception, if  other files  instantiate generics --
18--  from the units  of this program, or if you  link this unit with --
19--  other files  to produce  an executable, this  unit does  not by --
20--  itself cause the resulting executable  to be covered by the GNU --
21--  General  Public  License.   This  exception  does  not  however --
22--  invalidate any  other reasons why the executable  file might be --
23--  covered by the GNU Public License.                              --
24--                                                                  --
25--  This  software is  distributed  in  the hope  that  it will  be --
26--  useful,  but WITHOUT  ANY  WARRANTY; without  even the  implied --
27--  warranty  of  MERCHANTABILITY   or  FITNESS  FOR  A  PARTICULAR --
28--  PURPOSE.                                                        --
29----------------------------------------------------------------------
30
31-- Ada
32with
33  Ada.Characters.Handling,
34  Ada.Exceptions,
35  Ada.Strings.Wide_Fixed;
36
37-- ASIS
38with
39  Asis.Declarations,
40  Asis.Elements,
41  Asis.Expressions,
42  Asis.Statements;
43
44-- Adalog
45with
46  Rules.Unsafe_Paired_Calls.Services,
47  Scope_Manager,
48  Thick_Queries,
49  Utilities;
50
51package body Rules.Unsafe_Paired_Calls is
52   use Framework, Framework.Control_Manager;
53
54   -- Algorithm:
55   --
56   -- Analysis starts from (any) procedure call.
57   -- First identify if the call is an opening call, a closing call, or anything else (exit immediately if the latter).
58   -- For opening calls, check:
59   --    - That the call is the first statement in a sequence
60   --    - That there is no call for the same lock in an enclosing scope (opening calls are kept in a scoped store)
61   --    - That the current sequence of statements is terminated by a matching closing call
62   --    - That there is an exception parts with a "when others" handler
63   --    - That every handler includes exactly one closing call
64   -- For closing calls check:
65   --    - That the call is the last statemement in a sequence, except for possible return, exit and null
66   --    - That the current sequence of statements starts with a matching opening call
67   --
68   -- Note that the correspondance must be checked for both opening and closing calls, for the case where an opening
69   -- call has no closing call, or a closing call has no opening call
70
71   Rules_Used : Control_Index := 0;
72   Save_Used  : Control_Index;
73
74   type SP_Role is (Opening, Closing);
75   type SP_Lock_Parameter_Kind is (None, Entity_Spec, In_Def, In_Out_Def);
76   type Lock_Parameter (Kind: SP_Lock_Parameter_Kind := None) is
77      record
78         case Kind is
79            when None =>
80               null;
81            when Entity_Spec =>
82               Position : Location;
83               Entity   : Entity_Specification;
84            when In_Def | In_Out_Def =>
85               Formal : Asis.Defining_Name;
86         end case;
87      end record;
88   type SP_Context is new Basic_Rule_Context with
89      record
90         Role         : SP_Role;
91         Rule_Numbers : Control_Index_Set;
92         Lock         : Lock_Parameter;
93      end record;
94
95   Checked_Subprograms  : Context_Store;
96   package Active_Procs is new Scope_Manager.Scoped_Store (Asis.Element,
97                                                           Equivalent_Keys => Asis.Elements.Is_Equal);
98
99   ----------
100   -- Help --
101   ----------
102
103   procedure Help is
104      use Framework.Variables, Utilities;
105   begin
106      User_Message ("Rule: " & Rule_Id);
107      User_Message ("Controls calls like P/V operations that are not safely paired");
108      User_Message;
109      User_Message ("Parameter(1): First subprogram");
110      User_Message ("Parameter(2): Second subprogram");
111      User_Message ("Parameter(3): (optional) type of lock parameter");
112      User_Message ("Variables:");
113      Help_On_Variable (Rule_Id & ".Conditionals_Allowed");
114   end Help;
115
116   -----------------
117   -- Add_Control --
118   -----------------
119
120   procedure Add_Control (Ctl_Label : in Wide_String; Ctl_Kind : in Control_Kinds) is
121      use Framework.Language, Utilities, Ada.Strings.Wide_Fixed;
122      First_SP  : Entity_Specification;
123      Second_SP : Entity_Specification;
124      Lock_Type : Entity_Specification;
125      Lock_Pos  : Location;
126
127      procedure Associate_With_Set (Specification : in Entity_Specification;
128                                    Role          : in SP_Role;
129                                    LP            : in Lock_Parameter)
130      is
131         Existing  : Root_Context'Class := Association (Checked_Subprograms, Specification);
132         Rules_Set : Control_Index_Set := (others => False);
133      begin
134         if Existing = No_Matching_Context then
135            Rules_Set (Rules_Used) := True;
136            Associate (Checked_Subprograms,
137                       Specification,
138                       SP_Context'(Basic.New_Context (Ctl_Kind, Ctl_Label) with Role, Rules_Set, LP));
139         else
140            SP_Context (Existing).Rule_Numbers (Rules_Used) := True;
141            Update (Checked_Subprograms, Existing);
142         end if;
143      end Associate_With_Set;
144
145   begin  -- Add_Control
146      if Rules_Used = Control_Index_Set'Last then
147         Parameter_Error (Rule_Id,
148                          "this rule can be given at most"
149                          & Control_Index'Wide_Image(Control_Index_Set'Last)
150                          & " times");
151      end if;
152      Rules_Used := Rules_Used + 1;
153
154      if not Parameter_Exists then
155         Parameter_Error (Rule_Id, "first subprogram missing");
156      end if;
157      First_SP := Get_Entity_Parameter;
158
159      if not Parameter_Exists then
160         Parameter_Error (Rule_Id, "Second subprogram missing");
161      end if;
162      Second_SP := Get_Entity_Parameter;
163
164      if Parameter_Exists then
165         Lock_Pos  := Source_Location;
166         Lock_Type := Get_Entity_Parameter;
167         if Parameter_Exists then
168            Parameter_Error (Rule_Id, "spurious parameter after type name");
169         end if;
170         if Index (To_Upper (Image (Lock_Type)), "'CLASS") /= 0 then
171            Parameter_Error (Rule_Id, "class wide type not allowed for lock parameter");
172         end if;
173
174         Associate_With_Set (First_SP,  Opening, (Entity_Spec, Lock_Pos, Lock_Type));
175         Associate_With_Set (Second_SP, Closing, (Entity_Spec, Lock_Pos, Lock_Type));
176      else
177         Associate_With_Set (First_SP,  Opening, (Kind => None));
178         Associate_With_Set (Second_SP, Closing, (Kind => None));
179      end if;
180   end Add_Control;
181
182   -------------
183   -- Command --
184   -------------
185
186   procedure Command (Action : Framework.Rules_Manager.Rule_Action) is
187      use Framework.Rules_Manager;
188   begin
189      case Action is
190         when Clear =>
191            Rules_Used  := 0;
192            Clear (Checked_Subprograms);
193         when Suspend =>
194            Save_Used  := Rules_Used;
195            Rules_Used := 0;
196         when Resume =>
197            Rules_Used := Save_Used;
198      end case;
199   end Command;
200
201   -------------
202   -- Prepare --
203   -------------
204
205   procedure Prepare is
206   begin
207      if Rules_Used = 0 then
208         return;
209      end if;
210
211      Balance (Checked_Subprograms);
212      Active_Procs.Activate;
213   end Prepare;
214
215   ------------------
216   -- Call_Context --
217   ------------------
218
219   function Call_Context (Call : Asis.Statement) return Root_Context'Class is
220      use Asis.Elements;
221      use Thick_Queries;
222   begin
223      if Is_Nil (Call) then
224         return No_Matching_Context;
225      end if;
226      return Matching_Context (Checked_Subprograms, Ultimate_Name (Called_Simple_Name (Call)));
227   end Call_Context;
228
229   ------------------
230   -- Process_Call --
231   ------------------
232
233   procedure Process_Call (Call : in Asis.Element) is
234      use Asis, Asis.Elements, Asis.Statements;
235      use Framework.Reports, Thick_Queries, Utilities, Unsafe_Paired_Calls.Services;
236
237      function Call_Image (The_Call : Asis.Statement) return Wide_String is
238         -- Precondition: the matching context exists
239         Called_Context : constant SP_Context := SP_Context (Call_Context (The_Call));
240         Sp_Image       : constant Wide_String := Full_Name_Image (Called_Name (The_Call));
241
242         function Selected_Variable_Image (Var : Asis.Expression) return Wide_String is
243            use Asis.Expressions;
244            Sel : Asis.Expression;
245         begin
246            if Expression_Kind (Var) /= A_Selected_Component then
247               return Full_Name_Image (Var);
248            end if;
249            Sel := Selector (Var);
250            if Declaration_Kind (Corresponding_Name_Declaration (Sel)) = A_Component_Declaration then
251               return Selected_Variable_Image (Prefix (Var)) & '.' & Name_Image (Sel);
252            else
253               return Full_Name_Image (Var);
254            end if;
255         end Selected_Variable_Image;
256      begin  -- Call_Image
257         case Called_Context.Lock.Kind is
258            when None =>
259               return Sp_Image;
260            when In_Def =>
261               -- The lock value can be a static expression of a discrete type, or
262               -- a constant of any type, or anything else (since it is an error).
263               declare
264                  Val_Image : constant Wide_String
265                    := Static_Expression_Value_Image (Actual_Expression (The_Call, Called_Context.Lock.Formal));
266               begin
267                  if Val_Image = "" then
268                     return Sp_Image & " (different or non static lock value)";
269                  else
270                     return Sp_Image & " with lock value " & Val_Image ;
271                  end if;
272               end;
273            when In_Out_Def =>
274               return Sp_Image
275                 & " with lock variable "
276                 & Selected_Variable_Image (Actual_Expression (The_Call, Called_Context.Lock.Formal));
277            when Entity_Spec =>
278               Failure ("lock field not initialized");
279         end case;
280      end Call_Image;
281
282      procedure Update_Lock_Parameter (Lock_Call : in Asis.Element; Lock_Context : in out SP_Context) is
283      -- Initially, a SP_Context has Entity_Specification for its Lock field.
284      -- We must delay analyzing the lock until we have a way of getting to the corresponding
285      -- element, i.e. the first time we have a call to the procedure.
286      -- This procedure update the Lock field of Lock_Context according to the provided Lock_Call
287
288         use Framework.Language;
289         use Asis.Declarations, Asis.Expressions;
290      begin
291         if Lock_Context.Lock.Kind /= Entity_Spec then
292            -- Already transformed (or None)
293            return;
294         end if;
295
296         declare
297            Profile : constant Asis.Parameter_Specification_List := Called_Profile (Lock_Call);
298            Mark    : Asis.Expression;
299         begin
300            -- Note that we iterate through all parameters, and that we transform Lock_Context
301            -- as soon as we find a parameter of the appropriate type.
302            -- This is intended to diagnose the case where more than one parameter is of the
303            -- provided type.
304            for I in Profile'Range loop
305               Mark := Simple_Name (Declaration_Subtype_Mark (Profile (I)));
306               if Matches (Lock_Context.Lock.Entity, Mark) then
307                  if Lock_Context.Lock.Kind /= Entity_Spec or Names (Profile (I))'Length /= 1 then
308                     Parameter_Error (Rule_Id,
309                                      "more than one parameter of the provided type",
310                                      Lock_Context.Lock.Position);
311                  else
312                     case Mode_Kind (Profile (I)) is
313                        when An_In_Mode | A_Default_In_Mode =>
314                           -- Only discrete and access types allowed
315                           case Type_Kind (Type_Declaration_View (Corresponding_Name_Declaration (Mark))) is
316                              when An_Enumeration_Type_Definition
317                                | A_Signed_Integer_Type_Definition
318                                | A_Modular_Type_Definition
319                                | An_Access_Type_Definition
320                                =>
321                                 null;
322                              when others =>
323                                 Parameter_Error (Rule_Id,
324                                                  "only discrete and access types allowed for lock parameter",
325                                                  Lock_Context.Lock.Position);
326                           end case;
327
328                           Lock_Context.Lock := (In_Def,
329                                                 Formal => Names (Profile (I))(1));
330                        when An_In_Out_Mode =>
331                           Lock_Context.Lock := (In_Out_Def,
332                                                 Formal => Names (Profile (I))(1));
333                        when An_Out_Mode =>
334                           Parameter_Error (Rule_Id,
335                                            "parameter of the provided type is of mode ""out"" in "
336                                            & Full_Name_Image (Called_Name (Lock_Call)),
337                                            Lock_Context.Lock.Position);
338                        when Not_A_Mode =>
339                           Failure ("not a mode for parameter");
340                     end case;
341                  end if;
342               end if;
343            end loop;
344            if Lock_Context.Lock.Kind = Entity_Spec then
345               Parameter_Error (Rule_Id,
346                                "No parameter of the provided type in " & Full_Name_Image (Called_Name (Lock_Call)),
347                                Lock_Context.Lock.Position);
348            end if;
349         end;
350         Update (Checked_Subprograms, Lock_Context);
351      end Update_Lock_Parameter;
352
353      function Has_Same_Lock_Param (Called_Context : SP_Context;
354                                    Other_Call     : Asis.Statement;
355                                    Other_Context  : SP_Context) return Boolean
356      is
357      -- Returns True if Lock.Kind is none, or if the Lock parameters are the same
358      begin
359         if Other_Context.Lock.Kind /= Called_Context.Lock.Kind then
360            return False;
361         end if;
362
363         case Called_Context.Lock.Kind is
364            when None =>
365               return True;
366            when Entity_Spec =>
367               Failure ("Lock not updated");
368            when In_Def =>
369               return Same_Value (Actual_Expression (Call,       Called_Context.Lock.Formal),
370                                  Actual_Expression (Other_Call, Other_Context.Lock.Formal));
371            when In_Out_Def =>
372               declare
373                  Lock_Object       : constant Asis.Expression := Actual_Expression (Call, Called_Context.Lock.Formal);
374                  Other_Lock_Object : constant Asis.Expression := Actual_Expression (Other_Call,
375                                                                                     Other_Context.Lock.Formal);
376               begin
377                  return Variables_Proximity (Lock_Object, Other_Lock_Object) = Same_Variable;
378               end;
379         end case;
380      end Has_Same_Lock_Param;
381
382      function Is_Same_Opening_Locking (Called_Context : SP_Context;
383                                        Other_Call     : Asis.Statement) return Boolean
384      is
385      -- Returns True if Call and Other_Call refer to the same subprograms, with matching lock parameters
386         use Asis.Expressions;
387
388         Other_Context : Root_Context'Class := Call_Context (Other_Call);
389      begin
390         if Other_Context = No_Matching_Context then
391            return False;
392         end if;
393
394         if not Is_Equal (Corresponding_Name_Definition (Ultimate_Name (Called_Name (Call))),
395                          Corresponding_Name_Definition (Ultimate_Name (Called_Name (Other_Call))))
396         then
397            return False;
398         end if;
399
400         Update_Lock_Parameter (Other_Call, SP_Context (Other_Context));
401
402         return Has_Same_Lock_Param (Called_Context, Other_Call, SP_Context (Other_Context));
403      end Is_Same_Opening_Locking;
404
405      function Is_Matching_Locking (Called_Context : SP_Context;
406                                    Other_Call     : Asis.Statement) return Boolean
407      is
408      -- Returns True if Call and Other_Call are matching opening/closing calls (in any order).
409         Other_Context : Root_Context'Class := Call_Context (Other_Call);
410      begin
411         if Other_Context = No_Matching_Context then
412            return False;
413         end if;
414
415         -- One opening call and one closing call
416         if SP_Context (Other_Context).Role = Called_Context.Role then
417            return False;
418         end if;
419
420         Update_Lock_Parameter (Other_Call, SP_Context (Other_Context));
421
422         -- Must belong to the same control
423         if (SP_Context (Other_Context).Rule_Numbers and Called_Context.Rule_Numbers) = Empty_Control_Index_Set then
424            return False;
425         end if;
426
427         -- Must matching lock parameter
428         return Has_Same_Lock_Param (Called_Context, Other_Call, SP_Context (Other_Context));
429      end Is_Matching_Locking;
430
431      ------------------------
432      -- Check_Opening_Call --
433      ------------------------
434
435      procedure Check_Opening_Call (Called_Context : SP_Context; Called_Sig : Nesting_Signature) is
436         Enclosing  : Asis.Element;
437      begin
438         Enclosing := Enclosing_Element (Called_Sig (Called_Sig'First));
439
440         -- Check that the call (or top if) is in an handled sequence of statements
441         if not Is_Handled_Sequence_Container (Enclosing) then
442            Report (Rule_Id,
443                    Called_Context,
444                    Get_Location (Call),
445                    "opening call to " & Full_Name_Image (Called_Name (Call))
446                    & " is not directly in a handled sequence of statements");
447            return;  -- Cannot proceed, since we don't know where we are (to get stats and handlers)
448         end if;
449
450         declare
451            Stats      : constant Statement_List         := Thick_Queries.Statements         (Enclosing);
452            Handlers   : constant Exception_Handler_List := Thick_Queries.Exception_Handlers (Enclosing);
453            Other_Call : Asis.Statement;
454         begin
455            -- No call to same SP in enclosing scopes
456            -- Note that this check is done (and this SP later added) when we encounter
457            -- a *call*, i.e. after the declarative part of the enclosing unit.
458            -- Therefore, this will *not* prevent having P/V pairs in enclosed subprograms,
459            -- even if the outer one also has P/V pairs, as it should be.
460            Active_Procs.Reset (Scope_Manager.All_Scopes);
461            while Active_Procs.Data_Available loop
462               if Is_Same_Opening_Locking (Called_Context, Active_Procs.Current_Data) then
463                  Report (Rule_Id,
464                          Called_Context,
465                          Get_Location (Call),
466                          "nested call to " & Call_Image (Call));
467               end if;
468               Active_Procs.Next;
469            end loop;
470
471            -- OK, add ourself
472            Active_Procs.Push (Call);
473
474            -- This call (or top if) must be the first statement
475            Other_Call := Matching_Call (Effective_Last_Statement (Stats), Called_Sig);
476            if not Is_Equal (Called_Sig (Called_Sig'First), Stats (Stats'First)) then
477               Report (Rule_Id,
478                       Called_Context,
479                       Get_Location (Call),
480                       "opening call to " & Full_Name_Image (Called_Name (Call)) & " is not the first statement");
481
482            -- Last statement must be corresponding call
483            elsif not Is_Matching_Locking (Called_Context, Other_Call) then
484               Report (Rule_Id,
485                       Called_Context,
486                       Get_Next_Word_Location (Effective_Last_Statement (Stats), Starting => From_Tail),
487                       "sequence must end with closing call matching " & Call_Image (Call));
488            end if;
489
490            -- Construct must have exception handlers
491            if Is_Nil (Handlers) then
492               Report (Rule_Id,
493                       Called_Context,
494                       Get_Next_Word_Location (Stats, "END"),
495                       "construct must have exception handlers");
496               return;
497            end if;
498
499            -- Here, we have at least one exception handler
500            -- Construct must have a "when others" exception handler
501            if Definition_Kind (Exception_Choices (Handlers (Handlers'Last)) (1)) /= An_Others_Choice then
502               Report (Rule_Id,
503                       Called_Context,
504                       Get_Previous_Word_Location (Handlers, "EXCEPTION" ),
505                       "construct must have a ""when others"" exception handler");
506            end if;
507
508            -- Every handler must include directly one and only one call to an SP matching the opening call
509            for I in Handlers'Range loop
510               declare
511                  Handler_Stats : constant Asis.Statement_List := Handler_Statements (Handlers (I));
512                  Call_Count    : Asis.ASIS_Natural := 0;
513               begin
514                  for J in Handler_Stats'Range loop
515                     if Is_Matching_Locking (Called_Context, Matching_Call (Handler_Stats (J), Called_Sig)) then
516                        Call_Count := Call_Count + 1;
517                     end if;
518                  end loop;
519                  case Call_Count is
520                     when 0 =>
521                        Report (Rule_Id,
522                                Called_Context,
523                                Get_Location (Handlers (I)),
524                                "handler must have a closing call matching " & Call_Image (Call));
525                     when 1 => --OK
526                        null;
527                     when others =>
528                        Report (Rule_Id,
529                                Called_Context,
530                                Get_Location (Handlers (I)),
531                                "handler must have only one closing call matching " & Call_Image (Call));
532                  end case;
533               end;
534            end loop;
535         end;
536      end Check_Opening_Call;
537
538      procedure Check_Closing_Call (Called_Context : SP_Context; Called_Sig : Nesting_Signature) is
539         Enclosing  : Asis.Element;
540      begin
541         Enclosing := Enclosing_Element (Called_Sig (Called_Sig'First));
542
543         declare
544            Stats      : constant Statement_List := Thick_Queries.Statements (Enclosing);
545            Other_Call : Asis.Statement;
546         begin
547
548            -- This call (or top if) must be the last statement, not counting final null, return and exit statements
549            -- except in exception handlers
550            if Element_Kind (Enclosing) /= An_Exception_Handler
551              and then not Is_Equal (Called_Sig (Called_Sig'First), Effective_Last_Statement (Stats))
552            then
553               Report (Rule_Id,
554                       Called_Context,
555                       Get_Location (Call),
556                       "closing call to " & Full_Name_Image (Called_Name (Call)) & " is not the last statement");
557               return;
558            end if;
559
560            -- First statement must be matching call according to signature
561            if Element_Kind (Enclosing) = An_Exception_Handler then
562               declare
563                  Good_Stats : constant Statement_List := Thick_Queries.Statements (Enclosing_Element (Enclosing));
564               begin
565                  Other_Call := Matching_Call (Good_Stats (Good_Stats'First), Called_Sig);
566               end;
567            else
568               Other_Call := Matching_Call (Stats (Stats'First), Called_Sig);
569            end if;
570            if Is_Nil (Other_Call) or else Call_Context (Other_Call) = No_Matching_Context then
571               Report (Rule_Id,
572                       Called_Context,
573                       Get_Location (Call),
574                       "closing call to " & Call_Image (Call) & " has no matching opening call at start of sequence");
575               return;
576            end if;
577
578            if Is_Dispatching_Call (Other_Call) then
579               Uncheckable (Rule_Id, False_Negative, Get_Location (Other_Call), "Dispatching call");
580               return;
581            end if;
582
583            if not Is_Matching_Locking (Called_Context, Other_Call) then
584               Report (Rule_Id,
585                       Called_Context,
586                       Get_Location (Call),
587                       "call does not match opening call " & Call_Image (Other_Call));
588            end if;
589         end;
590      end Check_Closing_Call;
591
592      use Ada.Characters.Handling, Ada.Exceptions;
593   begin   -- Process_Call
594      if Rules_Used = 0 then
595         return;
596      end if;
597      Rules_Manager.Enter (Rule_Id);
598
599      if Is_Dispatching_Call (Call) then
600         Uncheckable (Rule_Id, False_Negative, Get_Location (Call), "Dispatching call");
601         return;
602      end if;
603
604      declare
605         Called_Context : Root_Context'Class := Call_Context (Call);
606      begin
607         if Called_Context = No_Matching_Context then
608            return;
609         end if;
610         Update_Lock_Parameter (Call, SP_Context (Called_Context));
611
612         case SP_Context (Called_Context).Role is
613            when Opening =>
614               begin
615                  Check_Opening_Call (SP_Context (Called_Context), Signature (Call));
616               exception
617                  when Occur: Invalid_Nesting =>
618                     Report (Rule_Id,
619                             Called_Context,
620                             Get_Location (Call),
621                             "Invalid placement of opening call to " & Full_Name_Image (Called_Name (Call))
622                             & ": " & To_Wide_String (Exception_Message (Occur)));
623               end;
624            when Closing =>
625               begin
626                  Check_Closing_Call (SP_Context (Called_Context), Signature (Call));
627               exception
628                  when Occur: Invalid_Nesting =>
629                     Report (Rule_Id,
630                             Called_Context,
631                             Get_Location (Call),
632                             "Invalid placement of closing call to " & Full_Name_Image (Called_Name (Call))
633                             & ": " & To_Wide_String (Exception_Message (Occur)));
634               end;
635         end case;
636      end;
637   end Process_Call;
638
639begin  -- Rules.Unsafe_Paired_Calls
640   Framework.Rules_Manager.Register (Rule_Id,
641                                     Rules_Manager.Semantic,
642                                     Help_CB        => Help'Access,
643                                     Add_Control_CB => Add_Control'Access,
644                                     Command_CB     => Command'Access,
645                                     Prepare_CB     => Prepare'Access);
646
647   Framework.Variables.Register (Conditionals_Allowed'Access, Rule_Id & ".CONDITIONALS_ALLOWED");
648end Rules.Unsafe_Paired_Calls;
649