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

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

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

revision 1.1 by cnh, Tue Apr 5 19:57:02 2005 UTC revision 1.2 by cnh, Fri Apr 8 14:55:40 2005 UTC
# Line 3  Line 3 
3        USE EEsmf_Mod        USE EEsmf_Mod
4    
5  !     Internal state type for a PRMTop component  !     Internal state type for a PRMTop component
6  !     nSets         :: Total number of component sets in this PRM.  !     cTab   :: Generic information held about a component.
7  !     cTypeArr      :: Array of nSets values that specify the  !            :: Includes how many children, basic start/end/base time
8  !                   :: component type of the components in  !            :: information etc...
 !                   :: a component set.  
 !     ncTypeArr     :: Number of entries in cTypeArr (should  
 !                   :: be the same as nSets).  
 !     fPrefArr      :: Array of prefix strings used to name  
 !                   :: the components.  
 !     nFPrefArr     :: Number of entries in fPrefArr (should  
 !                   :: be the same as nSets).  
 !     nComps        :: Number of components in each component  
 !                   :: set.  
 !     nNComps       :: Number of entries in the nComps list.  
 !                   :: (should be the same as nSets).  
 !     topTimeStep   :: Time step for PRMTop.  
 !     topStartStep  :: Time to start run.  
 !     topEndTime    :: Time to end run.  
 !     topStartStep  :: Starting step number.  
 !     rootDirectory :: Root directory for all relative pathnames used  
 !                   :: in PRMTop  
9        TYPE PRMTopInternalState        TYPE PRMTopInternalState
10         INTEGER                               :: nSets         TYPE(EEsmfCattr)                      :: cTab
        CHARACTER(LEN=1024), POINTER          :: cTypeArr(:)  
        INTEGER                               :: nCTypeArr  
        CHARACTER(LEN=1024), POINTER          :: fPrefArr(:)  
        INTEGER                               :: nFPrefArr  
        INTEGER, POINTER                      :: nComps(:)  
        INTEGER                               :: nNComps  
        INTEGER                               :: topTimeStep  
        INTEGER                               :: topStartTime  
        INTEGER                               :: topEndTime  
        INTEGER                               :: topStartStep  
        CHARACTER, POINTER                    :: rootDirectory  
11        END TYPE        END TYPE
12    
13        CONTAINS        CONTAINS
# Line 44  Line 16 
16  !  !
17  !     Set up the components for this experiment.  !     Set up the components for this experiment.
18  !     This is done by allocating a series of combined component and state  !     This is done by allocating a series of combined component and state
19  !     derived type objects. The returned list of components is then assigned  !     derived type objects. The returned list of components is then assigned
20  !     to point to this set of objects.  !     to point to this set of objects.
21    
22  !     Routine arguments  !     Routine arguments
23    !     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        TYPE( EEsmfComponentList ),    POINTER :: theComponents        TYPE( EEsmfComponentList ),    POINTER :: theComponents
29    
30  !     Local variables  !     Local variables
31    !     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        TYPE( PRMTopInternalState   ), POINTER :: internalState        TYPE( PRMTopInternalState   ), POINTER :: internalState
44        TYPE( EEsmfGridComp ), ALLOCATABLE  :: coarseGridOcean(:)        TYPE( EEsmfGridComp ), ALLOCATABLE  :: coarseGridOcean(:)
45        TYPE( EEsmfGridComp ), ALLOCATABLE  :: fineGridOceans(:)        TYPE( EEsmfGridComp ), ALLOCATABLE  :: fineGridOceans(:)
46        TYPE( EEsmfCplComp  ), ALLOCATABLE  :: coarse2fine(:)        TYPE( EEsmfCplComp  ), ALLOCATABLE  :: coarse2fine(:)
47        TYPE( EEsmfCplComp  ), ALLOCATABLE  :: fine2coarse(:)        TYPE( EEsmfCplComp  ), ALLOCATABLE  :: fine2coarse(:)
48        TYPE( EEsmfGridComp ), POINTER  :: gcArr(:)        TYPE( EEsmfGridComp ), POINTER  :: gcArr(:)
49        TYPE( EEsmfCplComp ),  POINTER  :: ccArr(:)        TYPE( EEsmfCplComp  ),  POINTER :: ccArr(:)
50    
51  !  !
52  !     Boot up ESMF  !     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        CALL PRMBoot( 'prmtop.rc', internalState )        CALL PRMBoot( 'prmtop.rc', internalState )
63        IF ( internalState%nFPrefArr .NE. internalState%nSets ) THEN  
64         STOP 'ABNORMAL END: PRMTop found too few file prefix entries'  !     Allocate requested numbers of child gridded and coupler components.
65        ENDIF  !     This involves calling the ESMF component create functions which, amongst
66        IF ( internalState%nCTypeArr .NE. internalState%nSets ) THEN  !     other things binds the components to certain PETs.
67         STOP 'ABNORMAL END: PRMTop found too few component type entries'        CALL EEsmfAllocChildren( internalState%cTab )
68        ENDIF  
69        IF ( internalState%nNComps   .NE. internalState%nSets ) THEN  !     For a PRM setup
70         STOP 'ABNORMAL END: PRMTop found too few component count entries'  !     The coarse grid ocean is the first set in the list of children.
71        ENDIF  !     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  !     Allocate requested gridded and coupler components.  !     The fine2coarse couplers are the fourth set in the list of children.
74        DO I=1,internalState%nSets  
        IF ( TRIM(internalState%cTypeArr(I)) .EQ. 'gridded' ) THEN  
         CALL EEsmfAllocGridC( gcArr, internalState%nComps(I) )  
        ENDIF  
        IF ( TRIM(internalState%cTypeArr(I)) .EQ. 'coupler' ) THEN  
         CALL EEsmfAllocCplC(  ccArr, internalState%nComps(I) )  
        ENDIF  
       ENDDO  
       CALL PRMShut( internalState )  
 !     CALL EEsmfAllocGridC( coarseGridOcean, 1      )  
 !     CALL EEsmfAllocGridC( fineGridOceans,  nFine  )  
 !     CALL EEsmfAllocCplC(  coarse2Fine,     nFine  )  
 !     CALL EEsmfAllocCplC(  fine2Coarse,     1      )  
