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_fdir.h90 in tags/nemo_dev_x6/NEMO/OPA_SRC/SBC – NEMO

source: tags/nemo_dev_x6/NEMO/OPA_SRC/SBC/flx_bulk_monthly_fdir.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: 9.6 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                 ***  flx_bulk_monthly_fdir.h90  ***
3   !!----------------------------------------------------------------------
4
5   !!----------------------------------------------------------------------
6   !!   flx          : define the thermohaline fluxes for the ocean using
7   !!                  bulk formulea and monthly mean fields read in direct
8   !!                  access files.
9   !!----------------------------------------------------------------------
10   !! * Modules used     C A U T I O N  already defined in flxmod.F90
11
12   !! * Module variables
13   INTEGER ::          &
14      numfl1, numfl2,  &  ! logical units for surface fluxes data
15      numfl3, numfl4,  &  !
16      numfl5,          &  !
17      nflx1, nflx2,    &  !  first and second record used
18      nflx11, nflx12      ! ???
19   REAL(wp), DIMENSION(jpi,jpj,2,7) ::   &
20      flxdta              ! 2 consecutive set of CLIO monthly fluxes
21   !!----------------------------------------------------------------------
22   !!   OPA 9.0 , LODYC-IPSL  (2003)
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  :   bulk formulae with monthly mean fields read in direct
35      !!      access file
36      !!
37      !! ** Method :
38      !!
39      !! History :
40      !!   8.5  !  02-09  (G. Madec)  F90: Free form and module
41      !!----------------------------------------------------------------------
42      !! * Modules used
43      USE bulk
44
45      !! * arguments
46      INTEGER, INTENT( in  ) ::   kt ! ocean time step
47
48      !! * Local declarations
49      INTEGER, PARAMETER ::   jpnk=1, jpmois=12, jpf=7
50      INTEGER ::   ji, jj, jm, ios, jt
51      INTEGER ::   iimlu, ijmlu, ikmlu, ilmlu, immlu
52      INTEGER ::   imois, iman, imois2, i15
53
54      REAL(wp) ::   zpdtan,zman,zpdtmo,zdemi
55      REAL(wp) ::   zxy,zdtt,zdatet,zttbt,zttat
56      REAL(wp) ::   zdtts6
57      INTEGER  ::   ildta,ibloc,ilseq
58
59      CHARACTER (len=30) ::   cltit
60      CHARACTER (len=21) ::   clunf,clold,cldir
61      CHARACTER (len=32) ::   clname
62      !!---------------------------------------------------------------------
63
64
65      ! Initialization
66      ! --------------
67
68      ! Open specifier
69
70      clold='OLD'
71      clunf='UNFORMATTED'
72      cldir='DIRECT'
73
74      ilseq = 1
75
76      ! computation of the record length for direct access file
77      ! this length depend of 4096 (device specification)
78
79      ibloc = 4096
80      ildta = ibloc*((jpidta*jpjdta*jpbytda-1 )/ibloc+1)
81
82      zpdtan= raass/rdttra(1)
83      zman  = 12.
84      iman  = int(zman)
85      zpdtmo= zpdtan/zman
86      zdemi = zpdtmo/2.
87
88      i15 = INT( 2.* FLOAT( nday ) / ( FLOAT( nobis(nmonth) ) + 0.5 ) )
89
90      imois = nmonth + i15 - 1
91      IF( imois == 0 ) imois = iman
92      imois2 = nmonth
93      numfl2=81
94      numfl3=82
95      numfl4=83
96      numfl5=84
97
98
99      ! First call kt=nit000
100      ! --------------------
101
102      IF( kt == nit000 ) THEN
103         nflx1 = 0
104         nflx11 = 0
105         IF(lwp) WRITE(numout,*)
106         IF(lwp) WRITE(numout,*) ' **** flx '
107         IF(lwp) WRITE(numout,*)
108         IF(lwp) WRITE(numout,*) 'read global ocean fluxes '
109         IF(lwp) WRITE(numout,9100) zpdtmo,zdemi
110         IF(lwp) WRITE(numout,*)
111         IF(lwp) WRITE(numout,*) ' read global ocean monthly fields'
112         IF(lwp) WRITE(numout,*) ' --------------------------------'
113         IF(lwp) WRITE(numout,*)
114         IF(lwp) WRITE(numout,*) 'opal file numfl1 = ',numfl1
115 9100    FORMAT (' esbensen : zpdtmo,zdemi :',2f12.3)
116
117
118         ! Read first records
119
120         ! title, dimensions and tests
121         clname='humidata_clio_orca'
122         CALL ctlopn(numfl1,clname,clold,clunf,cldir,ildta,numout,lwp,1)
123         READ (numfl1,REC=1,IOSTAT=ios) cltit,iimlu,ijmlu,ikmlu,ilmlu,immlu
124         
125         clname='winddata_clio_orca'
126         CALL ctlopn(numfl2,clname,clold,clunf,cldir,ildta,numout,lwp,1)
127         READ (numfl2,REC=1,IOSTAT=ios) cltit,iimlu,ijmlu,ikmlu,ilmlu,immlu
128         
129         clname='berdata_clio_orca'
130         CALL ctlopn(numfl3,clname,clold,clunf,cldir,ildta,numout,lwp,1)
131         READ (numfl3,REC=1,IOSTAT=ios) cltit,iimlu,ijmlu,ikmlu,ilmlu,immlu
132         
133         clname='xuedata_clio_orca'
134         CALL ctlopn(numfl4,clname,clold,clunf,cldir,ildta,numout,lwp,1)
135         READ (numfl4,REC=1,IOSTAT=ios) cltit,iimlu,ijmlu,ikmlu,ilmlu,immlu
136         
137         clname='ncardata_spline_orca'
138         CALL ctlopn(numfl5,clname,clold,clunf,cldir,ildta,numout,lwp,1)
139         READ (numfl5,REC=1,IOSTAT=ios) cltit,iimlu,ijmlu,ikmlu,ilmlu,immlu
140         ! temperature
141         ! Utilisation d'un spline, on lit le champ a mois=1
142         CALL read2D(numfl5,flxdta(1,1,1,5),1,3)
143         
144      ENDIF
145
146
147      ! Read monthly file
148      ! ----------------
149
150      IF( kt == nit000 .OR. imois /= nflx1 ) THEN
151
152         ! Calendar computation
153
154         ! nflx1 number of the first file record used in the simulation
155         ! nflx2 number of the last  file record
156
157         nflx1 = imois
158         nflx2 = nflx1+1
159         nflx1 = MOD(nflx1,iman)
160         IF( nflx1 == 0 ) nflx1 = iman
161         nflx2 = MOD(nflx2,iman)
162         IF( nflx2 == 0 ) nflx2 = iman
163         IF(lwp) WRITE(numout,*) 'first record file used nflx1 ',nflx1
164         IF(lwp) WRITE(numout,*) 'last  record file used nflx2 ',nflx2
165         
166         ! Read monthly fluxes data Esbensen Kushnir
167
168         ! humidite
169         CALL read2D(numfl1,flxdta(1,1,1,1),1,nflx1+1)
170         CALL read2D(numfl1,flxdta(1,1,2,1),1,nflx2+1)
171         ! vent
172         CALL read2D(numfl2,flxdta(1,1,1,2),1,nflx1+1)
173         CALL read2D(numfl2,flxdta(1,1,2,2),1,nflx2+1)
174         ! nuages
175         CALL read2D(numfl3,flxdta(1,1,1,3),1,nflx1+1)
176         CALL read2D(numfl3,flxdta(1,1,2,3),1,nflx2+1)
177         ! precipitations
178         CALL read2D(numfl4,flxdta(1,1,1,4),1,nflx1+1)
179         CALL read2D(numfl4,flxdta(1,1,2,4),1,nflx2+1)
180         ! temperature
181         ! Utilisation d'un spline, on lit le champ a mois=nflx1 et nflx2
182         ! CALL read2D(numfl5,flxdta(1,1,1,6),1,3*(nflx1-1)+3)
183         ! CALL read2D(numfl5,flxdta(1,1,2,6),1,3*(nflx2-1)+3)
184         ! on lit la derivee
185         ! CALL read2D(numfl5,flxdta(1,1,1,7),1,3*(nflx1-1)+4)
186         ! CALL read2D(numfl5,flxdta(1,1,2,7),1,3*(nflx2-1)+4)
187
188         IF(lwp) THEN
189            WRITE(numout,*)
190            WRITE(numout,*) ' read clio flx ok'
191            WRITE(numout,*)
192            DO jm = 1, 4
193               WRITE(numout,*)
194               WRITE(numout,*) 'Clio mounth: ',nflx1,'  field: ',jm,' multiply by ',0.1
195               CALL prihre(flxdta(1,1,1,jm),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout)
196            END DO
197         ENDIF
198
199      ENDIF
200
201      IF( kt == nit000 .OR. imois2 /= nflx11 ) THEN
202
203         ! calendar computation
204         
205         ! nflx1 number of the first file record used in the simulation
206         ! nflx2 number of the last  file record
207         
208         nflx11 = imois2
209         nflx12 = nflx11+1
210         nflx11 = MOD(nflx11,iman)
211         IF( nflx11 == 0 ) nflx11 = iman
212         nflx12 = MOD(nflx12,iman)
213         IF( nflx12 == 0 ) nflx12 = iman
214         IF(lwp) WRITE(numout,*) 'first record file used nflx11 ',nflx11
215         IF(lwp) WRITE(numout,*) 'last  record file used nflx12 ',nflx12
216         
217         ! Read monthly fluxes data Esbensen Kushnir
218         
219         ! temperature
220         ! Utilisation d'un spline, on lit le champ a mois=nflx1 et nflx2
221         CALL read2D(numfl5,flxdta(1,1,1,6),1,3*(nflx11-1)+3)
222         CALL read2D(numfl5,flxdta(1,1,2,6),1,3*(nflx12-1)+3)
223         ! on lit la derivee
224         CALL read2D(numfl5,flxdta(1,1,1,7),1,3*(nflx11-1)+4)
225         CALL read2D(numfl5,flxdta(1,1,2,7),1,3*(nflx12-1)+4)
226
227         IF(lwp) THEN
228            WRITE(numout,*)
229            WRITE(numout,*) ' read CLIO flx ok'
230            WRITE(numout,*)
231            DO jm = 6, jpf
232               WRITE(numout,*)
233               WRITE(numout,*) 'Clio mounth: ',nflx11,'  field: ',jm,' multiply by ',0.1
234               CALL prihre(flxdta(1,1,1,jm),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout)
235            END DO
236         ENDIF
237         
238      ENDIF
239
240
241      ! 3. at every time step interpolation of fluxes
242      ! ---------------------------------------------
243
244      zxy = FLOAT(nday) / FLOAT(nobis(nflx1)) + 0.5 - i15
245
246      zdtt = raajj/raamo
247      zdatet = 0.
248      DO jt = 1, nmonth-1
249         zdatet = zdatet + nobis(jt)
250      END DO
251      zdatet = ( zdatet + FLOAT(nday) -1. )/zdtt
252      zttbt = zdatet - int(zdatet)
253      zttat = 1. - zttbt
254      zdtts6 = zdtt/6.
255
256      hatm(:,:) = ( (1.-zxy) * flxdta(:,:,1,1) + zxy * flxdta(:,:,2,1) )
257      vatm(:,:) = ( (1.-zxy) * flxdta(:,:,1,2) + zxy * flxdta(:,:,2,2) )
258      catm(:,:) = ( (1.-zxy )* flxdta(:,:,1,3) + zxy * flxdta(:,:,2,3) )
259      watm(:,:) = ( (1.-zxy) * flxdta(:,:,1,4) + zxy * flxdta(:,:,2,4) )
260      tatm(:,:) = ( flxdta(:,:,2,6) - flxdta(:,:,1,6) )/zdtt     &
261                - ((3. * zttat * zttat - 1.) * flxdta(:,:,1,7)   &
262                - ( 3. * zttbt * zttbt - 1.) * flxdta(:,:,2,7) ) * zdtts6   &
263                + flxdta(:,:,1,5)
264
265      CALL blk(kt)
266
267      CALL FLUSH(numout)
268
269      ! ------------------- !
270      ! Last call kt=nitend !
271      ! ------------------- !
272
273      ! Closing of the 5 files (required in mpp) ????? it smells bug ...
274      IF( kt == nitend ) THEN
275          CALL flinclo(numfl1)
276          CALL flinclo(numfl2)
277          CALL flinclo(numfl3)
278          CALL flinclo(numfl4)
279          CALL flinclo(numfl5)
280      ENDIF
281
282   END SUBROUTINE flx
Note: See TracBrowser for help on using the repository browser.