/[MITgcm]/MITgcm/pkg/autodiff/active_file_control_slice.F
ViewVC logotype

Diff of /MITgcm/pkg/autodiff/active_file_control_slice.F

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

revision 1.2.2.1 by adcroft, Tue Feb 26 16:04:48 2002 UTC revision 1.13 by jmc, Fri Apr 4 23:03:59 2014 UTC
# Line 1  Line 1 
1    C $Header$
2    C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "AUTODIFF_OPTIONS.h"
5    #ifdef ALLOW_CTRL
6    # include "CTRL_OPTIONS.h"
7    #endif
8    
9    C     ==================================================================
10    C     active_file_control_slice.F: Routines to handle the I/O of active
11    C                                  variables for the adjoint calculations.
12    C                                  All files are diRect access files.
13    C     Routines:
14    C     o  ACTIVE_READ_XZ_RL  : Basic routine to handle active XZ read operations
15    C     o  ACTIVE_READ_XZ_RS  : Basic routine to handle active XZ read operations
16    C     o  ACTIVE_READ_YZ_RL  : Basic routine to handle active YZ read operations
17    C     o  ACTIVE_READ_YZ_RS  : Basic routine to handle active YZ read operations
18    
19    C     o  ACTIVE_WRITE_XZ_RL : Basic routine to handle active XZ write operations
20    C     o  ACTIVE_WRITE_XZ_RS : Basic routine to handle active XZ write operations
21    C     o  ACTIVE_WRITE_YZ_RL : Basic routine to handle active YZ write operations
22    C     o  ACTIVE_WRITE_YZ_RS : Basic routine to handle active YZ write operations
23    
24    C     ==================================================================
25    
26    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
27    CBOP
28    C     !ROUTINE: ACTIVE_READ_XZ_RL
29    C     !INTERFACE:
30          SUBROUTINE ACTIVE_READ_XZ_RL(
31         I                          activeVar_file,
32         O                          active_var,
33         I                          globalFile,
34         I                          useCurrentDir,
35         I                          lAdInit,
36         I                          iRec,
37         I                          myNr,
38         I                          theSimulationMode,
39         I                          myOptimIter,
40         I                          myThid )
41    C     !DESCRIPTION: \bv
42    C     ==================================================================
43    C     SUBROUTINE ACTIVE_READ_XZ_RL
44    C     ==================================================================
45    C     o Read an active XZ _RL variable from file.
46    C     The variable *globalfile* can be used as a switch, which allows
47    C     to read from a global file. The adjoint files are, however, always
48    C     treated as tiled files.
49    C     started: heimbach@mit.edu 05-Mar-2001
50    C     ==================================================================
51    C     SUBROUTINE ACTIVE_READ_XZ_RL
52    C     ==================================================================
53    C     \ev
54    
55  c     ==================================================================  C     !USES:
56  c        IMPLICIT NONE
 c     active_file_control.F: Routines to handle the i/o of active vari-  
 c                            ables for the adjoint calculations. All  
 c                            files are direct access files.  
 c  
 c     Routines:  
 c  
 c     o  active_read_xz_rl      - Basic routine to handle active read  
 c                                 operations.  
 c     o  active_write_xz_rl     - Basic routine to handle active write  
 c                                 operations.  
 c     o  active_read_yz_rl      - Basic routine to handle active read  
 c                                 operations.  
 c     o  active_write_yz_rl     - Basic routine to handle active write  
 c                                 operations.  
 c  
 c     ==================================================================  
   
   
       subroutine active_read_xz_rl(  
      I                           active_var_file,  
      O                           active_var,  
      I                           globalfile,  
      I                           lAdInit,  
      I                           irec,  
      I                           mynr,  
      I                           theSimulationMode,  
      I                           myOptimIter,  
      I                           mythid  
      &                         )  
   
 c     ==================================================================  
 c     SUBROUTINE active_read_xz_rl  
 c     ==================================================================  
 c  
 c     o Read an active variable from file.  
 c  
 c     The variable *globalfile* can be used as a switch, which allows  
 c     to read from a global file. The adjoint files are, however, always  
 c     treated as tiled files.  
 c  
 c     started: heimbach@mit.edu 05-Mar-2001  
 c  
 c     ==================================================================  
 c     SUBROUTINE active_read_xz_rl  
 c     ==================================================================  
   
       implicit none  
   
 c     == global variables ==  
57    
58    C     == global variables ==
59  #include "EEPARAMS.h"  #include "EEPARAMS.h"
60  #include "SIZE.h"  #include "SIZE.h"
61  #include "PARAMS.h"  #include "PARAMS.h"
62    #include "ctrl.h"
63    
64  c     == routine arguments ==  C     !INPUT/OUTPUT PARAMETERS:
65    C     activeVar_file :: filename
66        character*(*) active_var_file  C     active_var     :: array
67    C     globalFile     ::
68        logical  globalfile  C     useCurrentDir  :: always read from the current directory
69        logical  lAdInit  C                        (even if "mdsioLocalDir" is set)
70        integer  irec  C     lAdInit        :: initialisation of corresponding adjoint variable
71        integer  mynr  C                        and write to active file
72        integer  theSimulationMode  C     iRec           :: record number
73        integer  myOptimIter  C     myNr           :: vertical array dimension
74        integer  mythid  C     theSimulationMode :: forward mode or reverse mode simulation
75        _RL     active_var(1-olx:snx+olx,mynr,nsx,nsy)  C     myOptimIter    :: number of optimization iteration (default: 0)
76    C     myThid         :: thread number for this instance
77  c     == local variables ==        CHARACTER*(*) activeVar_file
78          INTEGER  myNr
79        character*(2)  adpref        _RL      active_var(1-OLx:sNx+OLx,myNr,nSx,nSy)
80        character*(80) adfname        LOGICAL  globalFile
81          LOGICAL  useCurrentDir
82        integer bi,bj        LOGICAL  lAdInit
83        integer i,j,k        INTEGER  iRec
84        integer oldprec        INTEGER  theSimulationMode
85        integer prec        INTEGER  myOptimIter
86        integer il        INTEGER  myThid
87        integer ilnblnk  
88    C     !FUNCTIONS:
89        logical writeglobalfile        INTEGER  ILNBLNK
90          EXTERNAL ILNBLNK
91        _RL  active_data_t(1-olx:snx+olx,nsx,nsy)  
92    C     !LOCAL VARIABLES:
93          CHARACTER*(2)  adpref
94          CHARACTER*(80) adfname
95          INTEGER bi,bj
96          INTEGER i,k
97          INTEGER prec
98          INTEGER il
99          LOGICAL w_globFile
100          _RS  dummyRS(1)
101          _RL  active_data_t(1-OLx:sNx+OLx,myNr,nSx,nSy)
102    CEOP
103    
104  c     == functions ==  C     force 64-bit io
105          prec = ctrlprec
106    
       external ilnblnk  
   
 c     == end of interface ==  
   
 c     force 64-bit io  
       oldPrec        = readBinaryPrec  
       readBinaryPrec = precFloat64  
       prec           = precFloat64  
   
       write(adfname(1:80),'(80a)') ' '  
