/[MITgcm]/MITgcm_contrib/ESMF/interface_test/code/driver_run.F
ViewVC logotype

Annotation of /MITgcm_contrib/ESMF/interface_test/code/driver_run.F

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


Revision 1.2 - (hide annotations) (download)
Mon Feb 16 18:57:52 2004 UTC (21 years, 5 months ago) by cnh
Branch: MAIN
CVS Tags: adoption_1_0_pre_A, HEAD
Changes since 1.1: +164 -0 lines
Base files needed for simple component build

1 cnh 1.2 C $Header: $
2     C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: DRIVER_RUN
8     C !INTERFACE:
9     SUBROUTINE DRIVER_RUN(
10     I atm_HeatFlux, atm_TauX, atm_TauY,
11     I atm_Qlatent, atm_Qsensible, atm_Qlongwave,
12     I atm_Qshortwave,
13     I atm_uVelGround, atm_vVelGround,
14     I atm_FWFlux,
15     O ocn_SSTocn,
16     I startStep, stopStep
17     & )
18    
19     C !DESCRIPTION: \bv
20     C *==================================================================
21     C | SUBROUTINE driver_run
22     C | o External driver control routine for MITgcm forward step
23     C | execution phase.
24     C *==================================================================
25     C |
26     C | DRIVER routines are used to control the MITgcm code from an external
27     C | driver. This routine invokes the forward phase of code execution.
28     C | The driver here is written for an ocean configuration and is designed
29     C | for use with either an argument based call/return interface or with a
30     C | messaging based "event loop" interface.
31     C |
32     C *==================================================================
33     C \ev
34    
35     C !USES:
36     IMPLICIT NONE
37     C == Global variables ==
38     #include "SIZE.h"
39     #include "EEPARAMS.h"
40     #include "EESUPPORT.h"
41     #include "PARAMS.h"
42     #include "OCNCPL.h"
43    
44     C == Routine arguments ==
45     _RL atm_HeatFlux( 1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
46     _RL atm_TauX( 1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
47     _RL atm_TauY( 1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
48     _RL atm_Qlatent( 1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
49     _RL atm_Qsensible( 1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
50     _RL atm_Qlongwave( 1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
51     _RL atm_Qshortwave( 1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
52     _RL atm_uVelGround( 1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
53     _RL atm_vVelGround( 1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
54     _RL atm_FWFlux( 1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
55     _RL ocn_SSTocn( 1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
56     INTEGER startStep, stopStep
57    
58     C == Local variables ==
59     C myThid :: Thread number for this instance of the routine
60     INTEGER myThid
61     INTEGER myCurrentIter
62     _RL myCurrentTime
63     INTEGER iLoop
64     INTEGER i,j,bi,bj
65     CHARACTER*(MAX_LEN_MBUF) msgBuf
66     CHARACTER*13 fNam
67     CEOP
68    
69     CALL COMP_OCN_PUSH_CONTEXT(1)
70     Cnocall myThid = 1
71     Cnocall CLOSE(errorMessageUnit)
72     Cnocall CLOSE(standardMessageUnit)
73     ! myProcessStr = '0000'
74     Cnocall WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:4)
75     Cnocall OPEN(standardMessageUnit,FILE=fNam,STATUS='old',POSITION='append')
76     Cnocall WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:4)
77     Cnocall OPEN(errorMessageUnit,FILE=fNam,STATUS='old',POSITION='append')
78    
79    
80     Cnocall WRITE(msgBuf,*) 'Entering OCN driver_run'
81     Cnocall CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
82     Cnocall & SQUEEZE_RIGHT , 1)
83    
84     C Extract the import fields
85     DO bj=myByLo(myThid),myByHi(myThid)
86     DO bi=myBxLo(myThid),myBxHi(myThid)
87     DO j=1-OLy,sNy+OLy
88     DO i=1-OLx,sNx+OLx
89     HeatFlux( i,j,bi,bj)=atm_HeatFlux( i,j,bi,bj)
90     TauX( i,j,bi,bj)=atm_tauX( i,j,bi,bj)
91     TauY( i,j,bi,bj)=atm_tauY( i,j,bi,bj)
92     Qlatent( i,j,bi,bj)=atm_qLatent( i,j,bi,bj)
93     Qsensible( i,j,bi,bj)=atm_qSensible( i,j,bi,bj)
94     Qlongwave( i,j,bi,bj)=atm_qLongwave( i,j,bi,bj)
95     Qshortwave( i,j,bi,bj)=atm_qShortwave(i,j,bi,bj)
96     uVelGround( i,j,bi,bj)=atm_uVelGround(i,j,bi,bj)
97     vVelGround( i,j,bi,bj)=atm_vVelGround(i,j,bi,bj)
98     FWFlux( i,j,bi,bj)=atm_FWFlux( i,j,bi,bj)
99     ENDDO
100     ENDDO
101     ENDDO
102     ENDDO
103    
104     myCurrentTime = startTime+startStep*deltaTClock
105     myCurrentIter = nIter0+startStep
106     myThid = 1
107     nTimesteps = stopStep-startStep
108    
109     Cnocall WRITE(msgBuf,*) 'OCN driver_run begin: myCurrentTime = ', myCurrentTime
110     Cnocall CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
111     Cnocall & SQUEEZE_RIGHT , 1)
112     Cnocall WRITE(msgBuf,*) 'OCN driver_run begin: myCurrentIter = ', myCurrentIter
113     Cnocall CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
114     Cnocall & SQUEEZE_RIGHT , 1)
115     Cnocall WRITE(msgBuf,*) 'OCN driver_run begin: nTimeSteps = ', nTimeSteps
116     Cnocall CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
117     Cnocall & SQUEEZE_RIGHT , 1)
118    
119     Cnocall CALL MONITOR( myCurrentIter, myCurrentTime, myThid )
120    
121     Cnocall DO iLoop = 1, nTimeSteps-1
122     Cnocall CALL CPL_IMPORT_EXTERNAL_DATA(
123     Cnocall I myCurrentIter, myCurrentTime, myThid )
124     Cnocall CALL FORWARD_STEP_EXECUTE( iLoop, myCurrentTime, myCurrentIter, myThid )
125     Cnocall CALL FORWARD_STEP_SETUP( iLoop+1, myCurrentTime, myCurrentIter, myThid )
126     Cnocall ENDDO
127    
128     Cnocall iLoop = nTimeSteps
129     Cnocall CALL CPL_IMPORT_EXTERNAL_DATA(
130     Cnocall I myCurrentIter, myCurrentTime, myThid )
131     Cnocall CALL FORWARD_STEP_EXECUTE( iLoop, myCurrentTime, myCurrentIter, myThid )
132     Cnocall CALL FORWARD_STEP_SETUP( iLoop+1, myCurrentTime, myCurrentIter, myThid )
133    
134     C Fill the export fields
135     Cnocall DO bj=myByLo(myThid),myByHi(myThid)
136     Cnocall DO bi=myBxLo(myThid),myBxHi(myThid)
137     Cnocall DO j=1,sNy
138     Cnocall DO i=1,sNx
139     Cnocall ocn_SSTocn( i,j,bi,bj)=SSTocn2cpl( i,j,bi,bj)
140     Cnocall ENDDO
141     Cnocall ENDDO
142     Cnocall ENDDO
143     Cnocall ENDDO
144    
145     Cnocall WRITE(msgBuf,*) 'OCN driver_run end: myCurrentTime = ', myCurrentTime
146     Cnocall CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
147     Cnocall & SQUEEZE_RIGHT , 1)
148     Cnocall WRITE(msgBuf,*) 'OCN driver_run end: myCurrentIter = ', myCurrentIter
149     Cnocall CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
150     Cnocall & SQUEEZE_RIGHT , 1)
151     Cnocall WRITE(msgBuf,*) 'OCN driver_run end: nTimeSteps = ', nTimeSteps
152     Cnocall CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
153     Cnocall & SQUEEZE_RIGHT , 1)
154     Cnocall
155     Cnocall WRITE(msgBuf,*) 'Exiting OCN driver_run'
156     Cnocall CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
157     Cnocall & SQUEEZE_RIGHT , 1)
158     Cnocall
159     Cnocall CLOSE(errorMessageUnit)
160     Cnocall CLOSE(standardMessageUnit)
161     CALL COMP_OCN_POP_CONTEXT(1)
162    
163     RETURN
164     END

  ViewVC Help
Powered by ViewVC 1.1.22