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/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/DIA – NEMO

source: NEMO/branches/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/DIA/diadct.F90 @ 12622

Last change on this file since 12622 was 12622, checked in by techene, 4 years ago

all: add e3 substitute (sometimes it requires to add ze3t/u/v/w) and limit precompiled files lines to about 130 character

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