107        adpref = 'ad'        adpref = 'ad'
108        il = ilnblnk( active_var_file )        il = ILNBLNK( activeVar_file )
109          WRITE(adfname(1:80),'(80a)') ' '
110        write(adfname(1:2),'(a)') adpref        WRITE(adfname(1:il+2),'(2A)') adpref, activeVar_file(1:il)
111        write(adfname(3:il+2),'(a)') active_var_file(1:il)  
112    C     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<
113  c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<        IF (theSimulationMode .EQ. FORWARD_SIMULATION) THEN
114  c     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<  
115  c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  C     Read the active variable from file.
116            CALL MDS_READ_SEC_XZ(
117        if (theSimulationMode .eq. FORWARD_SIMULATION) then       I                activeVar_file, prec, useCurrentDir,
118         I                'RL', myNr,
119          _BEGIN_MASTER( mythid )       O                active_var, dummyRS,
120         I                iRec, myThid )
121  c       Read the active variable from file.  
122            IF ( lAdInit ) THEN
123          call mdsreadfieldxz(  C     Initialise the corresponding adjoint variable on the
124       &                     active_var_file,  C     adjoint variable file. These files are tiled.
125       &                     prec,  
126       &                     'RL',            DO bj = myByLo(myThid), myByHi(myThid)
127       &                     mynr,                   DO bi = myBxLo(myThid), myBxHi(myThid)
128       &                     active_var,              DO k = 1, myNr
129       &                     irec,                DO i=1,sNx
130       &                     mythid )                  active_data_t(i,k,bi,bj) = 0. _d 0
131                  ENDDO
132          if (lAdInit) then              ENDDO
133  c         Initialise the corresponding adjoint variable on the             ENDDO
134  c         adjoint variable's file. These files are tiled.            ENDDO
135    
136            writeglobalfile = .false.            CALL MDS_WRITE_SEC_XZ(
137            do bj = 1,nsy       I                adfname, prec, globalFile, useCurrentDir,
138               do bi = 1,nsx       I                'RL', myNr,
139                  do i = 1,snx       I                active_data_t, dummyRS,
140                     active_data_t(i,bi,bj)= 0. _d 0       I                iRec, myOptimIter, myThid )
141                  enddo  
142               enddo          ENDIF
143            enddo  
144          ENDIF
145            do k = 1,mynr  
146               call mdswritefieldxz(  C     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<
147       &                           adfname,        IF (theSimulationMode .EQ. REVERSE_SIMULATION) THEN
148       &                           prec,  
149       &                           globalfile,          CALL MDS_READ_SEC_XZ(
150       &                           'RL',       I                activeVar_file, prec, useCurrentDir,
151       &                           1,       I                'RL', myNr,
152       &                           active_data_t,       O                active_data_t, dummyRS,
153       &                           (irec-1)*mynr+k,       I                iRec, myThid )
154       &                           myOptimIter,  
155       &                           mythid )  C     Add active_var from appropriate location to data.
156            enddo          DO bj = myByLo(myThid), myByHi(myThid)
157          endif           DO bi = myBxLo(myThid), myBxHi(myThid)
158              DO k = 1, myNr
159          _END_MASTER( mythid )              DO i=1,sNx
160                  active_data_t(i,k,bi,bj) = active_data_t(i,k,bi,bj)
161        endif       &                                 + active_var(i,k,bi,bj)
162                ENDDO
163  c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<            ENDDO
164  c     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<           ENDDO
165  c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<          ENDDO
166    
167        if (theSimulationMode .eq. REVERSE_SIMULATION) then  C     Store the result on disk.
168            w_globFile = .FALSE.
169          _BEGIN_MASTER( mythid )          CALL MDS_WRITE_SEC_XZ(
170         I                activeVar_file, prec, w_globFile, useCurrentDir,
171          writeglobalfile = .false.       I                'RL', myNr,
172          do k=1,mynr       I                active_data_t, dummyRS,
173  c             Read data from file layer by layer.       I                iRec, myOptimIter, myThid )
174             call mdsreadfieldxz(  
175       &                        active_var_file,  C     Set active_var to zero.
176       &                        prec,          DO bj = myByLo(myThid), myByHi(myThid)
177       &                        'RL',           DO bi = myBxLo(myThid), myBxHi(myThid)
178       &                        1,            DO k = 1, myNr
179       &                        active_data_t,              DO i=1,sNx
180       &                        (irec-1)*mynr+k,                active_var(i,k,bi,bj) = 0 _d 0
181       &                        mythid )              ENDDO
182              ENDDO
183  c             Add active_var from appropriate location to data.           ENDDO
184             do bj = 1,nsy          ENDDO
185                do bi = 1,nsx  
186                   do i = 1,snx        ENDIF
187                      active_data_t(i,bi,bj) = active_data_t(i,bi,bj) +  
188       &                   active_var(i,k,bi,bj)  C     >>>>>>>>>>>>>>>>>>> TANGENT RUN <<<<<<<<<<<<<<<<<<<
189                   enddo        IF (theSimulationMode .EQ. TANGENT_SIMULATION) THEN
190                enddo  C     Read the active variable from file.
191             enddo          CALL MDS_READ_SEC_XZ(
192         I                activeVar_file, prec, useCurrentDir,
193  c             Store the result on disk.       I                'RL', myNr,
194             call mdswritefieldxz(       O                active_var, dummyRS,
195       &                         active_var_file,       I                iRec, myThid )
196       &                         prec,        ENDIF
197       &                         writeglobalfile,  
198       &                         'RL',        RETURN
199       &                         1,        END
200       &                         active_data_t,  
201       &                         (irec-1)*mynr+k,  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
202       &                         myOptimIter,  CBOP
203       &                         mythid )  C     !ROUTINE: ACTIVE_READ_XZ_RS
204          enddo  C     !INTERFACE:
205          SUBROUTINE ACTIVE_READ_XZ_RS(
206         I                          activeVar_file,
207  c       Set active_var to zero.       O                          active_var,
208          do k=1,mynr       I                          globalFile,
209             do bj = 1,nsy       I                          useCurrentDir,
210                do bi = 1,nsx       I                          lAdInit,
211                   do i = 1,snx       I                          iRec,
212                      active_var(i,k,bi,bj) = 0. _d 0       I                          myNr,
213                   enddo       I                          theSimulationMode,
214                enddo       I                          myOptimIter,
215             enddo       I                          myThid )
216          enddo  
217    C     !DESCRIPTION: \bv
218          _END_MASTER( mythid )  C     ==================================================================
219        endif  C     SUBROUTINE ACTIVE_READ_XZ_RS
220    C     ==================================================================
221  c     Reset default io precision.  C     o Read an active XZ _RS variable from file.
222        readBinaryPrec = oldPrec  C     The variable *globalfile* can be used as a switch, which allows
223    C     to read from a global file. The adjoint files are, however, always
224        _BARRIER  C     treated as tiled files.
225    C     started: heimbach@mit.edu 05-Mar-2001
226        return  C     ==================================================================
227        end  C     SUBROUTINE ACTIVE_READ_XZ_RS
228    C     ==================================================================
229  c     ==================================================================  C     \ev
   
       subroutine active_write_xz_rl(  
      I                            active_var_file,  
      I                            active_var,  
      I                            globalfile,  
      I                            irec,  
      I                            mynr,  
      I                            theSimulationMode,  
      I                            myOptimIter,  
      I                            mythid  
      &                          )  
   
 c     ==================================================================  
 c     SUBROUTINE active_write_xz_rl  
 c     ==================================================================  
 c  
 c     o Write an active variable to a file.  
 c  
 c     started: heimbach@mit.edu 05-Mar-2001  
 c  
 c     ==================================================================  
 c     SUBROUTINE active_write_xz_rl  
 c     ==================================================================  
230    
231        implicit none  C     !USES:
232          IMPLICIT NONE
 c     == global variables ==  
