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 branches/2012/dev_r3452_UKMO2_DIADCT/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

source: branches/2012/dev_r3452_UKMO2_DIADCT/NEMOGCM/NEMO/OPA_SRC/DIA/diadct.F90 @ 3501

Last change on this file since 3501 was 3501, checked in by rfurner, 12 years ago

changes to ordering of calculations

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