/[MITgcm]/MITgcm_contrib/ESMF/global_ocean.128x60x15/code/driver_run.F
ViewVC logotype

Annotation of /MITgcm_contrib/ESMF/global_ocean.128x60x15/code/driver_run.F

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


Revision 1.2 - (hide annotations) (download)
Thu May 12 02:25:50 2005 UTC (20 years, 2 months ago) by cnh
Branch: MAIN
Changes since 1.1: +12 -1 lines
Added extra exports to ocean

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

  ViewVC Help
Powered by ViewVC 1.1.22