233    
234    C     == global variables ==
235  #include "EEPARAMS.h"  #include "EEPARAMS.h"
236  #include "SIZE.h"  #include "SIZE.h"
237  #include "PARAMS.h"  #include "PARAMS.h"
238    #include "ctrl.h"
239    
240  c     == routine arguments ==  C     !INPUT/OUTPUT PARAMETERS:
241    C     activeVar_file :: filename
242        character*(*) active_var_file  C     active_var     :: array
243    C     globalFile     ::
244    C     useCurrentDir  :: always read from the current directory
245    C                        (even if "mdsioLocalDir" is set)
246    C     lAdInit        :: initialisation of corresponding adjoint variable
247    C                        and write to active file
248    C     iRec           :: record number
249    C     myNr           :: vertical array dimension
250    C     theSimulationMode :: forward mode or reverse mode simulation
251    C     myOptimIter    :: number of optimization iteration (default: 0)
252    C     myThid         :: thread number for this instance
253          CHARACTER*(*) activeVar_file
254          INTEGER  myNr
255          _RS      active_var(1-OLx:sNx+OLx,myNr,nSx,nSy)
256          LOGICAL  globalFile
257          LOGICAL  useCurrentDir
258          LOGICAL  lAdInit
259          INTEGER  iRec
260          INTEGER  theSimulationMode
261          INTEGER  myOptimIter
262          INTEGER  myThid
263    
264    C     !FUNCTIONS:
265          INTEGER  ILNBLNK
266          EXTERNAL ILNBLNK
267    
268    C     !LOCAL VARIABLES:
269          CHARACTER*(2)  adpref
270          CHARACTER*(80) adfname
271          INTEGER bi,bj
272          INTEGER i,k
273          INTEGER prec
274          INTEGER il
275          LOGICAL w_globFile
276          _RS  active_data_t(1-OLx:sNx+OLx,myNr,nSx,nSy)
277          _RL  dummyRL(1)
278    CEOP
279    
280        integer  mynr  C     force 64-bit io
281        logical  globalfile        prec = ctrlprec
       integer  irec  
       integer  theSimulationMode  
       integer  myOptimIter  
       integer  mythid  
       _RL     active_var(1-olx:snx+olx,mynr,nsx,nsy)  
   
 c     == local variables ==  
   
       integer  i,j,k  
       integer  bi,bj  
       _RL  active_data_t(1-olx:snx+olx,nsx,nsy)  
       integer  oldprec  
       integer  prec  
   
 c     == end of interface ==  
   
 c     force 64-bit io  
       oldPrec        = readBinaryPrec  
       readBinaryPrec = precFloat64  
       prec           = precFloat64  
   
 c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  
 c     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<  
 c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  
   
       if (theSimulationMode .eq. FORWARD_SIMULATION) then  
   
         _BEGIN_MASTER( mythid )  
   
           call mdswritefieldxz(  
      &                        active_var_file,  
      &                        prec,  
      &                        globalfile,  
      &                        'RL',  
      &                        mynr,  
      &                        active_var,  
      &                        irec,  
      &                        myOptimIter,  
      &                        mythid )  
   
         _END_MASTER( mythid )  
   
       endif  
   
 c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  
 c     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<  
 c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  
   
       if (theSimulationMode .eq. REVERSE_SIMULATION) then  
   
         _BEGIN_MASTER( mythid )  
   
             do k=1,mynr  
 c             Read data from file layer by layer.  
               call mdsreadfieldxz(  
      &                           active_var_file,  
      &                           prec,  
      &                           'RL',  
      &                            1,  
      &                            active_data_t,  
      &                            (irec-1)*mynr+k,  
      &                            mythid )  
   
 c             Add active_var from appropriate location to data.  
               do bj = 1,nsy  
                  do bi = 1,nsx  
                     do i = 1,snx  
                        active_var(i,k,bi,bj) =  
      &                      active_var(i,k,bi,bj) +  
      &                      active_data_t(i,bi,bj)  
                        active_data_t(i,bi,bj) = 0. _d 0  
                     enddo  
                  enddo  
               enddo  
               call mdswritefieldxz(  
      &                            active_var_file,  
      &                            prec,  
      &                            globalfile,  
      &                            'RL',  
      &                            1,  
      &                            active_data_t,  
      &                            (irec-1)*mynr+k,  
      &                            myOptimIter,  
      &                            mythid )  
         enddo  
   
         _END_MASTER( mythid )  
   
       endif  
   
 c     Reset default io precision.  
       readBinaryPrec = oldPrec  
   
       _BARRIER  
   
       return  
       end  
   
 c     ==================================================================  
   
       subroutine active_read_yz_rl(  
      I                           active_var_file,  
      O                           active_var,  
      I                           globalfile,  
      I                           lAdInit,  
      I                           irec,  
      I                           mynr,  
      I                           theSimulationMode,  
      I                           myOptimIter,  
      I                           mythid  
      &                         )  
   
 c     ==================================================================  
 c     SUBROUTINE active_read_yz_rl  
 c     ==================================================================  
 c  
 c     o Read an active variable from file.  
 c  
 c     The variable *globalfile* can be used as a switch, which allows  
 c     to read from a global file. The adjoint files are, however, always  
 c     treated as tiled files.  
 c  
 c     started: heimbach@mit.edu 05-Mar-2001  
 c  
 c     ==================================================================  
 c     SUBROUTINE active_read_yz_rl  
 c     ==================================================================  
