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_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/OCE/DIA – NEMO

source: NEMO/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/OCE/DIA/diadct.F90 @ 14219

Last change on this file since 14219 was 14219, checked in by mcastril, 4 years ago

Add Mixed Precision support by Oriol Tintó

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