75  !  !
76  !     Setup the components we need  !     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        CALL EEsmfMakeGridComp(coarseGridOcean,        CALL EEsmfMakeGridComp(coarseGridOcean,
84       I 'cg.rc')       I 'cg.rc')
85        CALL EEsmfMakeGridComp( fineGridOceans,        CALL EEsmfMakeGridComp( fineGridOceans,
# Line 135  Line 127 
127  !     Find how many sets of components have been requested.  !     Find how many sets of components have been requested.
128  !     If the number requested is less than 1 it is an error.  !     If the number requested is less than 1 it is an error.
129        CALL EEsmf_ReadConfig( cf, label='nsets:', default=1,        CALL EEsmf_ReadConfig( cf, label='nsets:', default=1,
130       &                       rVal=theState%nSets, rc=rc )       &                       rVal=theState%cTab%nSets, rc=rc )
131        IF ( theState%nSets <= 0 ) THEN        IF ( theState%cTab%nSets <= 0 ) THEN
132         STOP 'ABNORMAL END:: PRMTop - nSets <= 0'         STOP 'ABNORMAL END:: PRMTop - nSets <= 0'
133        ENDIF        ENDIF
134    
135  !     Get basic details for each components set  !     Get basic details for each components set
136        ALLOCATE( theState%cTypeArr(theState%nSets) )        ALLOCATE( theState%cTab%cTypeArr(theState%cTab%nSets) )
137        ALLOCATE( theState%fPrefArr(theState%nSets) )        ALLOCATE( theState%cTab%cPrefArr(theState%cTab%nSets) )
138        ALLOCATE( theState%nComps(theState%nSets)   )        ALLOCATE( theState%cTab%nComps(theState%cTab%nSets)   )
139        theState%nCTypeArr = 0        theState%cTab%nCTypeArr = 0
140        theState%nFPrefArr = 0        theState%cTab%nCPrefArr = 0
141        theState%nNComps   = 0        theState%cTab%nNComps   = 0
142    
143        DO I=1,theState%nSets        DO I=1,theState%cTab%nSets
144  !      Get the component type for each component set.  !      Get the component type for each component set.
145         CALL EEsmf_ReadConfig( cf, label='ctype:', default='gridded', index=I,         CALL EEsmf_ReadConfig( cf, label='ctype:', default='gridded', index=I,
146       &                        rVal=theState%cTypeArr(I), rc=rc )       &                        rVal=theState%cTab%cTypeArr(I), rc=rc )
147         IF ( rc .EQ. ESMF_SUCCESS ) theState%nCTypeArr = theState%nCTypeArr+1         IF ( rc .EQ. ESMF_SUCCESS ) theState%cTab%nCTypeArr =
148         &  theState%cTab%nCTypeArr+1
149  !      Get the number of components to create for each component set.  !      Get the number of components to create for each component set.
150         CALL EEsmf_ReadConfig( cf, label='counts:', default=1, index=I,         CALL EEsmf_ReadConfig( cf, label='counts:', default=1, index=I,
151       &                        rVal=theState%nComps(I), rc=rc )       &                        rVal=theState%cTab%nComps(I), rc=rc )
152         IF ( rc .EQ. ESMF_SUCCESS ) theState%nNComps = theState%nNComps+1         IF ( rc .EQ. ESMF_SUCCESS ) theState%cTab%nNComps =
153         &  theState%cTab%nNComps+1
154  !      Get the prefix label used to distinguish each component set.  !      Get the prefix label used to distinguish each component set.
155         CALL EEsmf_ReadConfig( cf, label='preflist:', default='cg', index=I,         CALL EEsmf_ReadConfig( cf, label='preflist:', default='cg', index=I,
156       &                        rVal=theState%fPrefArr(I), rc=rc )       &                        rVal=theState%cTab%cPrefArr(I), rc=rc )
157         IF ( rc .EQ. ESMF_SUCCESS ) theState%nFPrefArr = theState%nFPrefArr+1         IF ( rc .EQ. ESMF_SUCCESS ) theState%cTab%nCPrefArr =
158         &  theState%cTab%nCPrefArr+1
159        ENDDO        ENDDO
160    
161        CALL EEsmf_ReadConfig( cf, label='topStartTime:', default=0,        CALL EEsmf_ReadConfig( cf, label='topStartTime:', default=0.,
162       &                       rVal=theState%topStartTime, rc=rc )       &                       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    
176        END SUBROUTINE PRMBoot        END SUBROUTINE PRMBoot
177    
# Line 174  Line 181 
181        TYPE( PRMTopInternalState ), POINTER :: theState        TYPE( PRMTopInternalState ), POINTER :: theState
182    
183  !     Free PRM internal data  !     Free PRM internal data
184        DEALLOCATE( theState%fPrefArr )        DEALLOCATE( theState%cTab%cPrefArr )
185        DEALLOCATE( theState%cTypeArr )        DEALLOCATE( theState%cTab%cTypeArr )
186        DEALLOCATE( theState%nComps   )        DEALLOCATE( theState%cTab%nComps   )
187    
188  !     Free PRMTop internal state object  !     Free PRMTop internal state object
189        DEALLOCATE( theState )        DEALLOCATE( theState )

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22