xref: /llvm-project/flang/test/Semantics/call11.f90 (revision 34a4eefcbd8d394616cdb16dcadc70b934a577ce)
16c1ac141SIvan Zhechev! RUN: %python %S/test_errors.py %s %flang_fc1
264ab3302SCarolineConcatto! Test 15.7 C1591 & others: contexts requiring pure subprograms
364ab3302SCarolineConcatto
464ab3302SCarolineConcattomodule m
564ab3302SCarolineConcatto
664ab3302SCarolineConcatto  type :: t
764ab3302SCarolineConcatto   contains
864ab3302SCarolineConcatto    procedure, nopass :: tbp_pure => pure
964ab3302SCarolineConcatto    procedure, nopass :: tbp_impure => impure
1064ab3302SCarolineConcatto  end type
1164ab3302SCarolineConcatto  type, extends(t) :: t2
1264ab3302SCarolineConcatto   contains
1364ab3302SCarolineConcatto    !ERROR: An overridden pure type-bound procedure binding must also be pure
1464ab3302SCarolineConcatto    procedure, nopass :: tbp_pure => impure ! 7.5.7.3
1564ab3302SCarolineConcatto  end type
1664ab3302SCarolineConcatto
1764ab3302SCarolineConcatto contains
1864ab3302SCarolineConcatto
1964ab3302SCarolineConcatto  pure integer function pure(n)
2064ab3302SCarolineConcatto    integer, value :: n
2164ab3302SCarolineConcatto    pure = n
2264ab3302SCarolineConcatto  end function
2364ab3302SCarolineConcatto  impure integer function impure(n)
2464ab3302SCarolineConcatto    integer, value :: n
2564ab3302SCarolineConcatto    impure = n
2664ab3302SCarolineConcatto  end function
2764ab3302SCarolineConcatto
2864ab3302SCarolineConcatto  subroutine test
2964ab3302SCarolineConcatto    real :: a(pure(1)) ! ok
3064ab3302SCarolineConcatto    !ERROR: Invalid specification expression: reference to impure function 'impure'
3164ab3302SCarolineConcatto    real :: b(impure(1)) ! 10.1.11(4)
3264ab3302SCarolineConcatto    forall (j=1:1)
3364ab3302SCarolineConcatto      !ERROR: Impure procedure 'impure' may not be referenced in a FORALL
3464ab3302SCarolineConcatto      a(j) = impure(j) ! C1037
3564ab3302SCarolineConcatto    end forall
3664ab3302SCarolineConcatto    forall (j=1:1)
3764ab3302SCarolineConcatto      !ERROR: Impure procedure 'impure' may not be referenced in a FORALL
3864ab3302SCarolineConcatto      a(j) = pure(impure(j)) ! C1037
3964ab3302SCarolineConcatto    end forall
4064ab3302SCarolineConcatto    !ERROR: DO CONCURRENT mask expression may not reference impure procedure 'impure'
4164ab3302SCarolineConcatto    do concurrent (j=1:1, impure(j) /= 0) ! C1121
42486be17dSPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in DO CONCURRENT
4364ab3302SCarolineConcatto      a(j) = impure(j) ! C1139
4464ab3302SCarolineConcatto    end do
45*34a4eefcSPeter Klausler    !WARNING: Impure procedure 'impure' should not be referenced in a DO CONCURRENT header
469390eb92SPeter Klausler    do concurrent (k=impure(1):1); end do
47*34a4eefcSPeter Klausler    !WARNING: Impure procedure 'impure' should not be referenced in a DO CONCURRENT header
489390eb92SPeter Klausler    do concurrent (k=1:impure(1)); end do
49*34a4eefcSPeter Klausler    !WARNING: Impure procedure 'impure' should not be referenced in a DO CONCURRENT header
509390eb92SPeter Klausler    do concurrent (k=1:1:impure(1)); end do
51*34a4eefcSPeter Klausler    !WARNING: Impure procedure 'impure' should not be referenced in a FORALL header
529390eb92SPeter Klausler    forall (k=impure(1):1); end forall
53*34a4eefcSPeter Klausler    !WARNING: Impure procedure 'impure' should not be referenced in a FORALL header
549390eb92SPeter Klausler    forall (k=1:impure(1)); end forall
55*34a4eefcSPeter Klausler    !WARNING: Impure procedure 'impure' should not be referenced in a FORALL header
569390eb92SPeter Klausler    forall (k=1:1:impure(1)); end forall
57*34a4eefcSPeter Klausler    do concurrent (j=1:1)
58*34a4eefcSPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a DO CONCURRENT
59*34a4eefcSPeter Klausler      do concurrent (k=impure(1):1); end do
60*34a4eefcSPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a DO CONCURRENT
61*34a4eefcSPeter Klausler      do concurrent (k=1:impure(1)); end do
62*34a4eefcSPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a DO CONCURRENT
63*34a4eefcSPeter Klausler      do concurrent (k=1:1:impure(1)); end do
64*34a4eefcSPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a DO CONCURRENT
65*34a4eefcSPeter Klausler      forall (k=impure(1):1); end forall
66*34a4eefcSPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a DO CONCURRENT
67*34a4eefcSPeter Klausler      forall (k=1:impure(1)); end forall
68*34a4eefcSPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a DO CONCURRENT
69*34a4eefcSPeter Klausler      forall (k=1:1:impure(1)); end forall
70*34a4eefcSPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a DO CONCURRENT
719390eb92SPeter Klausler      forall (k=impure(1):1) a(k) = 0.
72*34a4eefcSPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a DO CONCURRENT
739390eb92SPeter Klausler      forall (k=1:impure(1)) a(k) = 0.
74*34a4eefcSPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a DO CONCURRENT
759390eb92SPeter Klausler      forall (k=1:1:impure(1)) a(k) = 0.
769390eb92SPeter Klausler    end do
779390eb92SPeter Klausler    forall (j=1:1)
789390eb92SPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a FORALL
799390eb92SPeter Klausler      forall (k=impure(1):1); end forall
809390eb92SPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a FORALL
819390eb92SPeter Klausler      forall (k=1:impure(1)); end forall
829390eb92SPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a FORALL
839390eb92SPeter Klausler      forall (k=1:1:impure(1)); end forall
849390eb92SPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a FORALL
859390eb92SPeter Klausler      forall (k=impure(1):1) a(j*k) = 0.
869390eb92SPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a FORALL
879390eb92SPeter Klausler      forall (k=1:impure(1)) a(j*k) = 0.
889390eb92SPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in a FORALL
899390eb92SPeter Klausler      forall (k=1:1:impure(1)) a(j*k) = 0.
909390eb92SPeter Klausler    end forall
9164ab3302SCarolineConcatto  end subroutine
9264ab3302SCarolineConcatto
9364ab3302SCarolineConcatto  subroutine test2
9464ab3302SCarolineConcatto    type(t) :: x
9564ab3302SCarolineConcatto    real :: a(x%tbp_pure(1)) ! ok
9664ab3302SCarolineConcatto    !ERROR: Invalid specification expression: reference to impure function 'impure'
9764ab3302SCarolineConcatto    real :: b(x%tbp_impure(1))
9864ab3302SCarolineConcatto    forall (j=1:1)
9964ab3302SCarolineConcatto      a(j) = x%tbp_pure(j) ! ok
10064ab3302SCarolineConcatto    end forall
10164ab3302SCarolineConcatto    forall (j=1:1)
10264ab3302SCarolineConcatto      !ERROR: Impure procedure 'impure' may not be referenced in a FORALL
10364ab3302SCarolineConcatto      a(j) = x%tbp_impure(j) ! C1037
10464ab3302SCarolineConcatto    end forall
10564ab3302SCarolineConcatto    do concurrent (j=1:1, x%tbp_pure(j) /= 0) ! ok
10664ab3302SCarolineConcatto      a(j) = x%tbp_pure(j) ! ok
10764ab3302SCarolineConcatto    end do
10864ab3302SCarolineConcatto    !ERROR: DO CONCURRENT mask expression may not reference impure procedure 'impure'
10964ab3302SCarolineConcatto    do concurrent (j=1:1, x%tbp_impure(j) /= 0) ! C1121
110486be17dSPeter Klausler      !ERROR: Impure procedure 'impure' may not be referenced in DO CONCURRENT
11164ab3302SCarolineConcatto      a(j) = x%tbp_impure(j) ! C1139
11264ab3302SCarolineConcatto    end do
11364ab3302SCarolineConcatto  end subroutine
11464ab3302SCarolineConcatto
11564ab3302SCarolineConcatto  subroutine test3
11664ab3302SCarolineConcatto    type :: t
11764ab3302SCarolineConcatto      integer :: i
11864ab3302SCarolineConcatto    end type
11964ab3302SCarolineConcatto    type(t) :: a(10), b
12064ab3302SCarolineConcatto    forall (i=1:10)
12164ab3302SCarolineConcatto      a(i) = t(pure(i))  ! OK
12264ab3302SCarolineConcatto    end forall
12364ab3302SCarolineConcatto    forall (i=1:10)
12464ab3302SCarolineConcatto      !ERROR: Impure procedure 'impure' may not be referenced in a FORALL
12564ab3302SCarolineConcatto      a(i) = t(impure(i))  ! C1037
12664ab3302SCarolineConcatto    end forall
12764ab3302SCarolineConcatto  end subroutine
12864ab3302SCarolineConcatto
129452d7ebcSpeter klausler  subroutine test4(ch)
130452d7ebcSpeter klausler    type :: t
131452d7ebcSpeter klausler      real, allocatable :: x
132452d7ebcSpeter klausler    end type
133452d7ebcSpeter klausler    type(t) :: a(1), b(1)
134452d7ebcSpeter klausler    character(*), intent(in) :: ch
135452d7ebcSpeter klausler    allocate (b(1)%x)
136452d7ebcSpeter klausler    ! Intrinsic functions and a couple subroutines are pure; do not emit errors
137452d7ebcSpeter klausler    do concurrent (j=1:1)
138452d7ebcSpeter klausler      b(j)%x = cos(1.) + len(ch)
139452d7ebcSpeter klausler      call move_alloc(from=b(j)%x, to=a(j)%x)
140452d7ebcSpeter klausler    end do
141452d7ebcSpeter klausler  end subroutine
142452d7ebcSpeter klausler
14364ab3302SCarolineConcattoend module
144