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 trunk/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/DIA/diadct.F90 @ 3987

Last change on this file since 3987 was 3987, checked in by cbricaud, 11 years ago

bugfix diadct for ice transport ( LIM3 case ) ; see ticket 1080

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