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 tags/nemo_dev_x6/NEMO/OPA_SRC/SBC – NEMO

source: tags/nemo_dev_x6/NEMO/OPA_SRC/SBC/flx_bulk_monthly.h90 @ 158

Last change on this file since 158 was 158, checked in by cvs2svn, 20 years ago

This commit was manufactured by cvs2svn to create tag 'nemo_dev_x6'.

  • 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
110
111      ! 1. first call kt=nit000
112      ! -----------------------
113
114      IF( kt == nit000 ) THEN
115         nflx1  = 0
116         nflx11 = 0
117         IF(lwp) THEN
118            WRITE(numout,*)
119            WRITE(numout,*) ' global CLIO flx monthly fields in NetCDF format'
120            WRITE(numout,*) ' ------------------------------'
121            WRITE(numout,*)
122         ENDIF
123         
124         ! Read first records
125
126         ! title, dimensions and tests
127         CALL flinopen( clname, mig(1), nlci, mjg(1), nlcj,   &
128            &          .FALSE., ipi, ipj, ipk, zlon, zlat, zlev,   &
129            &          itime, istep, zdate0, zsecond, numflx )
130         
131         ! temperature
132         ! Utilisation d'un spline, on lit le champ a mois=1
133         CALL flinget( numflx, 'socliot1', jpidta, jpjdta, jpk,   &
134            &          jpmois, 1, 1, mig(1), nlci,   &
135            &          mjg(1), nlcj, flxdta(1:nlci,1:nlcj,1,5) )
136      ENDIF
137
138
139      ! Read monthly file
140      ! ----------------
141
142      IF( kt == nit000 .OR. imois /= nflx1 ) THEN
143
144         ! Calendar computation
145
146         ! nflx1 number of the first file record used in the simulation
147         ! nflx2 number of the last  file record
148
149         nflx1 = imois
150         nflx2 = nflx1+1
151         nflx1 = MOD( nflx1, iman )
152         nflx2 = MOD( nflx2, iman )
153         IF( nflx1 == 0 )   nflx1 = iman
154         IF( nflx2 == 0 )   nflx2 = iman
155         IF(lwp) WRITE(numout,*) 'first record file used nflx1 ',nflx1
156         IF(lwp) WRITE(numout,*) 'last  record file used nflx2 ',nflx2
157         
158         ! Read monthly fluxes data
159
160         ! humidity
161         CALL flinget(numflx,'socliohu',jpidta,jpjdta,jpk,jpmois,nflx1,   &
162            nflx1,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,1))
163         CALL flinget(numflx,'socliohu',jpidta,jpjdta,jpk,jpmois,nflx2,   &
164            nflx2,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,1))
165         ! 10m wind module
166         CALL flinget(numflx,'socliowi',jpidta,jpjdta,jpk,jpmois,nflx1,   &
167            nflx1,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,2))
168         CALL flinget(numflx,'socliowi',jpidta,jpjdta,jpk,jpmois,nflx2,   &
169            nflx2,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,2))
170         ! cloud cover
171         CALL flinget(numflx,'socliocl',jpidta,jpjdta,jpk,jpmois,nflx1,   &
172            nflx1,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,3))
173         CALL flinget(numflx,'socliocl',jpidta,jpjdta,jpk,jpmois,nflx2,   &
174            nflx2,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,3))
175         ! precipitations
176         CALL flinget(numflx,'socliopl',jpidta,jpjdta,jpk,jpmois,nflx1,   &
177            nflx1,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,4))
178         CALL flinget(numflx,'socliopl',jpidta,jpjdta,jpk,jpmois,nflx2,   &
179            nflx2,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,4))
180         
181         IF(lwp .AND. nitend-nit000 <= 100 ) THEN
182            WRITE(numout,*)
183            WRITE(numout,*) ' read clio flx ok'
184            WRITE(numout,*)
185            DO jm = 1, 4
186               WRITE(numout,*)
187               WRITE(numout,*) 'Clio mounth: ',nflx1,'  field: ',jm,' multiply by ',0.1
188               CALL prihre(flxdta(1,1,1,jm),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout)
189            END DO
190         ENDIF
191
192      ENDIF
193
194      ! ------------------- !
195      ! Last call kt=nitend !
196      ! ------------------- !
197
198      ! Closing of the numflx file (required in mpp)
199      IF( kt == nitend ) CALL flinclo(numflx)
200
201
202      IF( kt == nit000 .OR. imois2 /= nflx11 ) THEN
203
204         ! calendar computation
205         
206         ! nflx1 number of the first file record used in the simulation
207         ! nflx2 number of the last  file record
208         
209         nflx11 = imois2
210         nflx12 = nflx11 + 1
211         nflx11 = MOD( nflx11, iman )
212         nflx12 = MOD( nflx12, iman )
213         IF( nflx11 == 0 )   nflx11 = iman
214         IF( nflx12 == 0 )   nflx12 = iman
215         IF(lwp) WRITE(numout,*) 'first record file used nflx11 ',nflx11
216         IF(lwp) WRITE(numout,*) 'last  record file used nflx12 ',nflx12
217         
218         ! Read monthly fluxes data Esbensen Kushnir
219         
220         ! air temperature
221         ! Utilisation d'un spline, on lit le champ a mois=nflx1 et nflx2
222         CALL flinget(numflx,'socliot1',jpidta,jpjdta,jpk,jpmois,nflx11,   &
223            nflx11,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,6))
224         CALL flinget(numflx,'socliot1',jpidta,jpjdta,jpk,jpmois,nflx12,   &
225            nflx12,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,6))
226         ! air temperature derivative (to reconstruct a daily field)
227         CALL flinget(numflx,'socliot2',jpidta,jpjdta,jpk,jpmois,nflx11,   &
228            nflx11,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,1,7))
229         CALL flinget(numflx,'socliot2',jpidta,jpjdta,jpk,jpmois,nflx12,   &
230            nflx12,mig(1),nlci,mjg(1),nlcj,flxdta(1:nlci,1:nlcj,2,7))
231         
232         IF(lwp) THEN
233            WRITE(numout,*)
234            WRITE(numout,*) ' read CLIO flx ok'
235            WRITE(numout,*)
236            DO jm = 6, jpf
237               WRITE(numout,*) 'jpf =  ', jpf !C a u t i o n : information need for SX5NEC compilo bug
238               WRITE(numout,*) 'Clio mounth: ',nflx11,'  field: ',jm,' multiply by ',0.1
239               CALL prihre(flxdta(1,1,1,jm),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout)
240               WRITE(numout,*)
241            END DO
242         ENDIF
243         
244      ENDIF
245
246
247      ! 3. at every time step interpolation of fluxes
248      ! ---------------------------------------------
249
250      zxy = FLOAT( nday ) / FLOAT( nobis(nflx1) ) + 0.5 - i15
251
252      zdtt = raajj / raamo
253      zdatet = 0.
254      DO jt = 1, nmonth-1
255         zdatet = zdatet + nobis(jt)
256      END DO
257      zdatet = ( zdatet + FLOAT(nday) -1. )/zdtt
258      zttbt = zdatet - INT(zdatet)
259      zttat = 1. - zttbt
260      zdtts6 = zdtt/6.
261
262      hatm(:,:) = ( (1.-zxy) * flxdta(:,:,1,1) + zxy * flxdta(:,:,2,1) )
263      vatm(:,:) = ( (1.-zxy) * flxdta(:,:,1,2) + zxy * flxdta(:,:,2,2) )
264      catm(:,:) = ( (1.-zxy )* flxdta(:,:,1,3) + zxy * flxdta(:,:,2,3) )
265      watm(:,:) = ( (1.-zxy) * flxdta(:,:,1,4) + zxy * flxdta(:,:,2,4) )
266      tatm(:,:) = ( flxdta(:,:,2,6) - flxdta(:,:,1,6) )/zdtt   &
267                - ((3. * zttat * zttat - 1.) * flxdta(:,:,1,7)   &
268                - ( 3. * zttbt * zttbt - 1.) * flxdta(:,:,2,7) ) * zdtts6   &
269                + flxdta(:,:,1,5)
270 
271      CALL blk( kt )                ! bulk formulea fluxes
272
273   END SUBROUTINE flx
Note: See TracBrowser for help on using the repository browser.