OSDN Git Service

2010-04-24 Kai Tietz <kai.tietz@onevision.com>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / sequence_types_1.f90
1 ! { dg-do compile }
2 ! Tests the fix for PR28590, in which pointer components of sequence
3 ! types would give the error that the component is itself not a
4 ! sequence type (4.4.1) if the component was not already defined.
5 !
6 ! Contributed by Chris Nelson <ccnelson@itacllc.com>
7
8 module data_types
9   Integer, Parameter :: kindAry    = selected_int_kind(r=8)
10   Integer, Parameter :: kindInt    = selected_int_kind(r=8)
11
12   Integer, Parameter :: kindQ      = selected_real_kind(p=6,r=37)
13   Integer, Parameter :: kindXYZ    = selected_real_kind(p=13,r=200)
14   Integer, Parameter :: kindDouble = selected_real_kind(p=13,r=200)
15
16   type GroupLoadInfo
17     sequence
18     Integer(kindAry)          :: loadMode
19     Integer(kindAry)          :: normalDir
20     Real(kindQ)               :: refS, refL, refX, refY, refZ
21     Real(kindQ)               :: forcex,   forcey,   forcez 
22     Real(kindQ)               :: forcexv,  forceyv,  forcezv 
23     Real(kindQ)               :: momx,     momy,     momz 
24     Real(kindQ)               :: momxv,    momyv,    momzv 
25     Real(kindQ)               :: flmassx,  flmassy,  flmassz 
26     Real(kindQ)               :: flmomtmx, flmomtmy, flmomtmz 
27     Real(kindQ)               :: flheatN
28   end type GroupLoadInfo
29
30   type GroupRigidMotion
31     sequence
32     Integer(kindInt)                     :: motiontyp
33     Real(kindXYZ), dimension(3)          :: xref
34     Real(kindXYZ), dimension(3)          :: angCurrent
35     Real(kindXYZ), dimension(3)          :: xdot
36     Real(kindXYZ), dimension(3)          :: angNew
37     Real(kindXYZ), dimension(3)          :: angRate
38     Real(kindDouble)                     :: curTim
39     Real(kindXYZ)              , pointer :: properties
40     Type(PrescribedMotionData) , pointer :: PrescribeDat
41   end type GroupRigidMotion
42
43   type PrescribedMotionData
44     sequence
45     Integer(kindInt)            :: prescr_typ
46     Real(kindXYZ), dimension(3) :: xvel
47     Real(kindXYZ)               :: amplitude
48     Real(kindXYZ)               :: frequency
49     Real(kindXYZ)               :: phase
50     Real(kindXYZ), dimension(3) :: thetadot
51     Real(kindXYZ), dimension(3) :: thetaddot
52   end type PrescribedMotionData
53   
54   type GroupDeformingMotion
55     sequence
56     Integer(kindAry) :: nmodes
57   end type GroupDeformingMotion
58   
59   type GroupLL
60     sequence
61     type(GroupLL)             , pointer :: next
62     type(GroupLL)             , pointer :: parent
63     character(32)                       :: name
64     type(GroupDefLL)          , pointer :: entities
65     type(GroupLoadInfo)       , pointer :: loadInfo
66     type(GroupRigidMotion)    , pointer :: RigidMotion
67     type(GroupDeformingMotion), pointer :: DeformingMotion
68   end type GroupLL
69   
70   type GroupDefLL 
71     sequence
72     type ( GroupDefLL ), pointer            :: next
73     Integer(kindInt)                        :: zone
74     Integer(kindInt)                        :: surface
75     type ( GroupLL ), pointer               :: subGrp
76     Integer(kindInt)                        :: normalDir
77     Integer(kindInt), dimension(:), pointer :: subset
78   end type GroupDefLL
79 end module data_types
80 ! { dg-final { cleanup-modules "data_types" } }