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

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

CT : BUGFIX159 : initialize ipk=jpk to avoid error when running on IBM and with IOIPSL-2-0 tag

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