3 ! Tests the fix for PR68216
5 ! Reported on clf: https://groups.google.com/forum/#!topic/comp.lang.fortran/eWQTKfqKLZc
9 ! This is based on the first testcase, from Francisco (Ayyy LMAO). Original
10 ! lines are commented out. The second testcase from this thread is acalled
11 ! at the end of the program.
15 CHARACTER(LEN
=:),DIMENSION(:),ALLOCATABLE
:: array_lineas
16 CHARACTER(LEN
=:),DIMENSION(:),ALLOCATABLE
:: array_copia
17 character (3), dimension (2) :: array_fijo
= ["abc","def"]
18 character (100) :: buffer
19 INTEGER :: largo
, cant_lineas
, i
21 write (buffer
, "(2a3)") array_fijo
23 ! WRITE(*,*) ' Escriba un numero para el largo de cada linea'
25 largo
= LEN (array_fijo
)
27 ! WRITE(*,*) ' Escriba la cantidad de lineas'
28 ! READ(*,*) cant_lineas
29 cant_lineas
= size (array_fijo
, 1)
31 ALLOCATE(CHARACTER(LEN
=largo
) :: array_lineas(cant_lineas
))
33 ! WRITE(*,*) 'Escriba el array', len(array_lineas), size(array_lineas)
34 READ(buffer
,"(2a3)") (array_lineas(i
),i
=1,cant_lineas
)
36 ! WRITE(*,*) 'Array guardado: '
38 ! WRITE(*,*) array_lineas(i)
40 if (any (array_lineas
.ne
. array_fijo
)) STOP 1
42 ! The following are additional tests beyond that of the original.
44 ! Check that allocation with source = another deferred length is OK
45 allocate (array_copia
, source
= array_lineas
)
46 if (any (array_copia
.ne
. array_fijo
)) STOP 2
47 deallocate (array_lineas
, array_copia
)
49 ! Check that allocation with source = a non-deferred length is OK
50 allocate (array_lineas
, source
= array_fijo
)
51 if (any (array_lineas
.ne
. array_fijo
)) STOP 3
52 deallocate (array_lineas
)
54 ! Check that allocation with MOLD = a non-deferred length is OK
55 allocate (array_copia
, mold
= [array_fijo(:)(1:2), array_fijo(:)(1:2)])
56 if (size (array_copia
, 1) .ne
. 4) STOP 4
57 if (LEN (array_copia
, 1) .ne
. 2) STOP 5
59 ! Check that allocation with MOLD = another deferred length is OK
60 allocate (array_lineas
, mold
= array_copia
)
61 if (size (array_copia
, 1) .ne
. 4) STOP 6
62 if (LEN (array_copia
, 1) .ne
. 2) STOP 7
63 deallocate (array_lineas
, array_copia
)
68 subroutine testdefchar
70 ! This is the testcase in the above thread from Blokbuster
73 character(:), allocatable
:: test(:)
75 allocate(character(3) :: test(2))
78 if (any (test
.ne
. ['abc', 'def'])) STOP 8
80 test
= ['aa','bb','cc']
81 if (any (test
.ne
. ['aa', 'bb', 'cc'])) STOP 9
83 end subroutine testdefchar