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

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
diadct.F90 in branches/2011/dev_LOCEAN_CMCC_INGV_MERCATOR_2011/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

source: branches/2011/dev_LOCEAN_CMCC_INGV_MERCATOR_2011/NEMOGCM/NEMO/OPA_SRC/DIA/diadct.F90 @ 3106

Last change on this file since 3106 was 3106, checked in by cbricaud, 12 years ago

change tn and sn by tsn

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