282    
283        implicit none        adpref = 'ad'
284          il = ILNBLNK( activeVar_file )
285          WRITE(adfname(1:80),'(80a)') ' '
286          WRITE(adfname(1:il+2),'(2A)') adpref, activeVar_file(1:il)
287    
288    C     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<
289          IF (theSimulationMode .EQ. FORWARD_SIMULATION) THEN
290    
291    C     Read the active variable from file.
292            CALL MDS_READ_SEC_XZ(
293         I                activeVar_file, prec, useCurrentDir,
294         I                'RS', myNr,
295         O                dummyRL, active_var,
296         I                iRec, myThid )
297    
298            IF ( lAdInit ) THEN
299    C     Initialise the corresponding adjoint variable on the
300    C     adjoint variable file. These files are tiled.
301    
302              DO bj = myByLo(myThid), myByHi(myThid)
303               DO bi = myBxLo(myThid), myBxHi(myThid)
304                DO k = 1, myNr
305                  DO i=1,sNx
306                    active_data_t(i,k,bi,bj) = 0. _d 0
307                  ENDDO
308                ENDDO
309               ENDDO
310              ENDDO
311    
312              CALL MDS_WRITE_SEC_XZ(
313         I                adfname, prec, globalFile, useCurrentDir,
314         I                'RS', myNr,
315         I                dummyRL, active_data_t,
316         I                iRec, myOptimIter, myThid )
317    
318            ENDIF
319    
320          ENDIF
321    
322    C     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<
323          IF (theSimulationMode .EQ. REVERSE_SIMULATION) THEN
324    
325            CALL MDS_READ_SEC_XZ(
326         I                activeVar_file, prec, useCurrentDir,
327         I                'RS', myNr,
328         O                dummyRL, active_data_t,
329         I                iRec, myThid )
330    
331    C     Add active_var from appropriate location to data.
332            DO bj = myByLo(myThid), myByHi(myThid)
333             DO bi = myBxLo(myThid), myBxHi(myThid)
334              DO k = 1, myNr
335                DO i=1,sNx
336                  active_data_t(i,k,bi,bj) = active_data_t(i,k,bi,bj)
337         &                                 + active_var(i,k,bi,bj)
338                ENDDO
339              ENDDO
340             ENDDO
341            ENDDO
342    
343    C     Store the result on disk.
344            w_globFile = .FALSE.
345            CALL MDS_WRITE_SEC_XZ(
346         I                activeVar_file, prec, w_globFile, useCurrentDir,
347         I                'RS', myNr,
348         I                dummyRL, active_data_t,
349         I                iRec, myOptimIter, myThid )
350    
351    C     Set active_var to zero.
352            DO bj = myByLo(myThid), myByHi(myThid)
353             DO bi = myBxLo(myThid), myBxHi(myThid)
354              DO k = 1, myNr
355                DO i=1,sNx
356                  active_var(i,k,bi,bj) = 0 _d 0
357                ENDDO
358              ENDDO
359             ENDDO
360            ENDDO
361    
362          ENDIF
363    
364    C     >>>>>>>>>>>>>>>>>>> TANGENT RUN <<<<<<<<<<<<<<<<<<<
365          IF (theSimulationMode .EQ. TANGENT_SIMULATION) THEN
366    C     Read the active variable from file.
367            CALL MDS_READ_SEC_XZ(
368         I                activeVar_file, prec, useCurrentDir,
369         I                'RS', myNr,
370         O                dummyRL, active_var,
371         I                iRec, myThid )
372          ENDIF
373    
374          RETURN
375          END
376    
377    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
378    CBOP
379    C     !ROUTINE: ACTIVE_READ_YZ_RL
380    C     !INTERFACE:
381          SUBROUTINE ACTIVE_READ_YZ_RL(
382         I                          activeVar_file,
383         O                          active_var,
384         I                          globalFile,
385         I                          useCurrentDir,
386         I                          lAdInit,
387         I                          iRec,
388         I                          myNr,
389         I                          theSimulationMode,
390         I                          myOptimIter,
391         I                          myThid )
392    C     !DESCRIPTION: \bv
393    C     ==================================================================
394    C     SUBROUTINE ACTIVE_READ_YZ_RL
395    C     ==================================================================
396    C     o Read an active YZ _RL variable from file.
397    C     The variable *globalfile* can be used as a switch, which allows
398    C     to read from a global file. The adjoint files are, however, always
399    C     treated as tiled files.
400    C     started: heimbach@mit.edu 05-Mar-2001
401    C     ==================================================================
402    C     SUBROUTINE ACTIVE_READ_YZ_RL
403    C     ==================================================================
404    C     \ev
405    
406  c     == global variables ==  C     !USES:
407          IMPLICIT NONE
408    
409    C     == global variables ==
410  #include "EEPARAMS.h"  #include "EEPARAMS.h"
411  #include "SIZE.h"  #include "SIZE.h"
412  #include "PARAMS.h"  #include "PARAMS.h"
413    #include "ctrl.h"
414    
415  c     == routine arguments ==  C     !INPUT/OUTPUT PARAMETERS:
416    C     activeVar_file :: filename
417        character*(*) active_var_file  C     active_var     :: array
418    C     globalFile     ::
419    C     useCurrentDir  :: always read from the current directory
420    C                        (even if "mdsioLocalDir" is set)
421    C     lAdInit        :: initialisation of corresponding adjoint variable
422    C                        and write to active file
423    C     iRec           :: record number
424    C     myNr           :: vertical array dimension
425    C     theSimulationMode :: forward mode or reverse mode simulation
426    C     myOptimIter    :: number of optimization iteration (default: 0)
427    C     myThid         :: thread number for this instance
428          CHARACTER*(*) activeVar_file
429          INTEGER  myNr
430          _RL      active_var(1-OLy:sNy+OLy,myNr,nSx,nSy)
431          LOGICAL  globalFile
432          LOGICAL  useCurrentDir
433          LOGICAL  lAdInit
434          INTEGER  iRec
435          INTEGER  theSimulationMode
436          INTEGER  myOptimIter
437          INTEGER  myThid
438    
439    C     !FUNCTIONS:
440          INTEGER  ILNBLNK
441          EXTERNAL ILNBLNK
442    
443    C     !LOCAL VARIABLES:
444          CHARACTER*(2)  adpref
445          CHARACTER*(80) adfname
446          INTEGER bi,bj
447          INTEGER j,k
448          INTEGER prec
449          INTEGER il
450          LOGICAL w_globFile
451          _RS  dummyRS(1)
452          _RL  active_data_t(1-OLy:sNy+OLy,myNr,nSx,nSy)
453    CEOP
454    
455        logical  globalfile  C     force 64-bit io
456        logical  lAdInit        prec = ctrlprec
       integer  irec  
       integer  mynr  
       integer  theSimulationMode  
       integer  myOptimIter  
       integer  mythid  
       _RL     active_var(1-oly:sny+oly,mynr,nsx,nsy)  
457    
458  c     == local variables ==        adpref = 'ad'
459          il = ILNBLNK( activeVar_file )
460        character*(2)  adpref        WRITE(adfname(1:80),'(80a)') ' '
461        character*(80) adfname        WRITE(adfname(1:il+2),'(2A)') adpref, activeVar_file(1:il)
462    
463        integer bi,bj  C     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<
464        integer i,j,k        IF (theSimulationMode .EQ. FORWARD_SIMULATION) THEN
465        integer oldprec  
466        integer prec  C     Read the active variable from file.
467        integer il          CALL MDS_READ_SEC_YZ(
468        integer ilnblnk       I                activeVar_file, prec, useCurrentDir,
469         I                'RL', myNr,
470        logical writeglobalfile       O                active_var, dummyRS,
471         I                iRec, myThid )
472        _RL  active_data_t(1-oly:sny+oly,nsx,nsy)  
473            IF ( lAdInit ) THEN
474    C     Initialise the corresponding adjoint variable on the
475    C     adjoint variable file. These files are tiled.
476    
477              DO bj = myByLo(myThid), myByHi(myThid)
478               DO bi = myBxLo(myThid), myBxHi(myThid)
479                DO k = 1, myNr
480                 DO j=1,sNy
481                    active_data_t(j,k,bi,bj) = 0. _d 0
482                 ENDDO
483                ENDDO
484               ENDDO
485              ENDDO
486    
487              CALL MDS_WRITE_SEC_YZ(
488         I                adfname, prec, globalFile, useCurrentDir,
489         I                'RL', myNr,
490         I                active_data_t, dummyRS,
491         I                iRec, myOptimIter, myThid )
492    
493            ENDIF
494    
495          ENDIF
496    
497    C     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<
498          IF (theSimulationMode .EQ. REVERSE_SIMULATION) THEN
499    
500            CALL MDS_READ_SEC_YZ(
501         I                activeVar_file, prec, useCurrentDir,
502         I                'RL', myNr,
503         O                active_data_t, dummyRS,
504         I                iRec, myThid )
505    
506    C     Add active_var from appropriate location to data.
507            DO bj = myByLo(myThid), myByHi(myThid)
508             DO bi = myBxLo(myThid), myBxHi(myThid)
509              DO k = 1, myNr
510               DO j=1,sNy
511                  active_data_t(j,k,bi,bj) = active_data_t(j,k,bi,bj)
512         &                                 + active_var(j,k,bi,bj)
513               ENDDO
514              ENDDO
515             ENDDO
516            ENDDO
517    
518    C     Store the result on disk.
519            w_globFile = .FALSE.
520            CALL MDS_WRITE_SEC_YZ(
521         I                activeVar_file, prec, w_globFile, useCurrentDir,
522         I                'RL', myNr,
523         I                active_data_t, dummyRS,
524         I                iRec, myOptimIter, myThid )
525    
526    C     Set active_var to zero.
527            DO bj = myByLo(myThid), myByHi(myThid)
528             DO bi = myBxLo(myThid), myBxHi(myThid)
529              DO k = 1, myNr
530               DO j=1,sNy
531                  active_var(j,k,bi,bj) = 0 _d 0
532               ENDDO
533              ENDDO
534             ENDDO
535            ENDDO
536    
537          ENDIF
538    
539    C     >>>>>>>>>>>>>>>>>>> TANGENT RUN <<<<<<<<<<<<<<<<<<<
540          IF (theSimulationMode .EQ. TANGENT_SIMULATION) THEN
541    C     Read the active variable from file.
542            CALL MDS_READ_SEC_YZ(
543         I                activeVar_file, prec, useCurrentDir,
544         I                'RL', myNr,
545         O                active_var, dummyRS,
546         I                iRec, myThid )
547          ENDIF
548    
549          RETURN
550          END
551    
552    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
553    CBOP
554    C     !ROUTINE: ACTIVE_READ_YZ_RS
555    C     !INTERFACE:
556          SUBROUTINE ACTIVE_READ_YZ_RS(
557         I                          activeVar_file,
558         O                          active_var,
559         I                          globalFile,
560         I                          useCurrentDir,
561         I                          lAdInit,
562         I                          iRec,
563         I                          myNr,
564         I                          theSimulationMode,
565         I                          myOptimIter,
566         I                          myThid )
567    
568    C     !DESCRIPTION: \bv
569    C     ==================================================================
570    C     SUBROUTINE ACTIVE_READ_YZ_RS
571    C     ==================================================================
572    C     o Read an active YZ _RS variable from file.
573    C     The variable *globalfile* can be used as a switch, which allows
574    C     to read from a global file. The adjoint files are, however, always
575    C     treated as tiled files.
576    C     started: heimbach@mit.edu 05-Mar-2001
577    C     ==================================================================
578    C     SUBROUTINE ACTIVE_READ_YZ_RS
579    C     ==================================================================
580    C     \ev
581    
582  c     == functions ==  C     !USES:
583          IMPLICIT NONE
584    
585        external ilnblnk  C     == global variables ==
586    #include "EEPARAMS.h"
587    #include "SIZE.h"
588    #include "PARAMS.h"
589    #include "ctrl.h"
590    
591  c     == end of interface ==  C     !INPUT/OUTPUT PARAMETERS:
592    C     activeVar_file :: filename
593    C     active_var     :: array
594    C     globalFile     ::
595    C     useCurrentDir  :: always read from the current directory
596    C                        (even if "mdsioLocalDir" is set)
597    C     lAdInit        :: initialisation of corresponding adjoint variable
598    C                        and write to active file
599    C     iRec           :: record number
600    C     myNr           :: vertical array dimension
601    C     theSimulationMode :: forward mode or reverse mode simulation
602    C     myOptimIter    :: number of optimization iteration (default: 0)
603    C     myThid         :: thread number for this instance
604          CHARACTER*(*) activeVar_file
605          INTEGER  myNr
606          _RS      active_var(1-OLy:sNy+OLy,myNr,nSx,nSy)
607          LOGICAL  globalFile
608          LOGICAL  useCurrentDir
609          LOGICAL  lAdInit
610          INTEGER  iRec
611          INTEGER  theSimulationMode
612          INTEGER  myOptimIter
613          INTEGER  myThid
614    
615    C     !FUNCTIONS:
616          INTEGER  ILNBLNK
617          EXTERNAL ILNBLNK
618    
619    C     !LOCAL VARIABLES:
620          CHARACTER*(2)  adpref
621          CHARACTER*(80) adfname
622          INTEGER bi,bj
623          INTEGER j,k
624          INTEGER prec
625          INTEGER il
626          LOGICAL w_globFile
627          _RS  active_data_t(1-OLy:sNy+OLy,myNr,nSx,nSy)
628          _RL  dummyRL(1)
629    CEOP
630    
631  c     force 64-bit io  C     force 64-bit io
632        oldPrec        = readBinaryPrec        prec = ctrlprec
       readBinaryPrec = precFloat64  
       prec           = precFloat64  
