PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / prof / dynamic_dispatch_6.f03
blob82e4e6f9b8ed17d621de1b7aa5d8a2483acae587
1 ! { dg-require-profiling "-fprofile-generate" }
2 ! { dg-options "-Ofast" }
4 ! PR 45076: [OOP] gfortran.dg/dynamic_dispatch_6.f03 ICEs with -fprofile-use
6 ! Contributed by Damian Rouson <damian@rouson.net>
8 module field_module
9   implicit none
10   private
11   public :: field
12   type ,abstract :: field 
13   end type
14 end module
16 module periodic_5th_order_module
17   use field_module ,only : field
18   implicit none
19   type ,extends(field) :: periodic_5th_order
20   end type
21 end module
23 module field_factory_module
24   implicit none
25   private
26   public :: field_factory
27   type, abstract :: field_factory 
28   contains 
29     procedure(create_interface), deferred :: create 
30   end type 
31   abstract interface 
32     function create_interface(this) 
33       use field_module ,only : field
34       import :: field_factory
35       class(field_factory), intent(in) :: this 
36       class(field) ,pointer :: create_interface
37     end function
38   end interface 
39 end module
41 module periodic_5th_factory_module
42   use field_factory_module , only : field_factory
43   implicit none
44   private
45   public :: periodic_5th_factory
46   type, extends(field_factory) :: periodic_5th_factory 
47   contains 
48     procedure :: create=>new_periodic_5th_order
49   end type 
50 contains
51   function new_periodic_5th_order(this) 
52     use field_module ,only : field
53     use periodic_5th_order_module ,only : periodic_5th_order
54     class(periodic_5th_factory), intent(in) :: this
55     class(field) ,pointer :: new_periodic_5th_order
56   end function
57 end module
59 program main 
60   use field_module ,only : field 
61   use field_factory_module ,only : field_factory
62   use periodic_5th_factory_module ,only : periodic_5th_factory
63   implicit none 
64   class(field) ,pointer :: u
65   class(field_factory), allocatable :: field_creator 
66   allocate (periodic_5th_factory ::  field_creator) 
67   u => field_creator%create() 
68 end program