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_daily.h90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/flx_bulk_daily.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:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 7.0 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                    ***  flx_bulk_daily  ***
3   !!----------------------------------------------------------------------
4
5   !!----------------------------------------------------------------------
6   !!   bulk          : reading
7   !!----------------------------------------------------------------------
8   !! * Modules used     C A U T I O N  already defined in flxmod.F90
9
10   !! * Module variables
11   
12   INTEGER ::          &
13      ji, jj,          &  ! loop indices
14      numfl1, numfl2,  &  ! logical units for surface fluxes data
15      numfl3, numfl4,  &  !
16      nflx1 , nflx2 ,  &  !  first and second record used
17      ndayflx
18
19   REAL(wp), DIMENSION(jpi,jpj,2,3) ::   &
20      flxdta              ! 2 consecutive set of CLIO/CMAP monthly fluxes
21   !!----------------------------------------------------------------------
22   !!   OPA 9.0 , LOCEAN-IPSL (2005)
23   !! $Header$
24   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
25   !!----------------------------------------------------------------------
26
27CONTAINS
28
29   SUBROUTINE flx( kt )
30      !!---------------------------------------------------------------------
31      !!                    ***  ROUTINE flx  ***
32      !!       
33      !! ** Purpose :   provide the thermohaline fluxes (heat and freshwater)
34      !!      to the ocean at each time step.
35      !!
36      !! ** Method :
37      !!       ORCA FORCED VERSION WITH :
38      !!       Daily climatological NCEP temperature
39      !!       Daily climatological ERS-NCEP winds
40      !!       monthly climatological humidity and clouds
41      !!       monthly climatological CMAP precipitation
42      !!       Read several AGCM daily and monthly fluxes file
43      !!             temperature at 2m   tatm   (K)
44      !!             relative humidite   hatm   (%)
45      !!             wind speed          vatm   (m/s)
46      !!             monthly precip      watm   (kg/m2/day)  from Xie/Arkin
47      !!             clouds              catm   (%)
48      !!
49      !! caution : now, in the opa global model, the net upward water flux is
50      !! -------   with mm/day unit.
51      !!
52      !! History :
53      !!        !  91-03  (O. Marti and Ph Dandin)  Original code
54      !!        !  92-07  (M. Imbard)
55      !!        !  96-11  (E. Guilyardi)  Daily AGCM input files
56      !!        !  99-11  (M. Imbard)  NetCDF FORMAT with io-ipsl
57      !!        !  00-05  (K. Rodgers) Daily Netcdf
58      !!   8.5  !  02-09  (C. Ethe and G. Madec)  F90: Free form and MODULE
59      !!----------------------------------------------------------------------
60      !! * modules used
61      USE iom             ! I/O library
62      USE blk_oce         ! bulk variable
63      USE bulk            ! bulk module
64      USE ice_oce
65
66      !! * arguments
67      INTEGER, INTENT( in  ) ::   kt ! ocean time step
68
69      !! * Local declarations     
70      INTEGER  ::   iman,imois,i15
71      REAL(wp) ::   zxy
72      !!---------------------------------------------------------------------
73
74
75      ! Initialization
76      ! --------------
77
78      i15 = INT(2*FLOAT(nday)/(FLOAT(nobis(nmonth))+0.5))
79      iman  = INT( raamo )
80      imois = nmonth + i15 - 1
81      IF (imois == 0) imois = iman
82
83
84      ! 1. first call kt = nit000
85      ! -----------------------
86     
87      IF( kt == nit000 ) THEN
88         ! initializations
89         nflx1 = 0
90         ndayflx = 0
91         IF(lwp) THEN
92            WRITE(numout,*) ' '
93            WRITE(numout,*) ' **** Routine flx_bulk_daily.h90'
94            WRITE(numout,*) ' '
95         ENDIF         
96         ! open files
97         IF(lwp) WRITE(numout,*) ' **** global NCEP flx  daily fields '
98         CALL iom_open ( 'tair_1d.nc', numfl1 )
99         IF(lwp) WRITE(numout,*) ' **** global CLIO flx  monthly fields '
100         CALL iom_open ( 'hum_cloud_1m.nc', numfl2 )
101         IF(lwp) WRITE(numout,*) ' **** global XIE  flx  monthly fields '
102         CALL iom_open ( 'rain_1m.nc', numfl3 )
103         IF(lwp) WRITE(numout,*) ' **** global ERS-NCEP  wind daily  fields '
104         CALL iom_open ( 'wspd_1d.nc', numfl4 )
105      ENDIF
106
107
108      ! 2. Read daily DATA Temperature from NCEP
109      ! ---------------------------------------
110     
111      IF( ndayflx /= nday ) THEN
112         
113         ndayflx = nday
114         
115         ! read T 2m (Caution in K)
116         CALL iom_get ( numfl1, jpdom_data, 'air', tatm, nday_year )
117         
118         IF(lwp) WRITE (numout,*)' Lecture daily flx record OK :',nday_year
119         IF(lwp) WRITE (numout,*)' '
120         
121         ! conversion of temperature Kelvin --> Celsius  [rt0=273.15]
122         tatm(:,:) = ( tatm(:,:) - rt0 )
123         
124         ! read wind speed
125         CALL iom_get ( numfl4, jpdom_data, 'wspd', vatm, nday_year )
126         
127         IF(lwp) WRITE (numout,*)' Lecture daily wind speed flx :',nday_year
128         IF(lwp) WRITE (numout,*)' '
129         
130      ENDIF
131
132     
133      !  3. Read monthly data from CLIO and From Xie
134      !  -------------------------------------------
135     
136      IF( kt == nit000 .OR. imois /= nflx1 ) THEN
137         
138         ! calendar computation
139         
140         ! nflx1 number of the first file record used in the simulation
141         ! flx2 number of the last  file record
142         
143         nflx1 = imois
144         nflx2 = nflx1+1
145         nflx1 = MOD(nflx1,iman)
146         IF ( nflx1 == 0 ) nflx1 = iman
147         nflx2 = MOD(nflx2,iman)
148         IF ( nflx2 == 0 ) nflx2 = iman
149         IF(lwp)WRITE(numout,*) 'first record file used nflx1 ',nflx1
150         IF(lwp)WRITE(numout,*) 'last  record file used nflx2 ',nflx2
151
152         ! Read monthly fluxes data Esbensen Kushnir
153
154         ! humidity
155         CALL iom_get ( numfl2, jpdom_data, 'socliohu', flxdta(:,:,1,1), nflx1 )
156         CALL iom_get ( numfl2, jpdom_data, 'socliohu', flxdta(:,:,2,1), nflx2 )
157
158         ! clouds
159         CALL iom_get ( numfl2, jpdom_data, 'socliocl', flxdta(:,:,1,2), nflx1 )
160         CALL iom_get ( numfl2, jpdom_data, 'socliocl', flxdta(:,:,2,2), nflx2 )
161
162         ! Read monthly precipitations ds flxdta(:,:,1 ou 2,4)
163
164         CALL iom_get ( numfl3, jpdom_data, 'rain', flxdta(:,:,1,3), nflx1 )
165         CALL iom_get ( numfl3, jpdom_data, 'rain', flxdta(:,:,2,3), nflx2 )
166                 
167      ENDIF
168
169
170      ! 3. at every time step linear interpolation of precipitation fluxes
171      ! -----------------------------------------------------------
172     
173      zxy = FLOAT(nday) / FLOAT(nobis(nflx1)) + 0.5 - i15
174
175      hatm(:,:) = ( (1.-zxy) * flxdta(:,:,1,1) + zxy  * flxdta(:,:,2,1) )
176      catm(:,:) = ( (1.-zxy )* flxdta(:,:,1,2) + zxy  * flxdta(:,:,2,2) ) 
177      watm(:,:) = ( (1.-zxy) * flxdta(:,:,1,3) + zxy  * flxdta(:,:,2,3) )
178
179      ! 4. Closing all files
180      ! --------------------
181
182      IF( kt == nitend ) THEN
183         CALL iom_close (numfl1)
184         CALL iom_close (numfl2)
185         CALL iom_close (numfl3)
186         CALL iom_close (numfl4)
187      ENDIF
188
189      CALL blk(kt)
190
191#if defined key_lim3
192      tatm_ice(:,:) = tatm(:,:)
193#endif
194      CALL lbc_lnk(tatm_ice, 'T', 1. )  !RB necessary ??
195     
196      CALL FLUSH(numout)
197     
198   END SUBROUTINE flx
199   
Note: See TracBrowser for help on using the repository browser.