New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
diadct.F90 in NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/DIA – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/DIA/diadct.F90 @ 10965

Last change on this file since 10965 was 10965, checked in by davestorkey, 5 years ago

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : DIA and stpctl.F90. Just testing in ORCA1 so far.

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