633    
       write(adfname(1:80),'(80a)') ' '  
634        adpref = 'ad'        adpref = 'ad'
635        il = ilnblnk( active_var_file )        il = ILNBLNK( activeVar_file )
636          WRITE(adfname(1:80),'(80a)') ' '
637          WRITE(adfname(1:il+2),'(2A)') adpref, activeVar_file(1:il)
638    
639    C     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<
640          IF (theSimulationMode .EQ. FORWARD_SIMULATION) THEN
641    
642    C     Read the active variable from file.
643            CALL MDS_READ_SEC_YZ(
644         I                activeVar_file, prec, useCurrentDir,
645         I                'RS', myNr,
646         O                dummyRL, active_var,
647         I                iRec, myThid )
648    
649            IF ( lAdInit ) THEN
650    C     Initialise the corresponding adjoint variable on the
651    C     adjoint variable file. These files are tiled.
652    
653              DO bj = myByLo(myThid), myByHi(myThid)
654               DO bi = myBxLo(myThid), myBxHi(myThid)
655                DO k = 1, myNr
656                 DO j=1,sNy
657                    active_data_t(j,k,bi,bj) = 0. _d 0
658                 ENDDO
659                ENDDO
660               ENDDO
661              ENDDO
662    
663              CALL MDS_WRITE_SEC_YZ(
664         I                adfname, prec, globalFile, useCurrentDir,
665         I                'RS', myNr,
666         I                dummyRL, active_data_t,
667         I                iRec, myOptimIter, myThid )
668    
669            ENDIF
670    
671          ENDIF
672    
673    C     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<
674          IF (theSimulationMode .EQ. REVERSE_SIMULATION) THEN
675    
676            CALL MDS_READ_SEC_YZ(
677         I                activeVar_file, prec, useCurrentDir,
678         I                'RS', myNr,
679         O                dummyRL, active_data_t,
680         I                iRec, myThid )
681    
682    C     Add active_var from appropriate location to data.
683            DO bj = myByLo(myThid), myByHi(myThid)
684             DO bi = myBxLo(myThid), myBxHi(myThid)
685              DO k = 1, myNr
686               DO j=1,sNy
687                  active_data_t(j,k,bi,bj) = active_data_t(j,k,bi,bj)
688         &                                 + active_var(j,k,bi,bj)
689               ENDDO
690              ENDDO
691             ENDDO
692            ENDDO
693    
694    C     Store the result on disk.
695            w_globFile = .FALSE.
696            CALL MDS_WRITE_SEC_YZ(
697         I                activeVar_file, prec, w_globFile, useCurrentDir,
698         I                'RS', myNr,
699         I                dummyRL, active_data_t,
700         I                iRec, myOptimIter, myThid )
701    
702    C     Set active_var to zero.
703            DO bj = myByLo(myThid), myByHi(myThid)
704             DO bi = myBxLo(myThid), myBxHi(myThid)
705              DO k = 1, myNr
706               DO j=1,sNy
707                  active_var(j,k,bi,bj) = 0 _d 0
708               ENDDO
709              ENDDO
710             ENDDO
711            ENDDO
712    
713          ENDIF
714    
715    C     >>>>>>>>>>>>>>>>>>> TANGENT RUN <<<<<<<<<<<<<<<<<<<
716          IF (theSimulationMode .EQ. TANGENT_SIMULATION) THEN
717    C     Read the active variable from file.
718            CALL MDS_READ_SEC_YZ(
719         I                activeVar_file, prec, useCurrentDir,
720         I                'RS', myNr,
721         O                dummyRL, active_var,
722         I                iRec, myThid )
723          ENDIF
724    
725          RETURN
726          END
727    
728    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
729    CBOP
730    C     !ROUTINE: ACTIVE_WRITE_XZ_RL
731    C     !INTERFACE:
732          SUBROUTINE ACTIVE_WRITE_XZ_RL(
733         I                          activeVar_file,
734         I                          active_var,
735         I                          globalFile,
736         I                          useCurrentDir,
737         I                          iRec,
738         I                          myNr,
739         I                          theSimulationMode,
740         I                          myOptimIter,
741         I                          myThid )
742    
743    C     !DESCRIPTION: \bv
744    C     ==================================================================
745    C     SUBROUTINE ACTIVE_WRITE_XZ_RL
746    C     ==================================================================
747    C     o Write an active XZ _RL variable to a file.
748    C     started: heimbach@mit.edu 05-Mar-2001
749    C     ==================================================================
750    C     SUBROUTINE ACTIVE_WRITE_XZ_RL
751    C     ==================================================================
752    C     \ev
753    
754        write(adfname(1:2),'(a)') adpref  C     !USES:
755        write(adfname(3:il+2),'(a)') active_var_file(1:il)        IMPLICIT NONE
756    
757  c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  C     == global variables ==
758  c     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<  #include "EEPARAMS.h"
759  c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  #include "SIZE.h"
760    #include "PARAMS.h"
761        if (theSimulationMode .eq. FORWARD_SIMULATION) then  #include "ctrl.h"
   
         _BEGIN_MASTER( mythid )  
   
 c       Read the active variable from file.  
   
         call mdsreadfieldyz(  
      &                     active_var_file,  
      &                     prec,  
      &                     'RL',  
      &                     mynr,        
      &                     active_var,  
      &                     irec,  
      &                     mythid )  
   
         if (lAdInit) then  
 c         Initialise the corresponding adjoint variable on the  
 c         adjoint variable's file. These files are tiled.  
   
           writeglobalfile = .false.  
           do bj = 1,nsy  
              do bi = 1,nsx  
                 do j = 1,sny  
                    active_data_t(j,bi,bj)= 0. _d 0  
                 enddo  
              enddo  
           enddo  
   
           do k = 1,mynr  
              call mdswritefieldyz(  
      &                           adfname,  
      &                           prec,  
      &                           globalfile,  
      &                           'RL',  
      &                           1,  
      &                           active_data_t,  
      &                           (irec-1)*mynr+k,  
      &                           myOptimIter,  
      &                           mythid )  
           enddo  
         endif  
   
         _END_MASTER( mythid )  
   
       endif  
   
 c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  
 c     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<  
 c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  
   
       if (theSimulationMode .eq. REVERSE_SIMULATION) then  
   
         _BEGIN_MASTER( mythid )  
   
         writeglobalfile = .false.  
         do k=1,mynr  
 c             Read data from file layer by layer.  
            call mdsreadfieldyz(  
      &                        active_var_file,  
      &                        prec,  
      &                        'RL',  
      &                        1,  
      &                        active_data_t,  
      &                        (irec-1)*mynr+k,  
      &                        mythid )  
   
 c             Add active_var from appropriate location to data.  
            do bj = 1,nsy  
               do bi = 1,nsx  
                  do j = 1,sny  
                     active_data_t(j,bi,bj) = active_data_t(j,bi,bj) +  
      &                   active_var(j,k,bi,bj)  
                  enddo  
               enddo  
            enddo  
   
 c             Store the result on disk.  
            call mdswritefieldyz(  
      &                         active_var_file,  
      &                         prec,  
      &                         writeglobalfile,  
      &                         'RL',  
      &                         1,  
      &                         active_data_t,  
      &                         (irec-1)*mynr+k,  
      &                         myOptimIter,  
      &                         mythid )  
         enddo  
   
   
 c       Set active_var to zero.  
         do k=1,mynr  
            do bj = 1,nsy  
               do bi = 1,nsx  
                  do j = 1,sny  
                     active_var(j,k,bi,bj) = 0. _d 0  
                  enddo  
               enddo  
            enddo  
         enddo  
   
         _END_MASTER( mythid )  
       endif  
   
 c     Reset default io precision.  
       readBinaryPrec = oldPrec  
   
       _BARRIER  
   
       return  
       end  
   
 c     ==================================================================  
   
       subroutine active_write_yz_rl(  
      I                            active_var_file,  
      I                            active_var,  
      I                            globalfile,  
      I                            irec,  
      I                            mynr,  
      I                            theSimulationMode,  
      I                            myOptimIter,  
      I                            mythid  
      &                          )  
   
 c     ==================================================================  
 c     SUBROUTINE active_write_yz_rl  
 c     ==================================================================  
 c  
 c     o Write an active variable to a file.  
 c  
 c     started: heimbach@mit.edu 05-Mar-2001  
 c  
 c     ==================================================================  
 c     SUBROUTINE active_write_yz_rl  
 c     ==================================================================  
