+++ /dev/null
-package Element_Copy is
- type SmallInt is range 1 .. 4;
- type SmallStr is array (SmallInt range <>) of Character;
- type VariableSizedField (D : SmallInt := 2) is record
- S : SmallStr (1 .. D) := "Hi";
- end record;
- function F return VariableSizedField;
-end;
+++ /dev/null
-package Fat_Fields is
- pragma Elaborate_Body;
- type A is array (Positive range <>) of Boolean;
- type A_Ptr is access A;
- P : A_Ptr := null;
-end;
+++ /dev/null
-package Global_Constant is
- pragma Elaborate_Body;
- An_Error : exception;
-end;
+++ /dev/null
-package Non_LValue is
- type T (Length : Natural) is record
- A : String (1 .. Length);
- B : String (1 .. Length);
- end record;
- type T_Ptr is access all T;
- type U is record
- X : T_Ptr;
- end record;
- function A (Y : U) return String;
-end;
+++ /dev/null
-with Ada.Streams;
-package Real_Cst is
- procedure Write (Stream : access Ada.Streams.Root_Stream_Type'Class);
-end;
+++ /dev/null
-package Unc_Constructor is
- type C is null record;
- type A is array (Positive range <>) of C;
- A0 : constant A;
- procedure P (X : A);
-private
- A0 : aliased constant A := (1 .. 0 => (null record));
-end;
+++ /dev/null
-package Var_Offset is
- pragma Elaborate_Body;
- type T (L : Natural) is record
- Var_Len : String (1 .. L);
- Space : Integer;
- Small : Character;
- Bad_Field : Character;
- end record;
-end;
+++ /dev/null
-package Var_Size is
- type T (Length : Natural) is record
- A : String (1 .. Length);
- B : String (1 .. Length);
- end record;
- function A (X : T) return String;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-procedure Array_Constructor is
- A : array (Integer range <>) of Boolean := (True, False);
-begin
- null;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-procedure Array_Range_Ref is
- A : String (1 .. 3);
- B : String := A (A'RANGE)(1 .. 3);
-begin
- null;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-procedure Array_Ref is
- type A is array (Natural range <>, Natural range <>) of Boolean;
- type A_Access is access A;
- function Get (X : A_Access) return Boolean is
- begin
- return X (0, 0);
- end;
-begin
- null;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-procedure Array_Size is
- subtype S is String (1 .. 2);
- type R is record
- A : S;
- end record;
- X : R;
-begin
- null;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-with System.Machine_Code;
-procedure Asm is
-begin
- System.Machine_Code.Asm ("");
-end;
+++ /dev/null
--- RUN: %llvmgcc -S -emit-llvm %s -o - | not grep ptrtoint
-package Constant_Fold is
- Error : exception;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S -g %s
-package Debug_Var_Size is
- subtype Length_Type is Positive range 1 .. 64;
- type T (Length : Length_Type := 1) is record
- Varying_Length : String (1 .. Length);
- Fixed_Length : Boolean;
- end record;
-end;
+++ /dev/null
-load_lib llvm.exp
-
-if [ llvm_gcc_supports ada ] then {
- RunLLVMTests [lsort [glob -nocomplain $srcdir/$subdir/*.{adb,ads}]]
-}
-
+++ /dev/null
--- RUN: %llvmgcc -S -O2 %s -I%p/Support -o - | grep 105 | count 2
-package body Element_Copy is
- function F return VariableSizedField is
- X : VariableSizedField;
- begin
- return X;
- end;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-with Ada.Finalization;
-package Emit_Var is
- type Search_Type is new Ada.Finalization.Controlled with null record;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s -I%p/Support
--- RUN: %llvmgcc -S %s -I%p/Support -O2
-package body Fat_Fields is
- procedure Proc is
- begin
- if P = null then
- null;
- end if;
- end;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-package Field_Order is
- type Tagged_Type is abstract tagged null record;
- type With_Discriminant (L : Positive) is new Tagged_Type with record
- S : String (1 .. L);
- end record;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s -I%p/Support
-package body Global_Constant is
-begin
- raise An_Error;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-package Init_Size is
- type T (B : Boolean := False) is record
- case B is
- when False =>
- I : Integer;
- when True =>
- J : Long_Long_Integer; -- Bigger than I
- end case;
- end record;
- A_T : constant T := (False, 0);
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-with System;
-procedure Negative_Field_Offset (N : Integer) is
- type String_Pointer is access String;
- -- Force use of a thin pointer.
- for String_Pointer'Size use System.Word_Size;
- P : String_Pointer;
-
- procedure Q (P : String_Pointer) is
- begin
- P (1) := 'Z';
- end;
-begin
- P := new String (1 .. N);
- Q (P);
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-package Non_Bitfield is
- type SP is access String;
- type E is (A, B, C);
- type T (D : E) is record
- case D is
- when A => X : Boolean;
- when B => Y : SP;
- when C => Z : String (1 .. 2);
- end case;
- end record;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s -I%p/Support
-package body Non_LValue is
- function A (Y : U) return String is
- begin
- return Y.X.B;
- end;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-procedure Placeholder is
- subtype Bounded is Integer range 1 .. 5;
- type Vector is array (Bounded range <>) of Integer;
- type Interval (Length : Bounded := 1) is record
- Points : Vector (1 .. Length);
- end record;
- An_Interval : Interval := (Length => 1, Points => (1 => 1));
- generic The_Interval : Interval; package R is end;
- package body R is end;
- package S is new R (An_Interval);
-begin null; end;
+++ /dev/null
--- RUN: %llvmgcc -S -O2 -gnatn %s -I%p/Support
-package body Real_Cst is
- Cst : constant Float := 0.0;
- procedure Write (Stream : access Ada.Streams.Root_Stream_Type'Class) is
- begin
- Float'Write (Stream, Cst);
- end;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-function Switch (N : Integer) return Integer is
-begin
- case N is
- when Integer'First .. -1 =>
- return -1;
- when 0 =>
- return 0;
- when others =>
- return 1;
- end case;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s -I%p/Support
-package body Unc_Constructor is
- procedure P (X : A) is
- begin
- if X = A0 then
- null;
- end if;
- end;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s -I%p/Support
-package body Var_Offset is
- function F (X : T) return Character is
- begin
- return X.Bad_Field;
- end;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s -I%p/Support
-package body Var_Size is
- function A (X : T) return String is
- begin
- return X.A;
- end;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-procedure VCE is
- S : String (1 .. 2);
- B : Character := 'B';
-begin
- S := 'A' & B;
-end;
+++ /dev/null
--- RUN: %llvmgcc -S %s
-procedure VCE_LV is
- type P is access String ;
- type T is new P (5 .. 7);
- subtype U is String (5 .. 7);
- X : T := new U'(others => 'A');
-begin
- null;
-end;
+++ /dev/null
-! RUN: %llvmgcc -S %s -march=k8
-! XTARGET: x86
-! Note: this file intentionally left blank, the problem itself is in
-! frontend initialization routines and march flag!
+++ /dev/null
-! RUN: %llvmgcc -S %s
-! PR2437
-program main
- implicit none
- call build (77)
-contains
- subroutine build (order)
- integer :: order, i, j
-
-
- call test (1, order, 3, (/ (i, i = 1, order, 3) /))
- call test (order, 1, -3, (/ (i, i = order, 1, -3) /))
-
- do j = -10, 10
- call test (order + j, order, 5, (/ (i, i = order + j, order, 5) /))
- call test (order + j, order, -5, (/ (i, i = order + j, order, -5) /))
- end do
-
- end subroutine build
-
- subroutine test (from, to, step, values)
- integer, dimension (:) :: values
- integer :: from, to, step, last, i
-
- last = 0
- do i = from, to, step
- last = last + 1
- if (values (last) .ne. i) call abort
- end do
- if (size (values, dim = 1) .ne. last) call abort
- end subroutine test
-end program main
+++ /dev/null
-! RUN: %llvmgcc -S %s
-! PR2443
-
-! Program to test the power (**) operator
-program testpow
- implicit none
- real(kind=4) r, s, two
- real(kind=8) :: q
- complex(kind=4) :: c, z
- real, parameter :: del = 0.0001
- integer i, j
-
- two = 2.0
-
- c = (2.0, 3.0)
- c = c ** two
- if (abs(c - (-5.0, 12.0)) .gt. del) call abort
-end program
+++ /dev/null
-load_lib llvm.exp
-
-if [ llvm_gcc_supports fortran ] then {
- RunLLVMTests [lsort [glob -nocomplain $srcdir/$subdir/*.{f,f90}]]
-}
-