* fi.po: Update.
[official-gcc.git] / gcc / testsuite / gfortran.dg / abstract_type_6.f03
blob9dd0a37c56454cdcacf93ec15c13bbbdefd34f96
1 ! { dg-do compile }
2 ! Test the fix for PR43266, in which an ICE followed correct error messages.
4 ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
5 ! Reported in http://groups.google.ca/group/comp.lang.fortran/browse_thread/thread/f5ec99089ea72b79
7 !----------------
8 ! library code
10 module m
11 TYPE, ABSTRACT :: top
12 CONTAINS
13    PROCEDURE(xxx), DEFERRED :: proc_a ! { dg-error "must be explicit" }
14    ! some useful default behavior
15    PROCEDURE :: proc_c => top_c ! { dg-error "must be a module procedure" }
16 END TYPE top
18 ! Concrete middle class with useful behavior
19 TYPE, EXTENDS(top) :: middle
20 CONTAINS
21    ! do nothing, empty proc just to make middle concrete
22    PROCEDURE :: proc_a => dummy_middle_a ! { dg-error "must be a module procedure" }
23    ! some useful default behavior
24    PROCEDURE :: proc_b => middle_b ! { dg-error "must be a module procedure" }
25 END TYPE middle
27 !----------------
28 ! client code
30 TYPE, EXTENDS(middle) :: bottom
31 CONTAINS
32    ! useful proc to satisfy deferred procedure in top. Because we've
33    ! extended middle we wouldn't get told off if we forgot this.
34    PROCEDURE :: proc_a => bottom_a  ! { dg-error "must be a module procedure" }
35    ! calls middle%proc_b and then provides extra behavior
36    PROCEDURE :: proc_b => bottom_b
37    ! calls top_c and then provides extra behavior
38    PROCEDURE :: proc_c => bottom_c
39 END TYPE bottom
40 contains
41 SUBROUTINE bottom_b(obj)
42    CLASS(Bottom) :: obj
43    CALL obj%middle%proc_b ! { dg-error "should be a SUBROUTINE" }
44    ! other stuff
45 END SUBROUTINE bottom_b
47 SUBROUTINE bottom_c(obj)
48    CLASS(Bottom) :: obj
49    CALL top_c(obj)
50    ! other stuff
51 END SUBROUTINE bottom_c 
52 end module