762    
763        implicit none  C     !INPUT/OUTPUT PARAMETERS:
764    C     activeVar_file :: filename
765    C     active_var     :: array
766    C     globalFile     ::
767    C     useCurrentDir  :: always write to the current directory
768    C                        (even if "mdsioLocalDir" is set)
769    C     iRec           :: record number
770    C     myNr           :: vertical array dimension
771    C     theSimulationMode :: forward mode or reverse mode simulation
772    C     myOptimIter    :: number of optimization iteration (default: 0)
773    C     myThid         :: thread number for this instance
774          CHARACTER*(*) activeVar_file
775          INTEGER  myNr
776          _RL      active_var(1-OLx:sNx+OLx,myNr,nSx,nSy)
777          LOGICAL  globalFile
778          LOGICAL  useCurrentDir
779          INTEGER  iRec
780          INTEGER  theSimulationMode
781          INTEGER  myOptimIter
782          INTEGER  myThid
783    
784    C     !LOCAL VARIABLES:
785          INTEGER  i,k
786          INTEGER  bi,bj
787          INTEGER  prec
788          _RS  dummyRS(1)
789          _RL  active_data_t(1-OLx:sNx+OLx,myNr,nSx,nSy)
790    CEOP
791    
792    C     force 64-bit io
793          prec = ctrlprec
794    
795    C     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<
796          IF (theSimulationMode .EQ. FORWARD_SIMULATION) THEN
797            CALL MDS_WRITE_SEC_XZ(
798         I                activeVar_file, prec, globalFile, useCurrentDir,
799         I                'RL', myNr,
800         I                active_var, dummyRS,
801         I                iRec, myOptimIter, myThid )
802          ENDIF
803    
804    C     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<
805          IF (theSimulationMode .EQ. REVERSE_SIMULATION) THEN
806    
807            CALL MDS_READ_SEC_XZ(
808         I                activeVar_file, prec, useCurrentDir,
809         I                'RL', myNr,
810         O                active_data_t, dummyRS,
811         I                iRec, myThid )
812    
813    C     Add active_var from appropriate location to data.
814            DO bj = myByLo(myThid), myByHi(myThid)
815             DO bi = myBxLo(myThid), myBxHi(myThid)
816              DO k = 1, myNr
817                DO i=1,sNx
818                  active_var(i,k,bi,bj) = active_var(i,k,bi,bj)
819         &                              + active_data_t(i,k,bi,bj)
820                  active_data_t(i,k,bi,bj) = 0. _d 0
821                ENDDO
822              ENDDO
823             ENDDO
824            ENDDO
825            CALL MDS_WRITE_SEC_XZ(
826         I                activeVar_file, prec, globalFile, useCurrentDir,
827         I                'RL', myNr,
828         I                active_data_t, dummyRS,
829         I                iRec, myOptimIter, myThid )
830    
831          ENDIF
832    
833    C     >>>>>>>>>>>>>>>>>>> TANGENT RUN <<<<<<<<<<<<<<<<<<<
834          IF (theSimulationMode .EQ. TANGENT_SIMULATION) THEN
835            CALL MDS_WRITE_SEC_XZ(
836         I                activeVar_file, prec, globalFile, useCurrentDir,
837         I                'RL', myNr,
838         I                active_var, dummyRS,
839         I                iRec, myOptimIter, myThid )
840          ENDIF
841    
842          RETURN
843          END
844    
845    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
846    CBOP
847    C     !ROUTINE: ACTIVE_WRITE_XZ_RS
848    C     !INTERFACE:
849          SUBROUTINE ACTIVE_WRITE_XZ_RS(
850         I                          activeVar_file,
851         I                          active_var,
852         I                          globalFile,
853         I                          useCurrentDir,
854         I                          iRec,
855         I                          myNr,
856         I                          theSimulationMode,
857         I                          myOptimIter,
858         I                          myThid )
859    
860    C     !DESCRIPTION: \bv
861    C     ==================================================================
862    C     SUBROUTINE ACTIVE_WRITE_XZ_RS
863    C     ==================================================================
864    C     o Write an active XZ _RS variable to a file.
865    C     started: heimbach@mit.edu 05-Mar-2001
866    C     ==================================================================
867    C     SUBROUTINE ACTIVE_WRITE_XZ_RS
868    C     ==================================================================
869    C     \ev
870    
871  c     == global variables ==  C     !USES:
872          IMPLICIT NONE
873    
874    C     == global variables ==
875  #include "EEPARAMS.h"  #include "EEPARAMS.h"
876  #include "SIZE.h"  #include "SIZE.h"
877  #include "PARAMS.h"  #include "PARAMS.h"
878    #include "ctrl.h"
879    
880  c     == routine arguments ==  C     !INPUT/OUTPUT PARAMETERS:
881    C     activeVar_file :: filename
882    C     active_var     :: array
883    C     globalFile     ::
884    C     useCurrentDir  :: always write to the current directory
885    C                        (even if "mdsioLocalDir" is set)
886    C     iRec           :: record number
887    C     myNr           :: vertical array dimension
888    C     theSimulationMode :: forward mode or reverse mode simulation
889    C     myOptimIter    :: number of optimization iteration (default: 0)
890    C     myThid         :: thread number for this instance
891          CHARACTER*(*) activeVar_file
892          INTEGER  myNr
893          _RS      active_var(1-OLx:sNx+OLx,myNr,nSx,nSy)
894          LOGICAL  globalFile
895          LOGICAL  useCurrentDir
896          INTEGER  iRec
897          INTEGER  theSimulationMode
898          INTEGER  myOptimIter
899          INTEGER  myThid
900    
901    C     !LOCAL VARIABLES:
902          INTEGER  i,k
903          INTEGER  bi,bj
904          INTEGER  prec
905          _RS  active_data_t(1-OLx:sNx+OLx,myNr,nSx,nSy)
906          _RL  dummyRL(1)
907    CEOP
908    
909    C     force 64-bit io
910          prec = ctrlprec
911    
912    C     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<
913          IF (theSimulationMode .EQ. FORWARD_SIMULATION) THEN
914            CALL MDS_WRITE_SEC_XZ(
915         I                activeVar_file, prec, globalFile, useCurrentDir,
916         I                'RS', myNr,
917         I                dummyRL, active_var,
918         I                iRec, myOptimIter, myThid )
919          ENDIF
920    
921    C     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<
922          IF (theSimulationMode .EQ. REVERSE_SIMULATION) THEN
923    
924            CALL MDS_READ_SEC_XZ(
925         I                activeVar_file, prec, useCurrentDir,
926         I                'RS', myNr,
927         O                dummyRL, active_data_t,
928         I                iRec, myThid )
929    
930    C     Add active_var from appropriate location to data.
931            DO bj = myByLo(myThid), myByHi(myThid)
932             DO bi = myBxLo(myThid), myBxHi(myThid)
933              DO k = 1, myNr
934                DO i=1,sNx
935                  active_var(i,k,bi,bj) = active_var(i,k,bi,bj)
936         &                              + active_data_t(i,k,bi,bj)
937                  active_data_t(i,k,bi,bj) = 0. _d 0
938                ENDDO
939              ENDDO
940             ENDDO
941            ENDDO
942            CALL MDS_WRITE_SEC_XZ(
943         I                activeVar_file, prec, globalFile, useCurrentDir,
944         I                'RS', myNr,
945         I                dummyRL, active_data_t,
946         I                iRec, myOptimIter, myThid )
947    
948          ENDIF
949    
950    C     >>>>>>>>>>>>>>>>>>> TANGENT RUN <<<<<<<<<<<<<<<<<<<
951          IF (theSimulationMode .EQ. TANGENT_SIMULATION) THEN
952            CALL MDS_WRITE_SEC_XZ(
953         I                activeVar_file, prec, globalFile, useCurrentDir,
954         I                'RS', myNr,
955         I                dummyRL, active_var,
956         I                iRec, myOptimIter, myThid )
957          ENDIF
958    
959          RETURN
960          END
961    
962    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
963    CBOP
964    C     !ROUTINE: ACTIVE_WRITE_YZ_RL
965    C     !INTERFACE:
966          SUBROUTINE ACTIVE_WRITE_YZ_RL(
967         I                          activeVar_file,
968         I                          active_var,
969         I                          globalFile,
970         I                          useCurrentDir,
971         I                          iRec,
972         I                          myNr,
973         I                          theSimulationMode,
974         I                          myOptimIter,
975         I                          myThid )
976    
977    C     !DESCRIPTION: \bv
978    C     ==================================================================
979    C     SUBROUTINE ACTIVE_WRITE_YZ_RL
980    C     ==================================================================
981    C     o Write an active YZ _RL variable to a file.
982    C     started: heimbach@mit.edu 05-Mar-2001
983    C     ==================================================================
984    C     SUBROUTINE ACTIVE_WRITE_YZ_RL
985    C     ==================================================================
986    C     \ev
987    
988        character*(*) active_var_file  C     !USES:
989          IMPLICIT NONE
990    
991        integer  mynr  C     == global variables ==
992        logical  globalfile  #include "EEPARAMS.h"
993        integer  irec  #include "SIZE.h"
994        integer  theSimulationMode  #include "PARAMS.h"
995        integer  myOptimIter  #include "ctrl.h"
       integer  mythid  
       _RL     active_var(1-oly:sny+oly,mynr,nsx,nsy)  
   
 c     == local variables ==  
   
       integer  i,j,k  
       integer  bi,bj  
       _RL  active_data_t(1-oly:sny+oly,nsx,nsy)  
       integer  oldprec  
       integer  prec  
   
 c     == end of interface ==  
   
 c     force 64-bit io  
       oldPrec        = readBinaryPrec  
       readBinaryPrec = precFloat64  
       prec           = precFloat64  
   
 c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  
 c     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<  
 c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  
   
       if (theSimulationMode .eq. FORWARD_SIMULATION) then  
   
         _BEGIN_MASTER( mythid )  
   
           call mdswritefieldyz(  
      &                        active_var_file,  
      &                        prec,  
      &                        globalfile,  
      &                        'RL',  
      &                        mynr,  
      &                        active_var,  
      &                        irec,  
      &                        myOptimIter,  
      &                        mythid )  
   
         _END_MASTER( mythid )  
   
       endif  
   
 c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  
 c     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<  
 c     >>>>>>>>>>>>>>>>>>>             <<<<<<<<<<<<<<<<<<<  
   
       if (theSimulationMode .eq. REVERSE_SIMULATION) then  
   
         _BEGIN_MASTER( mythid )  
   
             do k=1,mynr  
 c             Read data from file layer by layer.  
               call mdsreadfieldyz(  
      &                           active_var_file,  
      &                           prec,  
      &                           'RL',  
      &                            1,  
      &                            active_data_t,  
      &                            (irec-1)*mynr+k,  
      &                            mythid )  
   
 c             Add active_var from appropriate location to data.  
               do bj = 1,nsy  
                  do bi = 1,nsx  
                     do j = 1,sny  
                        active_var(j,k,bi,bj) =  
      &                      active_var(j,k,bi,bj) +  
      &                      active_data_t(j,bi,bj)  
                        active_data_t(j,bi,bj) = 0. _d 0  
                     enddo  
                  enddo  
               enddo  
               call mdswritefieldyz(  
      &                            active_var_file,  
      &                            prec,  
      &                            globalfile,  
      &                            'RL',  
      &                            1,  
      &                            active_data_t,  
      &                            (irec-1)*mynr+k,  
      &                            myOptimIter,  
      &                            mythid )  
         enddo  
   
         _END_MASTER( mythid )  
   
       endif  
