/[MITgcm]/MITgcm_contrib/PRM/prmtop_mod.dir/src/prmtop.F90
ViewVC logotype

Annotation of /MITgcm_contrib/PRM/prmtop_mod.dir/src/prmtop.F90

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.2 - (hide annotations) (download)
Fri Apr 8 14:55:40 2005 UTC (20 years, 3 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint63m, checkpoint63n, HEAD
Changes since 1.1: +87 -80 lines
Added in allocation of different models to different CPU sets etc..

1 cnh 1.1 MODULE PRMTop
2    
3     USE EEsmf_Mod
4    
5     ! Internal state type for a PRMTop component
6 cnh 1.2 ! cTab :: Generic information held about a component.
7     ! :: Includes how many children, basic start/end/base time
8     ! :: information etc...
9 cnh 1.1 TYPE PRMTopInternalState
10 cnh 1.2 TYPE(EEsmfCattr) :: cTab
11 cnh 1.1 END TYPE
12    
13     CONTAINS
14    
15     SUBROUTINE ComponentsInit( theComponents )
16     !
17     ! Set up the components for this experiment.
18     ! This is done by allocating a series of combined component and state
19 cnh 1.2 ! derived type objects. The returned list of components is then assigned
20 cnh 1.1 ! to point to this set of objects.
21    
22     ! Routine arguments
23 cnh 1.2 ! theComponents :: Pointer to components that are created and initialized.
24     ! :: The pointer should not be "associated" on entry to
25     ! :: ComponentsInit. On return from ComponentsInit the
26     ! :: pointer will reference the components that have been
27     ! :: created.
28 cnh 1.1 TYPE( EEsmfComponentList ), POINTER :: theComponents
29    
30     ! Local variables
31 cnh 1.2 ! internalState :: Type that collects together all the internal state
32     ! :: associated with a PRM configuration. The PRM component
33     ! :: ESMF internal state could be set to point to this
34     ! :: location so that subsequent calls to the PRM run
35     ! :: routines have access to the PRM state.
36     ! coarseGridOcean :: Holds the reference to the PRM coarse grid ocean
37     ! :: component.
38     ! fineGridOceans :: Holds the references to the PRM fine grid ocean
39     ! :: components.
40     ! coarse2fine :: Holds references to the coarse2fine "couplers".
41     ! fine2coarse :: Holds references to the fine2coarse "coupler".
42     !
43 cnh 1.1 TYPE( PRMTopInternalState ), POINTER :: internalState
44     TYPE( EEsmfGridComp ), ALLOCATABLE :: coarseGridOcean(:)
45     TYPE( EEsmfGridComp ), ALLOCATABLE :: fineGridOceans(:)
46     TYPE( EEsmfCplComp ), ALLOCATABLE :: coarse2fine(:)
47     TYPE( EEsmfCplComp ), ALLOCATABLE :: fine2coarse(:)
48     TYPE( EEsmfGridComp ), POINTER :: gcArr(:)
49 cnh 1.2 TYPE( EEsmfCplComp ), POINTER :: ccArr(:)
50 cnh 1.1
51     !
52 cnh 1.2 ! o Boot up top PRM component
53    
54     ! First read in table of prmTop setup and put that information
55     ! into the prmTop internal state.
56     ! This table specifies one or more sets of child components to create.
57     ! Each component set corresponds to a specific set of Init(), Run() and
58     ! Finalize() (IRF) routines. The IRF routines need to be known at link time.
59     ! Which IRF routines are used for which component set is based on the prefix
60     ! given in the "preflist: line" entry for that component set that is read
61     ! from the table of components.
62 cnh 1.1 CALL PRMBoot( 'prmtop.rc', internalState )
63 cnh 1.2
64     ! Allocate requested numbers of child gridded and coupler components.
65     ! This involves calling the ESMF component create functions which, amongst
66     ! other things binds the components to certain PETs.
67     CALL EEsmfAllocChildren( internalState%cTab )
68    
69     ! For a PRM setup
70     ! The coarse grid ocean is the first set in the list of children.
71     ! The fine grid oceans are the second set in the list of children.
72     ! The coarse2fine couplers are the third set in the list of children.
73     ! The fine2coarse couplers are the fourth set in the list of children.
74    
75 cnh 1.1 !
76 cnh 1.2 ! Setup the components
77     ! We now set the IRF functions for each component and
78     ! then carry out the initialize stage.
79     ! First PRM component set is cg. There is only one of these.
80     ! Second PRM component set are the fg's. There are n of these.
81     ! Third PRM component set are the cg2fg couplers. There are n of these.
82     ! Fourth PRM component set are the fg2cg couplers. There is 1 of these.
83 cnh 1.1 CALL EEsmfMakeGridComp(coarseGridOcean,
84     I 'cg.rc')
85     CALL EEsmfMakeGridComp( fineGridOceans,
86     & 'fg.rc')
87     CALL EEsmfMakeCplComp( fine2coarse, fineGridOceans,
88     & coarseGridOcean,
89     I 'f2c.rc')
90     CALL EEsmfMakeCplComp( coarse2fine, coarseGridOcean,
91     & fineGridOceans,
92     I 'c2f.rc')
93    
94    
95     END SUBROUTINE ComponentsInit
96    
97     SUBROUTINE ComponentsRun( theComponents )
98     TYPE( EEsmfComponentList ), POINTER :: theComponents
99     END SUBROUTINE ComponentsRun
100    
101     SUBROUTINE ComponentsFinalize( theComponents )
102     TYPE( EEsmfComponentList ), POINTER :: theComponents
103     END SUBROUTINE ComponentsFinalize
104    
105     SUBROUTINE PRMBoot( theResourceFile, theState )
106    
107     ! Routine arguments
108     CHARACTER*(*) :: theResourceFile
109     TYPE( PRMTopInternalState ), POINTER :: theState
110    
111     ! Local variables
112     INTEGER rc
113     TYPE (ESMF_Config) :: cf
114     INTEGER :: nSets, nComps, I
115     CHARACTER(len=1024) :: fPref
116     CHARACTER(len=1024) :: cType
117    
118     ! Boot PRMTop
119    
120     ! Allocate a PRMTop internal state object
121     ALLOCATE( theState )
122    
123     ! Read PRM config
124     cf = ESMF_ConfigCreate(rc)
125     CALL ESMF_ConfigLoadFile( cf, theResourceFile, rc = rc)
126    
127     ! Find how many sets of components have been requested.
128     ! If the number requested is less than 1 it is an error.
129     CALL EEsmf_ReadConfig( cf, label='nsets:', default=1,
130 cnh 1.2 & rVal=theState%cTab%nSets, rc=rc )
131     IF ( theState%cTab%nSets <= 0 ) THEN
132 cnh 1.1 STOP 'ABNORMAL END:: PRMTop - nSets <= 0'
133     ENDIF
134    
135     ! Get basic details for each components set
136 cnh 1.2 ALLOCATE( theState%cTab%cTypeArr(theState%cTab%nSets) )
137     ALLOCATE( theState%cTab%cPrefArr(theState%cTab%nSets) )
138     ALLOCATE( theState%cTab%nComps(theState%cTab%nSets) )
139     theState%cTab%nCTypeArr = 0
140     theState%cTab%nCPrefArr = 0
141     theState%cTab%nNComps = 0
142 cnh 1.1
143 cnh 1.2 DO I=1,theState%cTab%nSets
144 cnh 1.1 ! Get the component type for each component set.
145     CALL EEsmf_ReadConfig( cf, label='ctype:', default='gridded', index=I,
146 cnh 1.2 & rVal=theState%cTab%cTypeArr(I), rc=rc )
147     IF ( rc .EQ. ESMF_SUCCESS ) theState%cTab%nCTypeArr =
148     & theState%cTab%nCTypeArr+1
149 cnh 1.1 ! Get the number of components to create for each component set.
150     CALL EEsmf_ReadConfig( cf, label='counts:', default=1, index=I,
151 cnh 1.2 & rVal=theState%cTab%nComps(I), rc=rc )
152     IF ( rc .EQ. ESMF_SUCCESS ) theState%cTab%nNComps =
153     & theState%cTab%nNComps+1
154 cnh 1.1 ! Get the prefix label used to distinguish each component set.
155     CALL EEsmf_ReadConfig( cf, label='preflist:', default='cg', index=I,
156 cnh 1.2 & rVal=theState%cTab%cPrefArr(I), rc=rc )
157     IF ( rc .EQ. ESMF_SUCCESS ) theState%cTab%nCPrefArr =
158     & theState%cTab%nCPrefArr+1
159 cnh 1.1 ENDDO
160    
161 cnh 1.2 CALL EEsmf_ReadConfig( cf, label='topStartTime:', default=0.,
162     & rVal=theState%cTab%startTime, rc=rc )
163    
164     IF ( theState%cTab%nCPrefArr .NE. theState%cTab%nSets ) THEN
165     STOP 'ABNORMAL END: PRMTop.PRMBoot found too few file prefix entries.'
166     ENDIF
167     IF ( theState%cTab%nCTypeArr .NE. theState%cTab%nSets ) THEN
168     STOP 'ABNORMAL END: PRMTop.PRMBoot found too few component type entries.'
169     ENDIF
170     IF ( theState%cTab%nNComps .NE. theState%cTab%nSets ) THEN
171     STOP 'ABNORMAL END: PRMTop.PRMBoot found too few component count entries.'
172     ENDIF
173    
174    
175 cnh 1.1
176     END SUBROUTINE PRMBoot
177    
178     SUBROUTINE PRMShut( theState )
179    
180     ! Routine arguments
181     TYPE( PRMTopInternalState ), POINTER :: theState
182    
183     ! Free PRM internal data
184 cnh 1.2 DEALLOCATE( theState%cTab%cPrefArr )
185     DEALLOCATE( theState%cTab%cTypeArr )
186     DEALLOCATE( theState%cTab%nComps )
187 cnh 1.1
188     ! Free PRMTop internal state object
189     DEALLOCATE( theState )
190    
191     END SUBROUTINE PRMShut
192    
193     END MODULE PRMTop

  ViewVC Help
Powered by ViewVC 1.1.22