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 @ 392

Last change on this file since 392 was 392, checked in by opalod, 18 years ago

RB:nemo_v1_update_038: first integration of Agrif :

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