OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [alloc_comp_auto_array_1.f90] - Blame information for rev 715

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do run }
2
! Fix for PR29699 - see below for details.
3
!
4
! Contributed by Tobias Burnus  
5
!
6
PROGRAM vocabulary_word_count
7
 
8
  IMPLICIT NONE
9
  TYPE VARYING_STRING
10
    CHARACTER,DIMENSION(:),ALLOCATABLE :: chars
11
  ENDTYPE VARYING_STRING
12
 
13
  INTEGER :: list_size=200
14
 
15
  call extend_lists2
16
 
17
CONTAINS
18
 
19
! First the original problem: vocab_swap not being referenced caused
20
! an ICE because default initialization is used, which results in a
21
! call to gfc_conv_variable, which calls gfc_get_symbol_decl.
22
 
23
  SUBROUTINE extend_lists1
24
    type(VARYING_STRING),DIMENSION(list_size) :: vocab_swap
25
  ENDSUBROUTINE extend_lists1
26
 
27
! Curing this then uncovered two more problems: If vocab_swap were
28
! actually referenced, an ICE occurred in the gimplifier because
29
! the declaration for this automatic array is presented as a
30
! pointer to the array, rather than the array. Curing this allows
31
! the code to compile but it bombed out at run time because the
32
! malloc/free occurred in the wrong order with respect to the
33
! nullify/deallocate of the allocatable components.
34
 
35
  SUBROUTINE extend_lists2
36
    type(VARYING_STRING),DIMENSION(list_size) :: vocab_swap
37
    allocate (vocab_swap(1)%chars(10))
38
    if (.not.allocated(vocab_swap(1)%chars)) call abort ()
39
    if (allocated(vocab_swap(10)%chars)) call abort ()
40
  ENDSUBROUTINE extend_lists2
41
 
42
ENDPROGRAM vocabulary_word_count

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.