996    
997  c     Reset default io precision.  C     !INPUT/OUTPUT PARAMETERS:
998        readBinaryPrec = oldPrec  C     activeVar_file :: filename
999    C     active_var     :: array
1000    C     globalFile     ::
1001    C     useCurrentDir  :: always write to the current directory
1002    C                        (even if "mdsioLocalDir" is set)
1003    C     iRec           :: record number
1004    C     myNr           :: vertical array dimension
1005    C     theSimulationMode :: forward mode or reverse mode simulation
1006    C     myOptimIter    :: number of optimization iteration (default: 0)
1007    C     myThid         :: thread number for this instance
1008          CHARACTER*(*) activeVar_file
1009          INTEGER  myNr
1010          _RL      active_var(1-OLy:sNy+OLy,myNr,nSx,nSy)
1011          LOGICAL  globalFile
1012          LOGICAL  useCurrentDir
1013          INTEGER  iRec
1014          INTEGER  theSimulationMode
1015          INTEGER  myOptimIter
1016          INTEGER  myThid
1017    
1018    C     !LOCAL VARIABLES:
1019          INTEGER  j,k
1020          INTEGER  bi,bj
1021          INTEGER  prec
1022          _RS  dummyRS(1)
1023          _RL  active_data_t(1-OLy:sNy+OLy,myNr,nSx,nSy)
1024    CEOP
1025    
1026    C     force 64-bit io
1027          prec = ctrlprec
1028    
1029    C     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<
1030          IF (theSimulationMode .EQ. FORWARD_SIMULATION) THEN
1031            CALL MDS_WRITE_SEC_YZ(
1032         I                activeVar_file, prec, globalFile, useCurrentDir,
1033         I                'RL', myNr,
1034         I                active_var, dummyRS,
1035         I                iRec, myOptimIter, myThid )
1036          ENDIF
1037    
1038    C     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<
1039          IF (theSimulationMode .EQ. REVERSE_SIMULATION) THEN
1040    
1041            CALL MDS_READ_SEC_YZ(
1042         I                activeVar_file, prec, useCurrentDir,
1043         I                'RL', myNr,
1044         O                active_data_t, dummyRS,
1045         I                iRec, myThid )
1046    
1047    C     Add active_var from appropriate location to data.
1048            DO bj = myByLo(myThid), myByHi(myThid)
1049             DO bi = myBxLo(myThid), myBxHi(myThid)
1050              DO k = 1, myNr
1051               DO j=1,sNy
1052                  active_var(j,k,bi,bj) = active_var(j,k,bi,bj)
1053         &                              + active_data_t(j,k,bi,bj)
1054                  active_data_t(j,k,bi,bj) = 0. _d 0
1055               ENDDO
1056              ENDDO
1057             ENDDO
1058            ENDDO
1059            CALL MDS_WRITE_SEC_YZ(
1060         I                activeVar_file, prec, globalFile, useCurrentDir,
1061         I                'RL', myNr,
1062         I                active_data_t, dummyRS,
1063         I                iRec, myOptimIter, myThid )
1064    
1065          ENDIF
1066    
1067    C     >>>>>>>>>>>>>>>>>>> TANGENT RUN <<<<<<<<<<<<<<<<<<<
1068          IF (theSimulationMode .EQ. TANGENT_SIMULATION) THEN
1069            CALL MDS_WRITE_SEC_YZ(
1070         I                activeVar_file, prec, globalFile, useCurrentDir,
1071         I                'RL', myNr,
1072         I                active_var, dummyRS,
1073         I                iRec, myOptimIter, myThid )
1074          ENDIF
1075    
1076          RETURN
1077          END
1078    
1079    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
1080    CBOP
1081    C     !ROUTINE: ACTIVE_WRITE_YZ_RS
1082    C     !INTERFACE:
1083          SUBROUTINE ACTIVE_WRITE_YZ_RS(
1084         I                          activeVar_file,
1085         I                          active_var,
1086         I                          globalFile,
1087         I                          useCurrentDir,
1088         I                          iRec,
1089         I                          myNr,
1090         I                          theSimulationMode,
1091         I                          myOptimIter,
1092         I                          myThid )
1093    
1094    C     !DESCRIPTION: \bv
1095    C     ==================================================================
1096    C     SUBROUTINE ACTIVE_WRITE_YZ_RS
1097    C     ==================================================================
1098    C     o Write an active YZ _RS variable to a file.
1099    C     started: heimbach@mit.edu 05-Mar-2001
1100    C     ==================================================================
1101    C     SUBROUTINE ACTIVE_WRITE_YZ_RS
1102    C     ==================================================================
1103    C     \ev
1104    
1105        _BARRIER  C     !USES:
1106          IMPLICIT NONE
1107    
1108    C     == global variables ==
1109    #include "EEPARAMS.h"
1110    #include "SIZE.h"
1111    #include "PARAMS.h"
1112    #include "ctrl.h"
1113    
1114        return  C     !INPUT/OUTPUT PARAMETERS:
1115        end  C     activeVar_file :: filename
1116    C     active_var     :: array
1117    C     globalFile     ::
1118    C     useCurrentDir  :: always write to the current directory
1119    C                        (even if "mdsioLocalDir" is set)
1120    C     iRec           :: record number
1121    C     myNr           :: vertical array dimension
1122    C     theSimulationMode :: forward mode or reverse mode simulation
1123    C     myOptimIter    :: number of optimization iteration (default: 0)
1124    C     myThid         :: thread number for this instance
1125          CHARACTER*(*) activeVar_file
1126          INTEGER  myNr
1127          _RS      active_var(1-OLy:sNy+OLy,myNr,nSx,nSy)
1128          LOGICAL  globalFile
1129          LOGICAL  useCurrentDir
1130          INTEGER  iRec
1131          INTEGER  theSimulationMode
1132          INTEGER  myOptimIter
1133          INTEGER  myThid
1134    
1135    C     !LOCAL VARIABLES:
1136          INTEGER  j,k
1137          INTEGER  bi,bj
1138          INTEGER  prec
1139          _RS  active_data_t(1-OLy:sNy+OLy,myNr,nSx,nSy)
1140          _RL  dummyRL(1)
1141    CEOP
1142    
1143    C     force 64-bit io
1144          prec = ctrlprec
1145    
1146    C     >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<
1147          IF (theSimulationMode .EQ. FORWARD_SIMULATION) THEN
1148            CALL MDS_WRITE_SEC_YZ(
1149         I                activeVar_file, prec, globalFile, useCurrentDir,
1150         I                'RS', myNr,
1151         I                dummyRL, active_var,
1152         I                iRec, myOptimIter, myThid )
1153          ENDIF
1154    
1155    C     >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<
1156          IF (theSimulationMode .EQ. REVERSE_SIMULATION) THEN
1157    
1158            CALL MDS_READ_SEC_YZ(
1159         I                activeVar_file, prec, useCurrentDir,
1160         I                'RS', myNr,
1161         O                dummyRL, active_data_t,
1162         I                iRec, myThid )
1163    
1164    C     Add active_var from appropriate location to data.
1165            DO bj = myByLo(myThid), myByHi(myThid)
1166             DO bi = myBxLo(myThid), myBxHi(myThid)
1167              DO k = 1, myNr
1168               DO j=1,sNy
1169                  active_var(j,k,bi,bj) = active_var(j,k,bi,bj)
1170         &                              + active_data_t(j,k,bi,bj)
1171                  active_data_t(j,k,bi,bj) = 0. _d 0
1172               ENDDO
1173              ENDDO
1174             ENDDO
1175            ENDDO
1176            CALL MDS_WRITE_SEC_YZ(
1177         I                activeVar_file, prec, globalFile, useCurrentDir,
1178         I                'RS', myNr,
1179         I                dummyRL, active_data_t,
1180         I                iRec, myOptimIter, myThid )
1181    
1182          ENDIF
1183    
1184    C     >>>>>>>>>>>>>>>>>>> TANGENT RUN <<<<<<<<<<<<<<<<<<<
1185          IF (theSimulationMode .EQ. TANGENT_SIMULATION) THEN
1186            CALL MDS_WRITE_SEC_YZ(
1187         I                activeVar_file, prec, globalFile, useCurrentDir,
1188         I                'RS', myNr,
1189         I                dummyRL, active_var,
1190         I                iRec, myOptimIter, myThid )
1191          ENDIF
1192    
1193          RETURN
1194          END

Legend:
Removed from v.1.2.2.1  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22