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.
diadct.F90 in NEMO/branches/2019/dev_r12072_MERGE_OPTION2_2019/src/OCE/DIA – NEMO

source: NEMO/branches/2019/dev_r12072_MERGE_OPTION2_2019/src/OCE/DIA/diadct.F90 @ 12202

Last change on this file since 12202 was 12202, checked in by cetlod, 4 years ago

dev_merge_option2 : merge in dev_r11613_ENHANCE-04_namelists_as_internalfiles

  • Property svn:keywords set to Id
File size: 57.7 KB
Line 
1MODULE diadct
2   !!======================================================================
3   !!                       ***  MODULE  diadct  ***
4   !! Ocean diagnostics: Compute the transport trough a sec.
5   !!======================================================================
6   !! History :  OPA  ! 02/1999 (Y Drillet)  original code
7   !!                 ! 10/2001 (Y Drillet, R Bourdalle Badie)
8   !!   NEMO     1.0  ! 10/2005 (M Laborie) F90
9   !!            3.0  ! 04/2007 (G Garric) Ice sections
10   !!             -   ! 04/2007 (C Bricaud) test on sec%nb_point, initialisation of ztransp1,ztransp2,...
11   !!            3.4  ! 09/2011 (C Bricaud)
12   !!----------------------------------------------------------------------
13   !! does not work with agrif
14#if ! defined key_agrif
15   !!----------------------------------------------------------------------
16   !!   dia_dct      :  Compute the transport through a sec.
17   !!   dia_dct_init :  Read namelist.
18   !!   readsec      :  Read sections description and pathway
19   !!   removepoints :  Remove points which are common to 2 procs
20   !!   transport    :  Compute transport for each sections
21   !!   dia_dct_wri  :  Write tranports results in ascii files
22   !!   interp       :  Compute temperature/salinity/density at U-point or V-point
23   !!   
24   !!----------------------------------------------------------------------
25   USE oce             ! ocean dynamics and tracers
26   USE dom_oce         ! ocean space and time domain
27   USE phycst          ! physical constants
28   USE in_out_manager  ! I/O manager
29   USE daymod          ! calendar
30   USE dianam          ! build name of file
31   USE lib_mpp         ! distributed memory computing library
32#if defined key_si3
33   USE ice
34#endif
35   USE domvvl
36   USE timing          ! preformance summary
37
38   IMPLICIT NONE
39   PRIVATE
40
41   PUBLIC   dia_dct      ! routine called by step.F90
42   PUBLIC   dia_dct_init ! routine called by nemogcm.F90
43
44   !                         !!** namelist variables **
45   LOGICAL, PUBLIC ::   ln_diadct     !: Calculate transport thru a section or not
46   INTEGER         ::   nn_dct        !  Frequency of computation
47   INTEGER         ::   nn_dctwri     !  Frequency of output
48   INTEGER         ::   nn_secdebug   !  Number of the section to debug
49   
50   INTEGER, PARAMETER :: nb_class_max  = 10
51   INTEGER, PARAMETER :: nb_sec_max    = 150
52   INTEGER, PARAMETER :: nb_point_max  = 2000
53   INTEGER, PARAMETER :: nb_type_class = 10
54   INTEGER, PARAMETER :: nb_3d_vars    = 3 
55   INTEGER, PARAMETER :: nb_2d_vars    = 2 
56   INTEGER            :: nb_sec 
57
58   TYPE POINT_SECTION
59      INTEGER :: I,J
60   END TYPE POINT_SECTION
61
62   TYPE COORD_SECTION
63      REAL(wp) :: lon,lat
64   END TYPE COORD_SECTION
65
66   TYPE SECTION
67      CHARACTER(len=60)                            :: name              ! name of the sec
68      LOGICAL                                      :: llstrpond         ! true if you want the computation of salt and
69                                                                       ! heat transports
70      LOGICAL                                      :: ll_ice_section    ! ice surface and ice volume computation
71      LOGICAL                                      :: ll_date_line      ! = T if the section crosses the date-line
72      TYPE(COORD_SECTION), DIMENSION(2)            :: coordSec          ! longitude and latitude of the extremities of the sec
73      INTEGER                                      :: nb_class          ! number of boundaries for density classes
74      INTEGER, DIMENSION(nb_point_max)             :: direction         ! vector direction of the point in the section
75      CHARACTER(len=40),DIMENSION(nb_class_max)    :: classname         ! characteristics of the class
76      REAL(wp), DIMENSION(nb_class_max)            :: zsigi           ,&! in-situ   density classes    (99 if you don't want)
77                                                      zsigp           ,&! potential density classes    (99 if you don't want)
78                                                      zsal            ,&! salinity classes   (99 if you don't want)
79                                                      ztem            ,&! temperature classes(99 if you don't want)
80                                                      zlay              ! level classes      (99 if you don't want)
81      REAL(wp), DIMENSION(nb_type_class,nb_class_max)  :: transport     ! transport output
82      REAL(wp)                                         :: slopeSection  ! slope of the section
83      INTEGER                                          :: nb_point      ! number of points in the section
84      TYPE(POINT_SECTION),DIMENSION(nb_point_max)      :: listPoint     ! list of points in the sections
85   END TYPE SECTION
86
87   TYPE(SECTION),DIMENSION(nb_sec_max) :: secs ! Array of sections
88 
89   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) ::  transports_3d 
90   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   ::  transports_2d 
91
92   !!----------------------------------------------------------------------
93   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
94   !! $Id$
95   !! Software governed by the CeCILL license (see ./LICENSE)
96   !!----------------------------------------------------------------------
97CONTAINS
98 
99   INTEGER FUNCTION diadct_alloc() 
100      !!----------------------------------------------------------------------
101      !!                   ***  FUNCTION diadct_alloc  ***
102      !!----------------------------------------------------------------------
103
104      ALLOCATE( transports_3d(nb_3d_vars,nb_sec_max,nb_point_max,jpk), &
105         &      transports_2d(nb_2d_vars,nb_sec_max,nb_point_max)    , STAT=diadct_alloc ) 
106
107      CALL mpp_sum( 'diadct', diadct_alloc ) 
108      IF( diadct_alloc /= 0 )   CALL ctl_stop( 'STOP', 'diadct_alloc: failed to allocate arrays' ) 
109
110   END FUNCTION diadct_alloc
111
112   SUBROUTINE dia_dct_init
113      !!---------------------------------------------------------------------
114      !!               ***  ROUTINE diadct  *** 
115      !!
116      !!  ** Purpose: Read the namelist parameters
117      !!              Open output files
118      !!
119      !!---------------------------------------------------------------------
120      INTEGER  ::   ios                 ! Local integer output status for namelist read
121      !!
122      NAMELIST/nam_diadct/ln_diadct, nn_dct, nn_dctwri, nn_secdebug
123      !!---------------------------------------------------------------------
124
125     READ  ( numnam_ref, nam_diadct, IOSTAT = ios, ERR = 901)
126901  IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diadct in reference namelist' )
127
128     READ  ( numnam_cfg, nam_diadct, IOSTAT = ios, ERR = 902 )
129902  IF( ios >  0 ) CALL ctl_nam ( ios , 'nam_diadct in configuration namelist' )
130     IF(lwm) WRITE ( numond, nam_diadct )
131
132     IF( lwp ) THEN
133        WRITE(numout,*) " "
134        WRITE(numout,*) "diadct_init: compute transports through sections "
135        WRITE(numout,*) "~~~~~~~~~~~~~~~~~~~~~"
136        WRITE(numout,*) "       Calculate transport thru sections: ln_diadct = ", ln_diadct
137        WRITE(numout,*) "       Frequency of computation:          nn_dct    = ", nn_dct
138        WRITE(numout,*) "       Frequency of write:                nn_dctwri = ", nn_dctwri
139
140        IF      ( nn_secdebug .GE. 1 .AND. nn_secdebug .LE. nb_sec_max )THEN
141                                            WRITE(numout,*)"       Debug section number: ", nn_secdebug 
142        ELSE IF ( nn_secdebug ==  0 )THEN ; WRITE(numout,*)"       No section to debug"
143        ELSE IF ( nn_secdebug == -1 )THEN ; WRITE(numout,*)"       Debug all sections"
144        ELSE                              ; WRITE(numout,*)"       Wrong value for nn_secdebug : ",nn_secdebug
145        ENDIF
146     ENDIF
147
148     IF( ln_diadct ) THEN
149        ! control
150        IF(nn_dct .GE. nn_dctwri .AND. MOD(nn_dct,nn_dctwri) .NE. 0)  &
151           &  CALL ctl_stop( 'diadct: nn_dct should be smaller and a multiple of nn_dctwri' )
152
153        ! allocate dia_dct arrays
154        IF( diadct_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'diadct_alloc: failed to allocate arrays' )
155
156        !Read section_ijglobal.diadct
157        CALL readsec
158
159        !open output file
160        IF( lwm ) THEN
161           CALL ctl_opn( numdct_vol,  'volume_transport', 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. )
162           CALL ctl_opn( numdct_heat, 'heat_transport'  , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. )
163           CALL ctl_opn( numdct_salt, 'salt_transport'  , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. )
164        ENDIF
165
166        ! Initialise arrays to zero
167        transports_3d(:,:,:,:)=0.0 
168        transports_2d(:,:,:)  =0.0 
169        !
170     ENDIF
171     !
172  END SUBROUTINE dia_dct_init
173 
174 
175  SUBROUTINE dia_dct( kt )
176     !!---------------------------------------------------------------------
177     !!               ***  ROUTINE diadct  *** 
178     !!
179     !!  Purpose :: Compute section transports and write it in numdct files
180     !!   
181     !!  Method  :: All arrays initialised to zero in dct_init
182     !!             Each nn_dct time step call subroutine 'transports' for
183     !!               each section to sum the transports over each grid cell.
184     !!             Each nn_dctwri time step:
185     !!               Divide the arrays by the number of summations to gain
186     !!               an average value
187     !!               Call dia_dct_sum to sum relevant grid boxes to obtain
188     !!               totals for each class (density, depth, temp or sal)
189     !!               Call dia_dct_wri to write the transports into file
190     !!               Reinitialise all relevant arrays to zero
191     !!---------------------------------------------------------------------
192     INTEGER, INTENT(in) ::   kt
193     !
194     INTEGER ::   jsec              ! loop on sections
195     INTEGER ::   itotal            ! nb_sec_max*nb_type_class*nb_class_max
196     LOGICAL ::   lldebug =.FALSE.  ! debug a section 
197     INTEGER              , DIMENSION(1)    ::   ish     ! work array for mpp_sum
198     INTEGER              , DIMENSION(3)    ::   ish2    !   "
199     REAL(wp), ALLOCATABLE, DIMENSION(:)    ::   zwork   !   " 
200     REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)::   zsum    !   "
201     !!---------------------------------------------------------------------   
202     !
203     IF( ln_timing )   CALL timing_start('dia_dct')
204
205     IF( lk_mpp )THEN
206        itotal = nb_sec_max*nb_type_class*nb_class_max
207        ALLOCATE( zwork(itotal) , zsum(nb_sec_max,nb_type_class,nb_class_max) )
208     ENDIF   
209 
210     ! Initialise arrays
211     zwork(:) = 0.0 
212     zsum(:,:,:) = 0.0
213
214     IF( lwp .AND. kt==nit000+nn_dct-1 ) THEN
215         WRITE(numout,*) " "
216         WRITE(numout,*) "diadct: compute transport"
217         WRITE(numout,*) "~~~~~~~~~~~~~~~~~~~~~~~~~"
218         WRITE(numout,*) "nb_sec = ",nb_sec
219     ENDIF
220
221 
222     ! Compute transport and write only at nn_dctwri
223     IF( MOD(kt,nn_dct)==0 ) THEN
224
225        DO jsec=1,nb_sec
226
227           !debug this section computing ?
228           lldebug=.FALSE.
229           IF( (jsec==nn_secdebug .OR. nn_secdebug==-1) .AND.  kt==nit000+nn_dct-1 ) lldebug=.TRUE. 
230
231           !Compute transport through section 
232           CALL transport(secs(jsec),lldebug,jsec) 
233
234        ENDDO
235             
236        IF( MOD(kt,nn_dctwri)==0 )THEN
237
238           IF( kt==nit000+nn_dctwri-1 )WRITE(numout,*)"      diadct: average transports and write at kt = ",kt         
239 
240           !! divide arrays by nn_dctwri/nn_dct to obtain average
241           transports_3d(:,:,:,:)=transports_3d(:,:,:,:)/(nn_dctwri/nn_dct) 
242           transports_2d(:,:,:)  =transports_2d(:,:,:)  /(nn_dctwri/nn_dct) 
243 
244           ! Sum over each class
245           DO jsec=1,nb_sec 
246              CALL dia_dct_sum(secs(jsec),jsec) 
247           ENDDO 
248
249           !Sum on all procs
250           IF( lk_mpp )THEN
251              ish(1)  =  nb_sec_max*nb_type_class*nb_class_max 
252              ish2    = (/nb_sec_max,nb_type_class,nb_class_max/)
253              DO jsec=1,nb_sec ; zsum(jsec,:,:) = secs(jsec)%transport(:,:) ; ENDDO
254              zwork(:)= RESHAPE(zsum(:,:,:), ish )
255              CALL mpp_sum('diadct', zwork, ish(1))
256              zsum(:,:,:)= RESHAPE(zwork,ish2)
257              DO jsec=1,nb_sec ; secs(jsec)%transport(:,:) = zsum(jsec,:,:) ; ENDDO
258           ENDIF
259
260           !Write the transport
261           DO jsec=1,nb_sec
262
263              IF( lwm )CALL dia_dct_wri(kt,jsec,secs(jsec))
264           
265              !nullify transports values after writing
266              transports_3d(:,jsec,:,:)=0.
267              transports_2d(:,jsec,:  )=0.
268              secs(jsec)%transport(:,:)=0. 
269
270           ENDDO
271
272        ENDIF
273
274     ENDIF
275
276     IF( lk_mpp )THEN
277        itotal = nb_sec_max*nb_type_class*nb_class_max
278        DEALLOCATE( zwork , zsum  )
279     ENDIF   
280
281     IF( ln_timing )   CALL timing_stop('dia_dct')
282     !
283  END SUBROUTINE dia_dct
284
285
286  SUBROUTINE readsec 
287     !!---------------------------------------------------------------------
288     !!               ***  ROUTINE readsec  ***
289     !!
290     !!  ** Purpose:
291     !!            Read a binary file(section_ijglobal.diadct)
292     !!            generated by the tools "NEMOGCM/TOOLS/SECTIONS_DIADCT"
293     !!
294     !!
295     !!---------------------------------------------------------------------
296     INTEGER :: iptglo , iptloc                               ! Global and local number of points for a section
297     INTEGER :: isec, iiglo, ijglo, iiloc, ijloc,iost,i1 ,i2  ! temporary  integer
298     INTEGER :: jsec, jpt                                     ! dummy loop indices
299     INTEGER, DIMENSION(2) :: icoord 
300     LOGICAL               :: llbon, lldebug   ! local logical
301     CHARACTER(len=160)    :: clname           ! filename
302     CHARACTER(len=200)    :: cltmp
303     CHARACTER(len=200)    :: clformat                          !automatic format
304     TYPE(POINT_SECTION),DIMENSION(nb_point_max)  ::coordtemp   !contains listpoints coordinates read in the file
305     INTEGER, DIMENSION(nb_point_max) :: directemp              !contains listpoints directions read in the files
306     !!-------------------------------------------------------------------------------------
307
308     !open input file
309     !---------------
310     CALL ctl_opn( numdct_in, 'section_ijglobal.diadct', 'OLD', 'UNFORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
311 
312     !---------------
313     !Read input file
314     !---------------
315     
316     DO jsec=1,nb_sec_max      !loop on the nb_sec sections
317
318        IF (  jsec==nn_secdebug .OR. nn_secdebug==-1  ) &
319           & WRITE(numout,*)'debuging for section number: ',jsec 
320
321        !initialization
322        !---------------
323        secs(jsec)%name=''
324        secs(jsec)%llstrpond    = .FALSE.  ; secs(jsec)%ll_ice_section = .FALSE.
325        secs(jsec)%ll_date_line = .FALSE.  ; secs(jsec)%nb_class       = 0
326        secs(jsec)%zsigi        = 99._wp   ; secs(jsec)%zsigp          = 99._wp
327        secs(jsec)%zsal         = 99._wp   ; secs(jsec)%ztem           = 99._wp
328        secs(jsec)%zlay         = 99._wp         
329        secs(jsec)%transport    =  0._wp   ; secs(jsec)%nb_point       = 0
330
331        !read section's number / name / computing choices / classes / slopeSection / points number
332        !-----------------------------------------------------------------------------------------
333        READ(numdct_in,iostat=iost)isec
334        IF (iost .NE. 0 )EXIT !end of file
335        WRITE(cltmp,'(a,i4.4,a,i4.4)')'diadct: read sections : Problem of section number: isec= ',isec,' and jsec= ',jsec
336        IF( jsec .NE. isec )  CALL ctl_stop( cltmp )
337
338        IF( jsec==nn_secdebug .OR. nn_secdebug==-1 )WRITE(numout,*)"isec ",isec 
339
340        READ(numdct_in)secs(jsec)%name
341        READ(numdct_in)secs(jsec)%llstrpond
342        READ(numdct_in)secs(jsec)%ll_ice_section
343        READ(numdct_in)secs(jsec)%ll_date_line
344        READ(numdct_in)secs(jsec)%coordSec
345        READ(numdct_in)secs(jsec)%nb_class
346        READ(numdct_in)secs(jsec)%zsigi
347        READ(numdct_in)secs(jsec)%zsigp
348        READ(numdct_in)secs(jsec)%zsal
349        READ(numdct_in)secs(jsec)%ztem
350        READ(numdct_in)secs(jsec)%zlay
351        READ(numdct_in)secs(jsec)%slopeSection
352        READ(numdct_in)iptglo
353
354        !debug
355        !-----
356
357        IF( jsec==nn_secdebug .OR. nn_secdebug==-1 )THEN
358         
359            WRITE(clformat,'(a,i2,a)') '(A40,', nb_class_max,'(f8.3,1X))' 
360
361            WRITE(numout,*)       "   Section name :                       ",TRIM(secs(jsec)%name)
362            WRITE(numout,*)       "      Compute heat and salt transport ? ",secs(jsec)%llstrpond
363            WRITE(numout,*)       "      Compute ice transport ?           ",secs(jsec)%ll_ice_section
364            WRITE(numout,*)       "      Section crosses date-line ?       ",secs(jsec)%ll_date_line
365            WRITE(numout,*)       "      Slope section :                   ",secs(jsec)%slopeSection
366            WRITE(numout,*)       "      Number of points in the section:  ",iptglo
367            WRITE(numout,*)       "      Number of classes                 ",secs(jsec)%nb_class
368            WRITE(numout,clformat)"      Insitu density classes :          ",secs(jsec)%zsigi
369            WRITE(numout,clformat)"      Potential density classes :       ",secs(jsec)%zsigp
370            WRITE(numout,clformat)"      Salinity classes :                ",secs(jsec)%zsal
371            WRITE(numout,clformat)"      Temperature classes :             ",secs(jsec)%ztem
372            WRITE(numout,clformat)"      Depth classes :                   ",secs(jsec)%zlay
373        ENDIF               
374
375        IF( iptglo /= 0 )THEN
376             
377           !read points'coordinates and directions
378           !--------------------------------------
379           coordtemp(:) = POINT_SECTION(0,0) !list of points read
380           directemp(:) = 0                  !value of directions of each points
381           DO jpt=1,iptglo
382              READ(numdct_in) i1, i2
383              coordtemp(jpt)%I = i1 
384              coordtemp(jpt)%J = i2
385           ENDDO
386           READ(numdct_in) directemp(1:iptglo)
387   
388           !debug
389           !-----
390           IF( jsec==nn_secdebug .OR. nn_secdebug==-1 )THEN
391              WRITE(numout,*)"      List of points in global domain:"
392              DO jpt=1,iptglo
393                 WRITE(numout,*)'        # I J ',jpt,coordtemp(jpt),directemp(jpt)
394              ENDDO                 
395           ENDIF
396 
397           !Now each proc selects only points that are in its domain:
398           !--------------------------------------------------------
399           iptloc = 0                    ! initialize number of points selected
400           DO jpt = 1, iptglo            ! loop on listpoint read in the file
401              !     
402              iiglo=coordtemp(jpt)%I          ! global coordinates of the point
403              ijglo=coordtemp(jpt)%J          !  "
404
405              IF( iiglo==jpiglo .AND. nimpp==1 )   iiglo = 2         !!gm BUG: Hard coded periodicity !
406
407              iiloc=iiglo-nimpp+1   ! local coordinates of the point
408              ijloc=ijglo-njmpp+1   !  "
409
410              !verify if the point is on the local domain:(1,nlei)*(1,nlej)
411              IF( iiloc >= 1 .AND. iiloc <= nlei .AND. &
412                  ijloc >= 1 .AND. ijloc <= nlej       )THEN
413                 iptloc = iptloc + 1                                                 ! count local points
414                 secs(jsec)%listPoint(iptloc) = POINT_SECTION(mi0(iiglo),mj0(ijglo)) ! store local coordinates
415                 secs(jsec)%direction(iptloc) = directemp(jpt)                       ! store local direction
416              ENDIF
417              !
418           END DO
419     
420           secs(jsec)%nb_point=iptloc !store number of section's points
421
422           !debug
423           !-----
424           IF( jsec==nn_secdebug .OR. nn_secdebug==-1 )THEN
425              WRITE(numout,*)"      List of points selected by the proc:"
426              DO jpt = 1,iptloc
427                 iiglo = secs(jsec)%listPoint(jpt)%I + nimpp - 1
428                 ijglo = secs(jsec)%listPoint(jpt)%J + njmpp - 1
429                 WRITE(numout,*)'         # I J : ',iiglo,ijglo
430              ENDDO
431           ENDIF
432
433              IF(jsec==nn_secdebug .AND. secs(jsec)%nb_point .NE. 0)THEN
434              DO jpt = 1,iptloc
435                 iiglo = secs(jsec)%listPoint(jpt)%I + nimpp - 1
436                 ijglo = secs(jsec)%listPoint(jpt)%J + njmpp - 1
437              ENDDO
438              ENDIF
439
440           !remove redundant points between processors
441           !------------------------------------------
442           lldebug = .FALSE. ; IF ( jsec==nn_secdebug .OR. nn_secdebug==-1 ) lldebug = .TRUE.
443           IF( iptloc .NE. 0 )THEN
444              CALL removepoints(secs(jsec),'I','top_list',lldebug)
445              CALL removepoints(secs(jsec),'I','bot_list',lldebug)
446              CALL removepoints(secs(jsec),'J','top_list',lldebug)
447              CALL removepoints(secs(jsec),'J','bot_list',lldebug)
448           ENDIF
449           IF(jsec==nn_secdebug .AND. secs(jsec)%nb_point .NE. 0)THEN
450              DO jpt = 1,secs(jsec)%nb_point
451                 iiglo = secs(jsec)%listPoint(jpt)%I + nimpp - 1
452                 ijglo = secs(jsec)%listPoint(jpt)%J + njmpp - 1
453              ENDDO
454           ENDIF
455
456           !debug
457           !-----
458           IF( jsec==nn_secdebug .OR. nn_secdebug==-1 )THEN
459              WRITE(numout,*)"      List of points after removepoints:"
460              iptloc = secs(jsec)%nb_point
461              DO jpt = 1,iptloc
462                 iiglo = secs(jsec)%listPoint(jpt)%I + nimpp - 1
463                 ijglo = secs(jsec)%listPoint(jpt)%J + njmpp - 1
464                 WRITE(numout,*)'         # I J : ',iiglo,ijglo
465                 CALL FLUSH(numout)
466              ENDDO
467           ENDIF
468
469        ELSE  ! iptglo = 0
470           IF( jsec==nn_secdebug .OR. nn_secdebug==-1 )&
471              WRITE(numout,*)'   No points for this section.'
472        ENDIF
473
474     ENDDO !end of the loop on jsec
475 
476     nb_sec = jsec-1   !number of section read in the file
477     !
478  END SUBROUTINE readsec
479
480
481  SUBROUTINE removepoints(sec,cdind,cdextr,ld_debug)
482     !!---------------------------------------------------------------------------
483     !!             *** function removepoints
484     !!
485     !!   ** Purpose :: Remove points which are common to 2 procs
486     !!
487     !----------------------------------------------------------------------------
488     !! * arguments
489     TYPE(SECTION),INTENT(INOUT) :: sec
490     CHARACTER(len=1),INTENT(IN) :: cdind   ! = 'I'/'J'
491     CHARACTER(len=8),INTENT(IN) :: cdextr  ! = 'top_list'/'bot_list'
492     LOGICAL,INTENT(IN)          :: ld_debug                     
493
494     !! * Local variables
495     INTEGER :: iextr         ,& !extremity of listpoint that we verify
496                iind          ,& !coord     of listpoint that we verify
497                itest         ,& !indice value of the side of the domain
498                                 !where points could be redundant
499                isgn          ,& ! isgn= 1 : scan listpoint from start to end
500                                 ! isgn=-1 : scan listpoint from end to start
501                istart,iend      !first and last points selected in listpoint
502     INTEGER :: jpoint           !loop on list points
503     INTEGER, DIMENSION(nb_point_max)   :: idirec !contains temporary sec%direction
504     INTEGER, DIMENSION(2,nb_point_max) :: icoord !contains temporary sec%listpoint
505     !----------------------------------------------------------------------------
506     !
507     IF( ld_debug )WRITE(numout,*)'      -------------------------'
508     IF( ld_debug )WRITE(numout,*)'      removepoints in listpoint'
509
510     !iextr=extremity of list_point that we verify
511     IF      ( cdextr=='bot_list' )THEN ; iextr=1            ; isgn=1
512     ELSE IF ( cdextr=='top_list' )THEN ; iextr=sec%nb_point ; isgn=-1
513     ELSE    ; CALL ctl_stop("removepoints :Wrong value for cdextr")
514     ENDIF
515 
516     !which coordinate shall we verify ?
517     IF      ( cdind=='I' )THEN   ; itest=nlei ; iind=1
518     ELSE IF ( cdind=='J' )THEN   ; itest=nlej ; iind=2
519     ELSE    ; CALL ctl_stop("removepoints :Wrong value for cdind") 
520     ENDIF
521
522     IF( ld_debug )THEN
523        WRITE(numout,*)'      case: coord/list extr/domain side'
524        WRITE(numout,*)'      ', cdind,' ',cdextr,' ',itest
525        WRITE(numout,*)'      Actual number of points: ',sec%nb_point
526     ENDIF
527
528     icoord(1,1:nb_point_max) = sec%listPoint%I
529     icoord(2,1:nb_point_max) = sec%listPoint%J
530     idirec                   = sec%direction
531     sec%listPoint            = POINT_SECTION(0,0)
532     sec%direction            = 0
533
534     jpoint=iextr+isgn
535     DO WHILE( jpoint .GE. 1 .AND. jpoint .LE. sec%nb_point )
536         IF( icoord( iind,jpoint-isgn ) == itest .AND. icoord( iind,jpoint ) == itest )THEN ; jpoint=jpoint+isgn
537         ELSE                                                                               ; EXIT
538         ENDIF
539     ENDDO 
540
541     IF( cdextr=='bot_list')THEN ; istart=jpoint-1 ; iend=sec%nb_point
542     ELSE                        ; istart=1        ; iend=jpoint+1
543     ENDIF
544
545     sec%listPoint(1:1+iend-istart)%I = icoord(1,istart:iend)
546     sec%listPoint(1:1+iend-istart)%J = icoord(2,istart:iend)
547     sec%direction(1:1+iend-istart)   = idirec(istart:iend)
548     sec%nb_point                     = iend-istart+1
549     
550     IF( ld_debug )THEN
551        WRITE(numout,*)'      Number of points after removepoints :',sec%nb_point
552        WRITE(numout,*)'      sec%direction after removepoints :',sec%direction(1:sec%nb_point)
553     ENDIF
554      !
555   END SUBROUTINE removepoints
556
557
558   SUBROUTINE transport(sec,ld_debug,jsec)
559     !!-------------------------------------------------------------------------------------------
560     !!                     ***  ROUTINE transport  ***
561     !!
562     !!  Purpose ::  Compute the transport for each point in a section
563     !!
564     !!  Method  ::  Loop over each segment, and each vertical level and add the transport
565     !!              Be aware :           
566     !!              One section is a sum of segments
567     !!              One segment is defined by 2 consecutive points in sec%listPoint
568     !!              All points of sec%listPoint are positioned on the F-point of the cell
569     !!
570     !!              There are two loops:                 
571     !!              loop on the segment between 2 nodes
572     !!              loop on the level jk !!
573     !!
574     !!  Output  ::  Arrays containing the volume,density,heat,salt transports for each i
575     !!              point in a section, summed over each nn_dct.
576     !!
577     !!-------------------------------------------------------------------------------------------
578     TYPE(SECTION),INTENT(INOUT) :: sec
579     LOGICAL      ,INTENT(IN)    :: ld_debug
580     INTEGER      ,INTENT(IN)    :: jsec        ! numeric identifier of section
581     !
582     INTEGER ::   jk, jseg, jclass,jl, isgnu, isgnv    ! loop on level/segment/classes/ice categories
583     REAL(wp)::   zumid, zvmid, zumid_ice, zvmid_ice   ! U/V ocean & ice velocity on a cell segment
584     REAL(wp)::   zTnorm                               ! transport of velocity through one cell's sides
585     REAL(wp)::   ztn, zsn, zrhoi, zrhop, zsshn, zdep  ! temperature/salinity/potential density/ssh/depth at u/v point
586     TYPE(POINT_SECTION) ::   k
587      !!--------------------------------------------------------
588      !
589      IF( ld_debug )WRITE(numout,*)'      Compute transport'
590
591      !---------------------------!
592      !  COMPUTE TRANSPORT        !
593      !---------------------------!
594      IF(sec%nb_point .NE. 0)THEN   
595
596         !----------------------------------------------------------------------------------------------------
597         !Compute sign for velocities:
598         !
599         !convention:
600         !   non horizontal section: direction + is toward left hand of section
601         !       horizontal section: direction + is toward north of section
602         !
603         !
604         !       slopeSection < 0     slopeSection > 0       slopeSection=inf            slopeSection=0
605         !       ----------------      -----------------     ---------------             --------------
606         !
607         !   isgnv=1         direction +     
608         !  ______         _____             ______                                                   
609         !        |           //|            |                  |                         direction +   
610         !        | isgnu=1  // |            |isgnu=1           |isgnu=1                     /|\
611         !        |_______  //         ______|    \\            | ---\                        |
612         !               |             | isgnv=-1  \\ |         | ---/ direction +       ____________
613         !               |             |          __\\|         |                   
614         !               |             |     direction +        |                      isgnv=1                                 
615         !                                                     
616         !----------------------------------------------------------------------------------------------------
617         isgnu = 1
618         IF( sec%slopeSection .GT. 0 ) THEN  ; isgnv = -1 
619         ELSE                                ; isgnv =  1
620         ENDIF
621         IF( sec%slopeSection .GE. 9999. )     isgnv =  1
622
623         IF( ld_debug )write(numout,*)"sec%slopeSection isgnu isgnv ",sec%slopeSection,isgnu,isgnv
624
625         !--------------------------------------!
626         ! LOOP ON THE SEGMENT BETWEEN 2 NODES  !
627         !--------------------------------------!
628         DO jseg=1,MAX(sec%nb_point-1,0)
629             
630            !-------------------------------------------------------------------------------------------
631            ! Select the appropriate coordinate for computing the velocity of the segment
632            !
633            !                      CASE(0)                                    Case (2)
634            !                      -------                                    --------
635            !  listPoint(jseg)                 listPoint(jseg+1)       listPoint(jseg)  F(i,j)     
636            !      F(i,j)----------V(i+1,j)-------F(i+1,j)                               |
637            !                                                                            |
638            !                                                                            |
639            !                                                                            |
640            !                      Case (3)                                            U(i,j)
641            !                      --------                                              |
642            !                                                                            |
643            !  listPoint(jseg+1) F(i,j+1)                                                |
644            !                        |                                                   |
645            !                        |                                                   |
646            !                        |                                 listPoint(jseg+1) F(i,j-1)
647            !                        |                                           
648            !                        |                                           
649            !                     U(i,j+1)                                           
650            !                        |                                       Case(1)     
651            !                        |                                       ------     
652            !                        |                                           
653            !                        |                 listPoint(jseg+1)             listPoint(jseg)                           
654            !                        |                 F(i-1,j)-----------V(i,j) -------f(jseg)                           
655            ! listPoint(jseg)     F(i,j)
656            !
657            !-------------------------------------------------------------------------------------------
658
659            SELECT CASE( sec%direction(jseg) )
660            CASE(0)   ;    k = sec%listPoint(jseg)
661            CASE(1)   ;    k = POINT_SECTION(sec%listPoint(jseg)%I+1,sec%listPoint(jseg)%J)
662            CASE(2)   ;    k = sec%listPoint(jseg)
663            CASE(3)   ;    k = POINT_SECTION(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J+1)
664            END SELECT
665
666            !---------------------------|
667            !     LOOP ON THE LEVEL     |
668            !---------------------------|
669            DO jk = 1, mbkt(k%I,k%J)            !Sum of the transport on the vertical
670            !           ! compute temperature, salinity, insitu & potential density, ssh and depth at U/V point
671            SELECT CASE( sec%direction(jseg) )
672               CASE(0,1) 
673                  ztn   = interp(k%I,k%J,jk,'V',tsn(:,:,:,jp_tem) ) 
674                  zsn   = interp(k%I,k%J,jk,'V',tsn(:,:,:,jp_sal) ) 
675                  zrhop = interp(k%I,k%J,jk,'V',rhop) 
676                  zrhoi = interp(k%I,k%J,jk,'V',rhd*rau0+rau0) 
677                  zsshn =  0.5*( sshn(k%I,k%J) + sshn(k%I,k%J+1)    ) * vmask(k%I,k%J,1) 
678               CASE(2,3) 
679                  ztn   = interp(k%I,k%J,jk,'U',tsn(:,:,:,jp_tem) ) 
680                  zsn   = interp(k%I,k%J,jk,'U',tsn(:,:,:,jp_sal) ) 
681                  zrhop = interp(k%I,k%J,jk,'U',rhop) 
682                  zrhoi = interp(k%I,k%J,jk,'U',rhd*rau0+rau0) 
683                  zsshn =  0.5*( sshn(k%I,k%J) + sshn(k%I+1,k%J)    ) * umask(k%I,k%J,1) 
684               END SELECT 
685               !
686               zdep= gdept_n(k%I,k%J,jk) 
687 
688               SELECT CASE( sec%direction(jseg) )                !compute velocity with the correct direction
689               CASE(0,1)   
690                  zumid=0._wp
691                  zvmid=isgnv*vn(k%I,k%J,jk)*vmask(k%I,k%J,jk) 
692               CASE(2,3) 
693                  zumid=isgnu*un(k%I,k%J,jk)*umask(k%I,k%J,jk) 
694                  zvmid=0._wp
695               END SELECT 
696 
697               !zTnorm=transport through one cell;
698               !velocity* cell's length * cell's thickness
699               zTnorm = zumid*e2u(k%I,k%J) * e3u_n(k%I,k%J,jk)     & 
700                  &   + zvmid*e1v(k%I,k%J) * e3v_n(k%I,k%J,jk) 
701
702!!gm  THIS is WRONG  no transport due to ssh in linear free surface case !!!!!
703               IF( ln_linssh ) THEN              !add transport due to free surface
704                  IF( jk==1 ) THEN
705                     zTnorm = zTnorm + zumid* e2u(k%I,k%J) * zsshn * umask(k%I,k%J,jk)   & 
706                        &            + zvmid* e1v(k%I,k%J) * zsshn * vmask(k%I,k%J,jk) 
707                  ENDIF
708               ENDIF
709!!gm end
710              !COMPUTE TRANSPORT 
711 
712              transports_3d(1,jsec,jseg,jk) = transports_3d(1,jsec,jseg,jk) + zTnorm 
713 
714              IF( sec%llstrpond ) THEN
715                 transports_3d(2,jsec,jseg,jk) = transports_3d(2,jsec,jseg,jk)  + zTnorm * ztn * zrhop * rcp
716                 transports_3d(3,jsec,jseg,jk) = transports_3d(3,jsec,jseg,jk)  + zTnorm * zsn * zrhop * 0.001
717              ENDIF
718   
719           END DO !end of loop on the level
720
721#if defined key_si3
722
723           !ICE CASE   
724           !------------
725           IF( sec%ll_ice_section )THEN
726              SELECT CASE (sec%direction(jseg))
727              CASE(0)
728                 zumid_ice = 0
729                 zvmid_ice =  isgnv*0.5*(v_ice(k%I,k%J+1)+v_ice(k%I+1,k%J+1))
730              CASE(1)
731                 zumid_ice = 0
732                 zvmid_ice =  isgnv*0.5*(v_ice(k%I,k%J+1)+v_ice(k%I+1,k%J+1))
733              CASE(2)
734                 zvmid_ice = 0
735                 zumid_ice =  isgnu*0.5*(u_ice(k%I+1,k%J)+u_ice(k%I+1,k%J+1))
736              CASE(3)
737                 zvmid_ice = 0
738                 zumid_ice =  isgnu*0.5*(u_ice(k%I+1,k%J)+u_ice(k%I+1,k%J+1))
739              END SELECT
740   
741              zTnorm=zumid_ice*e2u(k%I,k%J)+zvmid_ice*e1v(k%I,k%J)
742
743#if defined key_si3
744              DO jl=1,jpl
745                 transports_2d(1,jsec,jseg) = transports_2d(1,jsec,jseg) + (zTnorm)*       &
746                                    a_i(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J,jl) *  &
747                                  ( h_i(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J,jl) +  &
748                                    h_s(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J,jl) )
749                                   
750                 transports_2d(2,jsec,jseg) = transports_2d(2,jsec,jseg) + (zTnorm)*   &
751                                    a_i(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J,jl)
752              END DO
753#endif
754   
755           ENDIF !end of ice case
756#endif
757 
758        END DO !end of loop on the segment
759
760     ENDIF !end of sec%nb_point =0 case
761     !
762  END SUBROUTINE transport
763
764
765  SUBROUTINE dia_dct_sum(sec,jsec) 
766     !!-------------------------------------------------------------
767     !! Purpose: Average the transport over nn_dctwri time steps 
768     !! and sum over the density/salinity/temperature/depth classes
769     !!
770     !! Method:   Sum over relevant grid cells to obtain values 
771     !!           for each class
772     !!              There are several loops:                 
773     !!              loop on the segment between 2 nodes
774     !!              loop on the level jk
775     !!              loop on the density/temperature/salinity/level classes
776     !!              test on the density/temperature/salinity/level
777     !!
778     !!  Note:    Transport through a given section is equal to the sum of transports
779     !!           computed on each proc.
780     !!           On each proc,transport is equal to the sum of transport computed through
781     !!           segments linking each point of sec%listPoint  with the next one.   
782     !!
783     !!-------------------------------------------------------------
784     TYPE(SECTION),INTENT(INOUT) :: sec 
785     INTEGER      ,INTENT(IN)    :: jsec        ! numeric identifier of section
786 
787     TYPE(POINT_SECTION) :: k 
788     INTEGER  :: jk,jseg,jclass                        ! dummy variables for looping on level/segment/classes 
789     REAL(wp) :: ztn, zsn, zrhoi, zrhop, zsshn, zdep ! temperature/salinity/ssh/potential density /depth at u/v point
790     !!-------------------------------------------------------------
791 
792     !! Sum the relevant segments to obtain values for each class
793     IF(sec%nb_point .NE. 0)THEN   
794 
795        !--------------------------------------!
796        ! LOOP ON THE SEGMENT BETWEEN 2 NODES  !
797        !--------------------------------------!
798        DO jseg=1,MAX(sec%nb_point-1,0) 
799           
800           !-------------------------------------------------------------------------------------------
801           ! Select the appropriate coordinate for computing the velocity of the segment
802           !
803           !                      CASE(0)                                    Case (2)
804           !                      -------                                    --------
805           !  listPoint(jseg)                 listPoint(jseg+1)       listPoint(jseg)  F(i,j)       
806           !      F(i,j)----------V(i+1,j)-------F(i+1,j)                               |
807           !                                                                            |
808           !                                                                            |
809           !                                                                            |
810           !                      Case (3)                                            U(i,j)
811           !                      --------                                              |
812           !                                                                            |
813           !  listPoint(jseg+1) F(i,j+1)                                                |
814           !                        |                                                   |
815           !                        |                                                   |
816           !                        |                                 listPoint(jseg+1) F(i,j-1)
817           !                        |                                             
818           !                        |                                             
819           !                     U(i,j+1)                                             
820           !                        |                                       Case(1)     
821           !                        |                                       ------       
822           !                        |                                             
823           !                        |                 listPoint(jseg+1)             listPoint(jseg)                           
824           !                        |                 F(i-1,j)-----------V(i,j) -------f(jseg)                           
825           ! listPoint(jseg)     F(i,j)
826           
827           !-------------------------------------------------------------------------------------------
828 
829           SELECT CASE( sec%direction(jseg) ) 
830           CASE(0)  ;   k = sec%listPoint(jseg) 
831           CASE(1)  ;   k = POINT_SECTION(sec%listPoint(jseg)%I+1,sec%listPoint(jseg)%J) 
832           CASE(2)  ;   k = sec%listPoint(jseg) 
833           CASE(3)  ;   k = POINT_SECTION(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J+1) 
834           END SELECT 
835 
836           !---------------------------|
837           !     LOOP ON THE LEVEL     |
838           !---------------------------|
839           !Sum of the transport on the vertical 
840           DO jk=1,mbkt(k%I,k%J) 
841 
842              ! compute temperature, salinity, insitu & potential density, ssh and depth at U/V point
843              SELECT CASE( sec%direction(jseg) ) 
844              CASE(0,1) 
845                 ztn   = interp(k%I,k%J,jk,'V',tsn(:,:,:,jp_tem) ) 
846                 zsn   = interp(k%I,k%J,jk,'V',tsn(:,:,:,jp_sal) ) 
847                 zrhop = interp(k%I,k%J,jk,'V',rhop) 
848                 zrhoi = interp(k%I,k%J,jk,'V',rhd*rau0+rau0) 
849
850              CASE(2,3) 
851                 ztn   = interp(k%I,k%J,jk,'U',tsn(:,:,:,jp_tem) ) 
852                 zsn   = interp(k%I,k%J,jk,'U',tsn(:,:,:,jp_sal) ) 
853                 zrhop = interp(k%I,k%J,jk,'U',rhop) 
854                 zrhoi = interp(k%I,k%J,jk,'U',rhd*rau0+rau0) 
855                 zsshn =  0.5*( sshn(k%I,k%J)    + sshn(k%I+1,k%J)    ) * umask(k%I,k%J,1) 
856              END SELECT
857 
858              zdep= gdept_n(k%I,k%J,jk) 
859 
860              !-------------------------------
861              !  LOOP ON THE DENSITY CLASSES |
862              !-------------------------------
863              !The computation is made for each density/temperature/salinity/depth class
864              DO jclass=1,MAX(1,sec%nb_class-1) 
865 
866                 !----------------------------------------------!
867                 !TEST ON THE DENSITY/SALINITY/TEMPERATURE/LEVEL! 
868                 !----------------------------------------------!
869
870                 IF ( (                                                    & 
871                    ((( zrhop .GE. (sec%zsigp(jclass)+1000.  )) .AND.      & 
872                    (   zrhop .LE. (sec%zsigp(jclass+1)+1000. ))) .OR.     & 
873                    ( sec%zsigp(jclass) .EQ. 99.)) .AND.                   & 
874 
875                    ((( zrhoi .GE. (sec%zsigi(jclass) + 1000.  )) .AND.    & 
876                    (   zrhoi .LE. (sec%zsigi(jclass+1)+1000. ))) .OR.     & 
877                    ( sec%zsigi(jclass) .EQ. 99.)) .AND.                   & 
878 
879                    ((( zsn .GT. sec%zsal(jclass)) .AND.                   & 
880                    (   zsn .LE. sec%zsal(jclass+1))) .OR.                 & 
881                    ( sec%zsal(jclass) .EQ. 99.)) .AND.                    & 
882 
883                    ((( ztn .GE. sec%ztem(jclass)) .AND.                   & 
884                    (   ztn .LE. sec%ztem(jclass+1))) .OR.                 & 
885                    ( sec%ztem(jclass) .EQ.99.)) .AND.                     & 
886 
887                    ((( zdep .GE. sec%zlay(jclass)) .AND.                & 
888                    (   zdep .LE. sec%zlay(jclass+1))) .OR.              & 
889                    ( sec%zlay(jclass) .EQ. 99. ))                         & 
890                                                                   ))   THEN 
891 
892                    !SUM THE TRANSPORTS FOR EACH CLASSES FOR THE POSITIVE AND NEGATIVE DIRECTIONS
893                    !----------------------------------------------------------------------------
894                    IF (transports_3d(1,jsec,jseg,jk) .GE. 0.0) THEN 
895                       sec%transport(1,jclass) = sec%transport(1,jclass)+transports_3d(1,jsec,jseg,jk)*1.E-6 
896                    ELSE
897                       sec%transport(2,jclass) = sec%transport(2,jclass)+transports_3d(1,jsec,jseg,jk)*1.E-6 
898                    ENDIF
899                    IF( sec%llstrpond )THEN
900 
901                       IF ( transports_3d(2,jsec,jseg,jk) .GE. 0.0 ) THEN
902                          sec%transport(3,jclass) = sec%transport(3,jclass)+transports_3d(2,jsec,jseg,jk) 
903                       ELSE
904                          sec%transport(4,jclass) = sec%transport(4,jclass)+transports_3d(2,jsec,jseg,jk) 
905                       ENDIF
906 
907                       IF ( transports_3d(3,jsec,jseg,jk) .GE. 0.0 ) THEN
908                          sec%transport(5,jclass) = sec%transport(5,jclass)+transports_3d(3,jsec,jseg,jk) 
909                       ELSE
910                          sec%transport(6,jclass) = sec%transport(6,jclass)+transports_3d(3,jsec,jseg,jk) 
911                       ENDIF
912 
913                    ELSE
914                       sec%transport( 3,jclass) = 0._wp 
915                       sec%transport( 4,jclass) = 0._wp 
916                       sec%transport( 5,jclass) = 0._wp 
917                       sec%transport( 6,jclass) = 0._wp 
918                    ENDIF
919 
920                 ENDIF ! end of test if point is in class
921   
922              END DO ! end of loop on the classes
923 
924           END DO ! loop over jk
925 
926#if defined key_si3 
927 
928           !ICE CASE     
929           IF( sec%ll_ice_section )THEN
930 
931              IF ( transports_2d(1,jsec,jseg) .GE. 0.0 ) THEN
932                 sec%transport( 7,1) = sec%transport( 7,1)+transports_2d(1,jsec,jseg)*1.E-6 
933              ELSE
934                 sec%transport( 8,1) = sec%transport( 8,1)+transports_2d(1,jsec,jseg)*1.E-6 
935              ENDIF
936 
937              IF ( transports_2d(3,jsec,jseg) .GE. 0.0 ) THEN
938                 sec%transport( 9,1) = sec%transport( 9,1)+transports_2d(2,jsec,jseg)*1.E-6 
939              ELSE
940                 sec%transport(10,1) = sec%transport(10,1)+transports_2d(2,jsec,jseg)*1.E-6 
941              ENDIF
942 
943           ENDIF !end of ice case
944#endif
945 
946        END DO !end of loop on the segment
947 
948     ELSE  !if sec%nb_point =0
949        sec%transport(1:2,:)=0. 
950        IF (sec%llstrpond) sec%transport(3:6,:)=0. 
951        IF (sec%ll_ice_section) sec%transport(7:10,:)=0. 
952     ENDIF !end of sec%nb_point =0 case
953 
954  END SUBROUTINE dia_dct_sum 
955
956
957  SUBROUTINE dia_dct_wri(kt,ksec,sec)
958     !!-------------------------------------------------------------
959     !! Write transport output in numdct
960     !!
961     !! Purpose: Write  transports in ascii files
962     !!
963     !! Method:
964     !!        1. Write volume transports in "volume_transport"
965     !!           Unit: Sv : area * Velocity / 1.e6
966     !!
967     !!        2. Write heat transports in "heat_transport"
968     !!           Unit: Peta W : area * Velocity * T * rhop * Cp * 1.e-15
969     !!
970     !!        3. Write salt transports in "salt_transport"
971     !!           Unit: 10^9 Kg/m^2/s : area * Velocity * S * rhop * 1.e-9
972     !!
973     !!-------------------------------------------------------------
974     !!arguments
975     INTEGER, INTENT(IN)          :: kt          ! time-step
976     TYPE(SECTION), INTENT(INOUT) :: sec         ! section to write   
977     INTEGER ,INTENT(IN)          :: ksec        ! section number
978
979     !!local declarations
980     INTEGER               :: jclass             ! Dummy loop
981     CHARACTER(len=2)      :: classe             ! Classname
982     REAL(wp)              :: zbnd1,zbnd2        ! Class bounds
983     REAL(wp)              :: zslope             ! section's slope coeff
984     !
985     REAL(wp), DIMENSION(nb_type_class)::   zsumclasses   ! 1D workspace
986     !!-------------------------------------------------------------
987
988     zsumclasses(:)=0._wp
989     zslope = sec%slopeSection       
990
991 
992     DO jclass=1,MAX(1,sec%nb_class-1)
993
994        classe   = 'N       '
995        zbnd1   = 0._wp
996        zbnd2   = 0._wp
997        zsumclasses(1:nb_type_class)=zsumclasses(1:nb_type_class)+sec%transport(1:nb_type_class,jclass)
998
999   
1000        !insitu density classes transports
1001        IF( ( sec%zsigi(jclass)   .NE. 99._wp ) .AND. &
1002            ( sec%zsigi(jclass+1) .NE. 99._wp )       )THEN
1003           classe = 'DI       '
1004           zbnd1 = sec%zsigi(jclass)
1005           zbnd2 = sec%zsigi(jclass+1)
1006        ENDIF
1007        !potential density classes transports
1008        IF( ( sec%zsigp(jclass)   .NE. 99._wp ) .AND. &
1009            ( sec%zsigp(jclass+1) .NE. 99._wp )       )THEN
1010           classe = 'DP      '
1011           zbnd1 = sec%zsigp(jclass)
1012           zbnd2 = sec%zsigp(jclass+1)
1013        ENDIF
1014        !depth classes transports
1015        IF( ( sec%zlay(jclass)    .NE. 99._wp ) .AND. &
1016            ( sec%zlay(jclass+1)  .NE. 99._wp )       )THEN
1017           classe = 'Z       '
1018           zbnd1 = sec%zlay(jclass)
1019           zbnd2 = sec%zlay(jclass+1)
1020        ENDIF
1021        !salinity classes transports
1022        IF( ( sec%zsal(jclass) .NE. 99._wp    ) .AND. &
1023            ( sec%zsal(jclass+1) .NE. 99._wp  )       )THEN
1024           classe = 'S       '
1025           zbnd1 = sec%zsal(jclass)
1026           zbnd2 = sec%zsal(jclass+1)   
1027        ENDIF
1028        !temperature classes transports
1029        IF( ( sec%ztem(jclass) .NE. 99._wp     ) .AND. &
1030            ( sec%ztem(jclass+1) .NE. 99._wp     )       ) THEN
1031           classe = 'T       '
1032           zbnd1 = sec%ztem(jclass)
1033           zbnd2 = sec%ztem(jclass+1)
1034        ENDIF
1035                 
1036        !write volume transport per class
1037        WRITE(numdct_vol,118) ndastp,kt,ksec,sec%name,zslope, &
1038                              jclass,classe,zbnd1,zbnd2,&
1039                              sec%transport(1,jclass),sec%transport(2,jclass), &
1040                              sec%transport(1,jclass)+sec%transport(2,jclass)
1041
1042        IF( sec%llstrpond )THEN
1043
1044           !write heat transport per class:
1045           WRITE(numdct_heat,119) ndastp,kt,ksec,sec%name,zslope,  &
1046                              jclass,classe,zbnd1,zbnd2,&
1047                              sec%transport(3,jclass)*1.e-15,sec%transport(4,jclass)*1.e-15, &
1048                              ( sec%transport(3,jclass)+sec%transport(4,jclass) )*1.e-15
1049           !write salt transport per class
1050           WRITE(numdct_salt,119) ndastp,kt,ksec,sec%name,zslope,  &
1051                              jclass,classe,zbnd1,zbnd2,&
1052                              sec%transport(5,jclass)*1.e-9,sec%transport(6,jclass)*1.e-9,&
1053                              (sec%transport(5,jclass)+sec%transport(6,jclass))*1.e-9
1054        ENDIF
1055
1056     ENDDO
1057
1058     zbnd1 = 0._wp
1059     zbnd2 = 0._wp
1060     jclass=0
1061
1062     !write total volume transport
1063     WRITE(numdct_vol,118) ndastp,kt,ksec,sec%name,zslope, &
1064                           jclass,"total",zbnd1,zbnd2,&
1065                           zsumclasses(1),zsumclasses(2),zsumclasses(1)+zsumclasses(2)
1066
1067     IF( sec%llstrpond )THEN
1068
1069        !write total heat transport
1070        WRITE(numdct_heat,119) ndastp,kt,ksec,sec%name,zslope, &
1071                           jclass,"total",zbnd1,zbnd2,&
1072                           zsumclasses(3)*1.e-15,zsumclasses(4)*1.e-15,&
1073                           (zsumclasses(3)+zsumclasses(4) )*1.e-15
1074        !write total salt transport
1075        WRITE(numdct_salt,119) ndastp,kt,ksec,sec%name,zslope, &
1076                           jclass,"total",zbnd1,zbnd2,&
1077                           zsumclasses(5)*1.e-9,zsumclasses(6)*1.e-9,&
1078                           (zsumclasses(5)+zsumclasses(6))*1.e-9
1079     ENDIF
1080
1081     
1082     IF ( sec%ll_ice_section) THEN
1083        !write total ice volume transport
1084        WRITE(numdct_vol,118) ndastp,kt,ksec,sec%name,zslope,&
1085                              jclass,"ice_vol",zbnd1,zbnd2,&
1086                              sec%transport(7,1),sec%transport(8,1),&
1087                              sec%transport(7,1)+sec%transport(8,1)
1088        !write total ice surface transport
1089        WRITE(numdct_vol,118) ndastp,kt,ksec,sec%name,zslope,&
1090                              jclass,"ice_surf",zbnd1,zbnd2,&
1091                              sec%transport(9,1),sec%transport(10,1), &
1092                              sec%transport(9,1)+sec%transport(10,1) 
1093      ENDIF
1094                                             
1095118   FORMAT(I8,1X,I8,1X,I4,1X,A30,1X,f9.2,1X,I4,3X,A8,1X,2F12.4,5X,3F12.4)
1096119   FORMAT(I8,1X,I8,1X,I4,1X,A30,1X,f9.2,1X,I4,3X,A8,1X,2F12.4,5X,3E15.6)
1097      !
1098   END SUBROUTINE dia_dct_wri
1099
1100
1101   FUNCTION interp(ki, kj, kk, cd_point, ptab)
1102  !!----------------------------------------------------------------------
1103  !!
1104  !!   Purpose: compute temperature/salinity/density at U-point or V-point
1105  !!   --------
1106  !!
1107  !!   Method:
1108  !!   ------
1109  !!
1110  !!   ====> full step and partial step
1111  !!
1112  !!
1113  !!    |    I          |    I+1           |    Z=temperature/salinity/density at U-poinT
1114  !!    |               |                  |
1115  !!  ----------------------------------------  1. Veritcal interpolation: compute zbis
1116  !!    |               |                  |       interpolation between ptab(I,J,K) and ptab(I,J,K+1)
1117  !!    |               |                  |       zbis =
1118  !!    |               |                  |      [ e3w(I+1,J,K)*ptab(I,J,K) + ( e3w(I,J,K) - e3w(I+1,J,K) ) * ptab(I,J,K-1) ]
1119  !!    |               |                  |      /[ e3w(I+1,J,K) + e3w(I,J,K) - e3w(I+1,J,K) ]
1120  !!    |               |                  |
1121  !!    |               |                  |    2. Horizontal interpolation: compute value at U/V point
1122  !!K-1 | ptab(I,J,K-1) |                  |       interpolation between zbis and ptab(I+1,J,K) 
1123  !!    |     .         |                  |
1124  !!    |     .         |                  |       interp = ( 0.5*zet2*zbis + 0.5*zet1*ptab(I+1,J,K) )/(0.5*zet2+0.5*zet1)
1125  !!    |     .         |                  |
1126  !!  ------------------------------------------
1127  !!    |     .         |                  |
1128  !!    |     .         |                  |
1129  !!    |     .         |                  |
1130  !!K   |    zbis.......U...ptab(I+1,J,K)  |
1131  !!    |     .         |                  |
1132  !!    | ptab(I,J,K)   |                  |
1133  !!    |               |------------------|
1134  !!    |               | partials         |
1135  !!    |               |  steps           |
1136  !!  -------------------------------------------
1137  !!    <----zet1------><----zet2--------->
1138  !!
1139  !!
1140  !!   ====>  s-coordinate
1141  !!     
1142  !!    |                |                  |   1. Compute distance between T1 and U points: SQRT( zdep1^2 + (0.5 * zet1 )^2
1143  !!    |                |                  |      Compute distance between T2 and U points: SQRT( zdep2^2 + (0.5 * zet2 )^2
1144  !!    |                | ptab(I+1,J,K)    |
1145  !!    |                |      T2          |   2. Interpolation between  T1 and T2 values at U point
1146  !!    |                |      ^           |   
1147  !!    |                |      | zdep2     |   
1148  !!    |                |      |           |   
1149  !!    |       ^        U      v           |
1150  !!    |       |        |                  |
1151  !!    |       | zdep1  |                  |   
1152  !!    |       v        |                  |
1153  !!    |      T1        |                  |
1154  !!    | ptab(I,J,K)    |                  |
1155  !!    |                |                  |
1156  !!    |                |                  |
1157  !!
1158  !!    <----zet1--------><----zet2--------->
1159  !!
1160  !!----------------------------------------------------------------------
1161  !*arguments
1162  INTEGER, INTENT(IN)                          :: ki, kj, kk   ! coordinate of point
1163  CHARACTER(len=1), INTENT(IN)                 :: cd_point     ! type of point (U, V)
1164  REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(IN) :: ptab         ! variable to compute at (ki, kj, kk )
1165  REAL(wp)                                     :: interp       ! interpolated variable
1166
1167  !*local declations
1168  INTEGER :: ii1, ij1, ii2, ij2                                ! local integer
1169  REAL(wp):: ze3t, ze3, zwgt1, zwgt2, zbis, zdepu            ! local real
1170  REAL(wp):: zet1, zet2                                        ! weight for interpolation
1171  REAL(wp):: zdep1,zdep2                                       ! differences of depth
1172  REAL(wp):: zmsk                                              ! mask value
1173  !!----------------------------------------------------------------------
1174
1175  IF( cd_point=='U' )THEN
1176     ii1 = ki    ; ij1 = kj 
1177     ii2 = ki+1  ; ij2 = kj 
1178
1179     zet1=e1t(ii1,ij1)
1180     zet2=e1t(ii2,ij2)
1181     zmsk=umask(ii1,ij1,kk)
1182 
1183
1184  ELSE ! cd_point=='V'
1185     ii1 = ki    ; ij1 = kj 
1186     ii2 = ki    ; ij2 = kj+1 
1187
1188     zet1=e2t(ii1,ij1)
1189     zet2=e2t(ii2,ij2)
1190     zmsk=vmask(ii1,ij1,kk)
1191
1192  ENDIF
1193
1194  IF( ln_sco )THEN   ! s-coordinate case
1195
1196     zdepu = ( gdept_n(ii1,ij1,kk) +  gdept_n(ii2,ij2,kk) ) * 0.5_wp 
1197     zdep1 = gdept_n(ii1,ij1,kk) - zdepu
1198     zdep2 = gdept_n(ii2,ij2,kk) - zdepu
1199
1200     ! weights
1201     zwgt1 = SQRT( ( 0.5 * zet1 ) * ( 0.5 * zet1 ) + ( zdep1 * zdep1 ) )
1202     zwgt2 = SQRT( ( 0.5 * zet2 ) * ( 0.5 * zet2 ) + ( zdep2 * zdep2 ) )
1203 
1204     ! result
1205     interp = zmsk * ( zwgt2 *  ptab(ii1,ij1,kk) + zwgt1 *  ptab(ii1,ij1,kk) ) / ( zwgt2 + zwgt1 )   
1206
1207
1208  ELSE       ! full step or partial step case
1209
1210     ze3t  = e3t_n(ii2,ij2,kk) - e3t_n(ii1,ij1,kk) 
1211     zwgt1 = ( e3w_n(ii2,ij2,kk) - e3w_n(ii1,ij1,kk) ) / e3w_n(ii2,ij2,kk)
1212     zwgt2 = ( e3w_n(ii1,ij1,kk) - e3w_n(ii2,ij2,kk) ) / e3w_n(ii1,ij1,kk)
1213
1214     IF(kk .NE. 1)THEN
1215
1216        IF( ze3t >= 0. )THEN 
1217           ! zbis
1218           zbis = ptab(ii2,ij2,kk) + zwgt1 * ( ptab(ii2,ij2,kk-1) - ptab(ii2,ij2,kk) ) 
1219           ! result
1220            interp = zmsk * ( zet2 * ptab(ii1,ij1,kk) + zet1 * zbis )/( zet1 + zet2 )
1221        ELSE
1222           ! zbis
1223           zbis = ptab(ii1,ij1,kk) + zwgt2 * ( ptab(ii1,ij1,kk-1) - ptab(ii1,ij2,kk) )
1224           ! result
1225           interp = zmsk * ( zet2 * zbis + zet1 * ptab(ii2,ij2,kk) )/( zet1 + zet2 )
1226        ENDIF   
1227
1228     ELSE
1229        interp = zmsk * (  zet2 * ptab(ii1,ij1,kk) + zet1 * ptab(ii2,ij2,kk) )/( zet1 + zet2 )
1230     ENDIF
1231
1232  ENDIF
1233      !
1234   END FUNCTION interp
1235
1236#else
1237   !!----------------------------------------------------------------------
1238   !!   Dummy module                                             
1239   !!----------------------------------------------------------------------
1240   LOGICAL, PUBLIC ::   ln_diadct = .FALSE.
1241CONTAINS
1242   SUBROUTINE dia_dct_init
1243      IMPLICIT NONE
1244   END SUBROUTINE dia_dct_init
1245   SUBROUTINE dia_dct( kt )
1246      IMPLICIT NONE
1247      INTEGER, INTENT(in) ::   kt
1248   END SUBROUTINE dia_dct
1249   !
1250#endif
1251
1252   !!======================================================================
1253END MODULE diadct
Note: See TracBrowser for help on using the repository browser.