New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
flx_bulk_monthly.h90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/flx_bulk_monthly.h90 @ 229

Last change on this file since 229 was 229, checked in by opalod, 19 years ago

CT : BUGFIX162 : add an initialization of extra-hallo in MPP

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 12.7 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                    ***  flx_blulk_monthly.h90  ***
3   !!----------------------------------------------------------------------
4   !!   flx     : update surface thermohaline fluxes using bulk formulae
5   !!             and fields read in a NetCDF file
6   !!----------------------------------------------------------------------
7   !! * Modules used     C A U T I O N  already defined in flxmod.F90
8
9   !! * Module variables
10   
11   INTEGER ::          &
12      ji, jj,          &  ! loop indices
13      numflx,          &  ! logical unit for surface fluxes data
14      nflx1, nflx2,    &  !  first and second record used
15      nflx11, nflx12      ! ???
16
17   REAL(wp), DIMENSION(jpi,jpj,2,7) ::   &
18      flxdta              ! 2 consecutive set of CLIO monthly fluxes
19   !!----------------------------------------------------------------------
20   !!   OPA 9.0 , LODYC-IPSL  (2003)
21   !!----------------------------------------------------------------------
22
23CONTAINS
24
25   SUBROUTINE flx( kt )
26      !!---------------------------------------------------------------------
27      !!                     ***  ROUTINE flx  ***
28      !!                   
29      !! ** Purpose :   provide the thermohaline fluxes (heat and freshwater)
30      !!      to the ocean at each time step.
31      !!
32      !! ** Method  :   Read monthly climatological fluxes in a NetCDF file
33      !!          the net downward radiative flux qsr      1 (watt/m2)
34      !!          the net downward heat flux      q        2 (watt/m2)
35      !!          the net upward water            emp      3 (mm/month)
36      !!              (evaporation - precipitation)
37      !!          the climatological ice cover    rclice   4 (0 or 1)
38      !!
39      !!     Qsr and q is obtained from Esbensen-Kushnir data (opal file) with
40      !!   some corrections :
41      !!          - Data are extended over the polar area and for the net heat
42      !!            flux, values are put at 200 w/m2 on the ice regions
43      !!          - Red sea and Mediterranean values are imposed.
44      !!
45      !!     emp is the Oberhuber climatology with a function of Levitus
46      !!   salinity
47      !!
48      !!     rclice is an handmade climalological ice cover on the polar
49      !!   regions.
50      !!
51      !!     runoff is an handmade climalological runoff.
52      !!
53      !! caution : now, in the opa global model, the net upward water flux is
54      !! -------   with mm/day unit.
55      !!
56      !! History :
57      !!        !  91-03  (O. Marti and Ph Dandin)  Original code
58      !!        !  92-07  (M. Imbard)
59      !!        !  96-11  (E. Guilyardi)  Daily AGCM input files
60      !!        !  99-11  (M. Imbard)  NetCDF FORMAT with ioipsl
61      !!        !  00-10  (J.-P. Boulanger)  adjusted for reading any
62      !!                         daily wind stress data including a climatology
63      !!        !  01-09  (A. Lazar and C. Levy)  Daily NetCDF by default
64      !!   8.5  !  02-09  (G. Madec)  F90: Free form and module
65      !!----------------------------------------------------------------------
66      !! * modules used
67      USE ioipsl
68      USE blk_oce         ! bulk variable
69      USE bulk            ! bulk module
70
71      !! * arguments
72      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
73
74      !! * Local declarations
75      INTEGER, PARAMETER ::   &
76         jpmois = 12,               &  ! number of months
77         jpf    =  7                   ! ??? !bug ?
78      INTEGER ::   jm, jt      ! dummy loop indices
79      INTEGER ::   &
80         imois, imois2, itime,      &  ! temporary integers
81         i15  , iman  ,             &  !    "          "
82         ipi  , ipj   , ipk            !    "          "
83      INTEGER, DIMENSION(jpmois) ::   &
84         istep                         ! ???
85      REAL(wp) ::   &
86         zsecond, zdate0,           &  ! temporary scalars
87         zxy    , zdtt  ,           &  !    "         "
88         zdatet , zttbt ,           &  !    "         "
89         zttat  , zdtts6               !    "         "
90      REAL(wp), DIMENSION(jpk) ::   &
91         zlev                          ! ???
92      REAL(wp), DIMENSION(jpi,jpj) ::   &
93         zlon   , zlat                 ! ???
94      CHARACTER (len=32) ::   &
95         clname = 'flx.nc'             ! flux filename
96      !!---------------------------------------------------------------------
97
98
99      ! Initialization
100      ! --------------
101
102      i15 = INT( 2 * FLOAT( nday ) / ( FLOAT( nobis(nmonth) ) + 0.5 ) )
103      iman  = 12
104      imois = nmonth + i15 - 1
105      IF( imois == 0 ) imois = iman
106      imois2 = nmonth
107
108      ipi = jpiglo
109      ipj = jpjglo
110      ipk = jpk
111
112
113      ! 1. first call kt=nit000
114      ! -----------------------
115
116      IF( kt == nit000 ) THEN
117         nflx1  = 0
118         nflx11 = 0
119         IF(lwp) THEN
120            WRITE(numout,*)
121            WRITE(numout,*) ' global CLIO flx monthly fields in NetCDF format'
122            WRITE(numout,*) ' ------------------------------'
123            WRITE(numout,*)
124         ENDIF
125         
126         ! Read first records
127
128         ! title, dimensions and tests
129         CALL flinopen( clname, mig(1), nlci, mjg(1), nlcj,   &
130            &          .FALSE., ipi, ipj, ipk, zlon, zlat, zlev,   &
131            &          itime, istep, zdate0, zsecond, numflx )
132         
133         ! temperature
134         ! Utilisation d'un spline, on lit le champ a mois=1
135         CALL flinget( numflx, 'socliot1', jpidta, jpjdta, jpk,   &
136            &          jpmois, 1, 1, mig(1), nlci,   &
137            &          mjg(1), nlcj, flxdta(1:nlci,1:nlcj,1,5) )
138
139         ! Extra-halo initialization in MPP
140         IF( lk_mpp ) THEN
141            DO ji = nlci+1, jpi
142               flxdta(ji,:,1,5) = flxdta(1,:,1,5)   ;   flxdta(ji,:,2,5) = flxdta(1,:,2,5)
143            ENDDO
144            DO jj = nlcj+1, jpj
145               flxdta(:,jj,1,5) = flxdta(:,1,1,5)   ;   flxdta(:,jj,2,5) = flxdta(:,1,2,5)
146            ENDDO
147         ENDIF
148      ENDIF
149
150
151      ! Read monthly file
152      ! ----------------
153
154      IF( kt == nit000 .OR. imois /= nflx1 ) THEN
155
156         ! Calendar computation
157
158         ! nflx1 number of the first file record used in the simulation
159         ! nflx2 number of the last  file record
160
161         nflx1 = imois
162         nflx2 = nflx1+1
163         nflx1 = MOD( nflx1, iman )
164         nflx2 = MOD( nflx2, iman )
165         IF( nflx1 == 0 )   nflx1 = iman
166         IF( nflx2 == 0 )   nflx2 = iman
167         IF(lwp) WRITE(numout,*) 'first record file used nflx1 ',nflx1
168         IF(lwp) WRITE(numout,*) 'last  record file used nflx2 ',nflx2
169         
170         ! Read monthly fluxes data
171
172         ! humidity
173         CALL flinget(numflx,'socliohu',jpidta,jpjdta,jpk,jpmois,nflx1,   &
174            nflx1,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,1))
175         CALL flinget(numflx,'socliohu',jpidta,jpjdta,jpk,jpmois,nflx2,   &
176            nflx2,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,1))
177         ! 10m wind module
178         CALL flinget(numflx,'socliowi',jpidta,jpjdta,jpk,jpmois,nflx1,   &
179            nflx1,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,2))
180         CALL flinget(numflx,'socliowi',jpidta,jpjdta,jpk,jpmois,nflx2,   &
181            nflx2,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,2))
182         ! cloud cover
183         CALL flinget(numflx,'socliocl',jpidta,jpjdta,jpk,jpmois,nflx1,   &
184            nflx1,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,3))
185         CALL flinget(numflx,'socliocl',jpidta,jpjdta,jpk,jpmois,nflx2,   &
186            nflx2,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,3))
187         ! precipitations
188         CALL flinget(numflx,'socliopl',jpidta,jpjdta,jpk,jpmois,nflx1,   &
189            nflx1,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,4))
190         CALL flinget(numflx,'socliopl',jpidta,jpjdta,jpk,jpmois,nflx2,   &
191            nflx2,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,4))
192         
193         IF(lwp .AND. nitend-nit000 <= 100 ) THEN
194            WRITE(numout,*)
195            WRITE(numout,*) ' read clio flx ok'
196            WRITE(numout,*)
197            DO jm = 1, 4
198               WRITE(numout,*)
199               WRITE(numout,*) 'Clio mounth: ',nflx1,'  field: ',jm,' multiply by ',0.1
200               CALL prihre(flxdta(1,1,1,jm),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout)
201            END DO
202         ENDIF
203
204         ! Extra-halo initialization in MPP
205         IF( lk_mpp ) THEN
206            DO ji = nlci+1, jpi
207               flxdta(ji,:,1,1) = flxdta(1,:,1,1)   ;   flxdta(ji,:,2,1) = flxdta(1,:,2,1)
208               flxdta(ji,:,1,2) = flxdta(1,:,1,2)   ;   flxdta(ji,:,2,2) = flxdta(1,:,2,2)
209               flxdta(ji,:,1,3) = flxdta(1,:,1,3)   ;   flxdta(ji,:,2,3) = flxdta(1,:,2,3)
210               flxdta(ji,:,1,4) = flxdta(1,:,1,4)   ;   flxdta(ji,:,2,4) = flxdta(1,:,2,4)
211            ENDDO
212            DO jj = nlcj+1, jpj
213               flxdta(:,jj,1,1) = flxdta(:,1,1,1)   ;   flxdta(:,jj,2,1) = flxdta(:,1,2,1)
214               flxdta(:,jj,1,2) = flxdta(:,1,1,2)   ;   flxdta(:,jj,2,2) = flxdta(:,1,2,2)
215               flxdta(:,jj,1,3) = flxdta(:,1,1,3)   ;   flxdta(:,jj,2,3) = flxdta(:,1,2,3)
216               flxdta(:,jj,1,4) = flxdta(:,1,1,4)   ;   flxdta(:,jj,2,4) = flxdta(:,1,2,4)
217            ENDDO
218         ENDIF
219
220      ENDIF
221
222      ! ------------------- !
223      ! Last call kt=nitend !
224      ! ------------------- !
225
226      ! Closing of the numflx file (required in mpp)
227      IF( kt == nitend ) CALL flinclo(numflx)
228
229
230      IF( kt == nit000 .OR. imois2 /= nflx11 ) THEN
231
232         ! calendar computation
233         
234         ! nflx1 number of the first file record used in the simulation
235         ! nflx2 number of the last  file record
236         
237         nflx11 = imois2
238         nflx12 = nflx11 + 1
239         nflx11 = MOD( nflx11, iman )
240         nflx12 = MOD( nflx12, iman )
241         IF( nflx11 == 0 )   nflx11 = iman
242         IF( nflx12 == 0 )   nflx12 = iman
243         IF(lwp) WRITE(numout,*) 'first record file used nflx11 ',nflx11
244         IF(lwp) WRITE(numout,*) 'last  record file used nflx12 ',nflx12
245         
246         ! Read monthly fluxes data Esbensen Kushnir
247         
248         ! air temperature
249         ! Utilisation d'un spline, on lit le champ a mois=nflx1 et nflx2
250         CALL flinget(numflx,'socliot1',jpidta,jpjdta,jpk,jpmois,nflx11,   &
251            nflx11,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,6))
252         CALL flinget(numflx,'socliot1',jpidta,jpjdta,jpk,jpmois,nflx12,   &
253            nflx12,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,6))
254         ! air temperature derivative (to reconstruct a daily field)
255         CALL flinget(numflx,'socliot2',jpidta,jpjdta,jpk,jpmois,nflx11,   &
256            nflx11,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,7))
257         CALL flinget(numflx,'socliot2',jpidta,jpjdta,jpk,jpmois,nflx12,   &
258            nflx12,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,7))
259         
260         IF(lwp) THEN
261            WRITE(numout,*)
262            WRITE(numout,*) ' read CLIO flx ok'
263            WRITE(numout,*)
264            DO jm = 6, jpf
265               WRITE(numout,*) 'jpf =  ', jpf !C a u t i o n : information need for SX5NEC compilo bug
266               WRITE(numout,*) 'Clio mounth: ',nflx11,'  field: ',jm,' multiply by ',0.1
267               CALL prihre(flxdta(1,1,1,jm),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout)
268               WRITE(numout,*)
269            END DO
270         ENDIF
271
272         ! Extra-halo initialization in MPP
273         IF( lk_mpp ) THEN
274            DO ji = nlci+1, jpi
275               flxdta(ji,:,1,6) = flxdta(1,:,1,6)   ;   flxdta(ji,:,2,6) = flxdta(1,:,2,6)
276               flxdta(ji,:,1,7) = flxdta(1,:,1,7)   ;   flxdta(ji,:,2,7) = flxdta(1,:,2,7)
277            ENDDO
278            DO jj = nlcj+1, jpj
279               flxdta(:,jj,1,6) = flxdta(:,1,1,6)   ;   flxdta(:,jj,2,6) = flxdta(:,1,2,6)
280               flxdta(:,jj,1,7) = flxdta(:,1,1,7)   ;   flxdta(:,jj,2,7) = flxdta(:,1,2,7)
281            ENDDO
282         ENDIF
283         
284      ENDIF
285
286
287      ! 3. at every time step interpolation of fluxes
288      ! ---------------------------------------------
289
290      zxy = FLOAT( nday ) / FLOAT( nobis(nflx1) ) + 0.5 - i15
291
292      zdtt = raajj / raamo
293      zdatet = 0.
294      DO jt = 1, nmonth-1
295         zdatet = zdatet + nobis(jt)
296      END DO
297      zdatet = ( zdatet + FLOAT(nday) -1. )/zdtt
298      zttbt = zdatet - INT(zdatet)
299      zttat = 1. - zttbt
300      zdtts6 = zdtt/6.
301
302      hatm(:,:) = ( (1.-zxy) * flxdta(:,:,1,1) + zxy * flxdta(:,:,2,1) )
303      vatm(:,:) = ( (1.-zxy) * flxdta(:,:,1,2) + zxy * flxdta(:,:,2,2) )
304      catm(:,:) = ( (1.-zxy )* flxdta(:,:,1,3) + zxy * flxdta(:,:,2,3) )
305      watm(:,:) = ( (1.-zxy) * flxdta(:,:,1,4) + zxy * flxdta(:,:,2,4) )
306      tatm(:,:) = ( flxdta(:,:,2,6) - flxdta(:,:,1,6) )/zdtt   &
307                - ((3. * zttat * zttat - 1.) * flxdta(:,:,1,7)   &
308                - ( 3. * zttbt * zttbt - 1.) * flxdta(:,:,2,7) ) * zdtts6   &
309                + flxdta(:,:,1,5)
310 
311      CALL blk( kt )                ! bulk formulea fluxes
312
313   END SUBROUTINE flx
Note: See TracBrowser for help on using the repository browser.