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

Last change on this file since 869 was 869, checked in by rblod, 16 years ago

Parallelisation of LIM3. This commit seems to ensure the reproducibility mono/mpp. See ticket #77.

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