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.
Changeset 11639 for branches/UKMO – NEMO

Changeset 11639 for branches/UKMO


Ignore:
Timestamp:
2019-10-02T13:13:03+02:00 (5 years ago)
Author:
rrenshaw
Message:

regional mean and transport diagnostics added for reanalysis

Location:
branches/UKMO/AMM15_v3_6_STABLE_package_reanalysis4/NEMOGCM/NEMO
Files:
2 added
9 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/AMM15_v3_6_STABLE_package_reanalysis4/NEMOGCM/NEMO/OPA_SRC/DIA/diaar5.F90

    r8058 r11639  
    3939   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:  ) ::   thick0       ! ocean thickness (interior domain) 
    4040   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sn0          ! initial salinity 
     41   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tn0          ! initial temperature 
     42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sshthster_mat         ! ssh_thermosteric height 
     43   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sshhlster_mat         ! ssh_halosteric height 
     44   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sshsteric_mat         ! ssh_steric height 
     45   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zbotpres_mat          ! bottom pressure 
    4146       
    4247   !! * Substitutions 
     
    5661      !!---------------------------------------------------------------------- 
    5762      ! 
    58       ALLOCATE( area(jpi,jpj), thick0(jpi,jpj) , sn0(jpi,jpj,jpk) , STAT=dia_ar5_alloc ) 
     63      ALLOCATE( area(jpi,jpj), thick0(jpi,jpj) , sn0(jpi,jpj,jpk), tn0(jpi,jpj,jpk) , & 
     64          & sshthster_mat(jpi,jpj),sshhlster_mat(jpi,jpj),sshsteric_mat(jpi,jpj), & 
     65          & zbotpres_mat(jpi,jpj),STAT=dia_ar5_alloc ) 
    5966      ! 
    6067      IF( lk_mpp             )   CALL mpp_sum ( dia_ar5_alloc ) 
     
    8592      CALL wrk_alloc( jpi , jpj , jpk        , zrhd      , zrhop    ) 
    8693      CALL wrk_alloc( jpi , jpj , jpk , jpts , ztsn                 ) 
     94       
     95      sshthster_mat(:,:) = 0._wp   
     96      sshhlster_mat(:,:) = 0._wp   
     97      sshsteric_mat(:,:) = 0._wp   
     98      zbotpres_mat(:,:)  = 0._wp   
    8799 
    88100      zarea_ssh(:,:) = area(:,:) * sshn(:,:) 
     
    121133      zssh_steric = - zarho / area_tot 
    122134      CALL iom_put( 'sshthster', zssh_steric ) 
     135      sshthster_mat(:,:) =  -zbotpres(:,:) 
     136      CALL iom_put( 'sshthster_mat', sshthster_mat ) 
     137 
     138      !                      
     139      ztsn(:,:,:,jp_tem) = tn0(:,:,:)                    ! thermohaline ssh 
     140      ztsn(:,:,:,jp_sal) = tsn(:,:,:,jp_sal)  
     141      CALL eos( ztsn, zrhd, fsdept_n(:,:,:) )                       ! now in situ density using initial temperature 
     142      ! 
     143      zbotpres(:,:) = 0._wp                        ! no atmospheric surface pressure, levitating sea-ice 
     144      DO jk = 1, jpkm1 
     145         zbotpres(:,:) = zbotpres(:,:) + fse3t(:,:,jk) * zrhd(:,:,jk) 
     146      END DO 
     147      IF( .NOT.lk_vvl ) THEN 
     148         IF ( ln_isfcav ) THEN 
     149            DO ji=1,jpi 
     150               DO jj=1,jpj 
     151                  zbotpres(ji,jj) = zbotpres(ji,jj) + sshn(ji,jj) * zrhd(ji,jj,mikt(ji,jj)) + riceload(ji,jj) 
     152               END DO 
     153            END DO 
     154         ELSE 
     155            zbotpres(:,:) = zbotpres(:,:) + sshn(:,:) * zrhd(:,:,1) 
     156         END IF 
     157      END IF 
     158      !                                          
     159      zarho = SUM( area(:,:) * zbotpres(:,:) )  
     160      IF( lk_mpp )   CALL mpp_sum( zarho ) 
     161      zssh_steric = - zarho / area_tot 
     162      CALL iom_put( 'sshhlster', zssh_steric ) 
     163      sshhlster_mat(:,:) = -zbotpres(:,:) 
     164      CALL iom_put( 'sshhlster_mat', sshhlster_mat ) 
     165       
     166 
    123167       
    124168      !                                         ! steric sea surface height 
     
    147191      zssh_steric = - zarho / area_tot 
    148192      CALL iom_put( 'sshsteric', zssh_steric ) 
     193      sshsteric_mat(:,:) = -zbotpres(:,:)  
     194      CALL iom_put( 'sshsteric_mat', sshsteric_mat ) 
    149195       
    150196      !                                         ! ocean bottom pressure 
    151197      zztmp = rau0 * grav * 1.e-4_wp               ! recover pressure from pressure anomaly and cover to dbar = 1.e4 Pa 
    152198      zbotpres(:,:) = zztmp * ( zbotpres(:,:) + sshn(:,:) + thick0(:,:) ) 
    153       CALL iom_put( 'botpres', zbotpres ) 
    154  
     199      zbotpres_mat(:,:) = zbotpres(:,:) 
     200      CALL iom_put( 'botpres', zbotpres_mat ) 
     201       
    155202      !                                         ! Mean density anomalie, temperature and salinity 
    156203      ztemp = 0._wp 
     
    211258      REAL(wp) ::   zztmp   
    212259      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   zsaldta   ! Jan/Dec levitus salinity 
     260      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   ztemdta   ! Jan/Dec levitus salinity 
    213261      ! reading initial file 
    214262      LOGICAL  ::   ln_tsd_init      !: T & S data flag 
     
    234282      ! 
    235283      CALL wrk_alloc( jpi , jpj , jpk, jpts, zsaldta ) 
     284      CALL wrk_alloc( jpi , jpj , jpk, jpts, ztemdta ) 
    236285      !                                      ! allocate dia_ar5 arrays 
    237286      IF( dia_ar5_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'dia_ar5_init : unable to allocate arrays' ) 
     
    253302      CALL iom_get  ( inum, jpdom_data, TRIM(sn_sal%clvar), zsaldta(:,:,:,2), 12 ) 
    254303      CALL iom_close( inum ) 
     304 
     305      CALL iom_open ( TRIM( cn_dir )//TRIM(sn_tem%clname), inum ) 
     306      CALL iom_get  ( inum, jpdom_data, TRIM(sn_tem%clvar), ztemdta(:,:,:,1), 1  ) 
     307      CALL iom_get  ( inum, jpdom_data, TRIM(sn_tem%clvar), ztemdta(:,:,:,2), 12 ) 
     308      CALL iom_close( inum ) 
    255309      sn0(:,:,:) = 0.5_wp * ( zsaldta(:,:,:,1) + zsaldta(:,:,:,2) )         
    256       sn0(:,:,:) = sn0(:,:,:) * tmask(:,:,:) 
     310      tn0(:,:,:) = 0.5_wp * ( ztemdta(:,:,:,1) + ztemdta(:,:,:,2) )         
     311      sn0(:,:,:) = sn0(:,:,:) * tmask(:,:,:)   
     312      tn0(:,:,:) = tn0(:,:,:) * tmask(:,:,:) 
    257313      IF( ln_zps ) THEN               ! z-coord. partial steps 
    258314         DO jj = 1, jpj               ! interpolation of salinity at the last ocean level (i.e. the partial step) 
     
    262318                  zztmp = ( gdept_1d(ik) - gdept_0(ji,jj,ik) ) / ( gdept_1d(ik) - gdept_1d(ik-1) ) 
    263319                  sn0(ji,jj,ik) = ( 1._wp - zztmp ) * sn0(ji,jj,ik) + zztmp * sn0(ji,jj,ik-1) 
     320                  tn0(ji,jj,ik) = ( 1._wp - zztmp ) * tn0(ji,jj,ik) + zztmp * tn0(ji,jj,ik-1) 
    264321               ENDIF 
    265322            END DO 
     
    268325      ! 
    269326      CALL wrk_dealloc( jpi , jpj , jpk, jpts, zsaldta ) 
     327      CALL wrk_dealloc( jpi , jpj , jpk, jpts, ztemdta ) 
    270328      ! 
    271329      IF( nn_timing == 1 )   CALL timing_stop('dia_ar5_init') 
  • branches/UKMO/AMM15_v3_6_STABLE_package_reanalysis4/NEMOGCM/NEMO/OPA_SRC/DIA/diadct.F90

    r10237 r11639  
    3535  USE phycst          ! physical constants 
    3636  USE in_out_manager  ! I/O manager 
     37  USE iom             ! I/0 library 
    3738  USE daymod          ! calendar 
    3839  USE dianam          ! build name of file 
     
    6566  !! * Shared module variables 
    6667  LOGICAL, PUBLIC, PARAMETER ::   lk_diadct = .TRUE.   !: model-data diagnostics flag 
     68  LOGICAL, PUBLIC ::   ln_dct_calc_noos_25h !: Calcuate noos 25 h means 
     69  LOGICAL, PUBLIC ::   ln_dct_calc_noos_hr !: Calcuate noos hourly means 
     70  ! JT 
     71  LOGICAL, PUBLIC ::   ln_dct_iom_cont !: Use IOM Output? 
     72  LOGICAL, PUBLIC ::   ln_dct_ascii    !: Output ascii or binary 
     73  LOGICAL, PUBLIC ::   ln_dct_h        !: Output hourly instantaneous or mean values 
     74  ! JT 
    6775 
    6876  !! * 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   INTEGER :: nn_dct_h    = 1     ! Frequency of computation for NOOS hourly files 
    73   INTEGER :: nn_dctwri_h = 1     ! Frequency of output for NOOS hourly files 
     77  INTEGER :: nn_dct        ! Frequency of computation 
     78  INTEGER :: nn_dctwri     ! Frequency of output 
     79  INTEGER :: nn_secdebug   ! Number of the section to debug 
     80  INTEGER :: nn_dct_h      ! Frequency of computation for NOOS hourly files 
     81  INTEGER :: nn_dctwri_h   ! Frequency of output for NOOS hourly files 
    7482    
    7583  INTEGER, PARAMETER :: nb_class_max  = 12   ! maximum number of classes, i.e. depth levels or density classes 
    76   INTEGER, PARAMETER :: nb_sec_max    = 30   ! maximum number of sections 
    77   INTEGER, PARAMETER :: nb_point_max  = 300  ! maximum number of points in a single section 
     84  INTEGER, PARAMETER :: nb_sec_max    = 100  ! maximum number of sections 
     85  INTEGER, PARAMETER :: nb_point_max  = 375  ! maximum number of points in a single section 
    7886  INTEGER, PARAMETER :: nb_type_class       = 14   ! types of calculations, i.e. pos transport, neg transport, heat transport, salt transport 
    7987  INTEGER, PARAMETER :: nb_3d_vars    = 5 
     
    134142     ALLOCATE(transports_3d_h(nb_3d_vars,nb_sec_max,nb_point_max,jpk), STAT=ierr(3) ) 
    135143     ALLOCATE(transports_2d_h(nb_2d_vars,nb_sec_max,nb_point_max)    , STAT=ierr(4) ) 
    136      ALLOCATE(z_hr_output(nb_sec_max,168,nb_class_max)               , STAT=ierr(5) ) ! 168 = 24 * 7days 
     144     ALLOCATE(z_hr_output(nb_sec_max,3,nb_class_max)                , STAT=ierr(5) ) 
    137145 
    138146     diadct_alloc = MAXVAL( ierr )  
     
    149157     !! 
    150158     !!--------------------------------------------------------------------- 
    151      NAMELIST/namdct/nn_dct,nn_dctwri,nn_secdebug 
    152      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     159     NAMELIST/namdct/nn_dct,ln_dct_h,nn_dctwri,ln_dct_ascii,nn_secdebug,ln_dct_calc_noos_25h,ln_dct_calc_noos_hr,ln_dct_iom_cont 
     160     INTEGER           ::   ios,jsec        ! Local integer output status for namelist read 
     161     CHARACTER(len=3)  ::   jsec_str        ! name of the jsec 
     162     LOGICAL       ::   verbose      
     163     verbose = .false. 
    153164 
    154165     IF( nn_timing == 1 )   CALL timing_start('dia_dct_init') 
     
    164175 
    165176     IF( ln_NOOS ) THEN 
    166         nn_dct=3600./rdt         ! hard coded for NOOS transects, to give 25 hour means  
     177 
     178        !Do calculation for daily, 25hourly mean every hour 
     179        nn_dct=3600./rdt         ! hard coded for NOOS transects, to give 25 hour means from hourly instantaneous values 
     180 
     181        !write out daily, 25hourly mean every day 
    167182        nn_dctwri=86400./rdt 
    168         nn_dct_h=1       ! hard coded for NOOS transects, to give hourly data 
     183 
     184 
     185        !nn_dct_h=1       ! hard coded for NOOS transects, to give hourly data     
     186        ! If you want hourly instantaneous values, you only do the calculation every 12 timesteps (if rdt = 300) 
     187        ! and output it every 12 time steps. For this, you set the ln_dct_h to be True, and it calcuates it automatically 
     188        ! if you want hourly mean values, set ln_dct_h to be False, and it will do the calculate every time step. 
     189        ! 
     190        !SELECT CASE( ln_dct_h ) 
     191        !   CASE(.TRUE.)   
     192        !      nn_dct_h=3600./rdt 
     193        !   CASE(.FALSE.) 
     194        !      nn_dct_h=1 
     195        !END SELECT 
     196         
     197        IF ( ln_dct_h ) THEN 
     198            nn_dct_h=3600./rdt 
     199        ELSE 
     200            nn_dct_h=1. 
     201        ENDIF     
     202         
     203        !JT write out hourly calculation every hour 
    169204        nn_dctwri_h=3600./rdt 
    170205     ENDIF 
    171206 
    172207     IF( lwp ) THEN 
     208       IF( verbose ) THEN 
    173209        WRITE(numout,*) " " 
    174210        WRITE(numout,*) "diadct_init: compute transports through sections " 
    175211        WRITE(numout,*) "~~~~~~~~~~~~~~~~~~~~~" 
    176212        IF( ln_NOOS ) THEN 
     213           WRITE(numout,*) "       Calculate NOOS hourly output: ln_dct_calc_noos_hr = ",ln_dct_calc_noos_hr 
     214           WRITE(numout,*) "       Calculate NOOS 25 hour mean output: ln_dct_calc_noos_hr = ",ln_dct_calc_noos_25h 
     215           WRITE(numout,*) "       Use IOM Output: ln_dct_iom_cont = ",ln_dct_iom_cont 
     216           WRITE(numout,*) "       Output in ASCII (True) or Binary (False): ln_dct_ascii = ",ln_dct_ascii 
     217           WRITE(numout,*) "       Frequency of hourly computation - instantaneous (TRUE) or hourly mean (FALSE): ln_dct_h  = ",ln_dct_h 
     218 
    177219           WRITE(numout,*) "       Frequency of computation hard coded to be every hour: nn_dct    = ",nn_dct 
    178220           WRITE(numout,*) "       Frequency of write hard coded to average 25 instantaneous hour values: nn_dctwri = ",nn_dctwri 
    179            WRITE(numout,*) "       Frequency of hourly computation hard coded to be every timestep: nn_dct_h  = ",nn_dct_h 
     221           WRITE(numout,*) "       Frequency of hourly computation (timestep) : nn_dct_h  = ",nn_dct_h 
     222           WRITE(numout,*) "       Frequency of hourly computation Not hard coded to be every timestep, or : nn_dct_h  = ",nn_dct_h 
    180223           WRITE(numout,*) "       Frequency of hourly write hard coded to every hour: nn_dctwri_h = ",nn_dctwri_h 
    181224        ELSE 
     
    183226           WRITE(numout,*) "       Frequency of write:       nn_dctwri = ",nn_dctwri 
    184227        ENDIF 
     228       ENDIF 
    185229 
    186230        IF      ( nn_secdebug .GE. 1 .AND. nn_secdebug .LE. nb_sec_max )THEN 
     
    195239 
    196240     ENDIF 
    197  
    198      !Read section_ijglobal.diadct 
    199      CALL readsec 
     241      
     242      
     243     IF ( ln_NOOS ) THEN 
     244        IF ( ln_dct_calc_noos_25h .or. ln_dct_calc_noos_hr ) CALL readsec 
     245     ENDIF 
    200246 
    201247     !open output file 
    202      IF( lwm ) THEN 
     248     IF( lwp ) THEN 
    203249        IF( ln_NOOS ) THEN 
    204            CALL ctl_opn( numdct_NOOS  ,'NOOS_transport'  , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
    205            CALL ctl_opn( numdct_NOOS_h,'NOOS_transport_h', 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
     250           WRITE(numout,*) "diadct_init: Open output files. ASCII? ",ln_dct_ascii 
     251           WRITE(numout,*) "~~~~~~~~~~~~~~~~~~~~~" 
     252           IF  ( ln_dct_ascii ) THEN 
     253               if ( ln_dct_calc_noos_25h ) CALL ctl_opn( numdct_NOOS  ,'NOOS_transport'  , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .TRUE. ) 
     254               if ( ln_dct_calc_noos_hr )  CALL ctl_opn( numdct_NOOS_h,'NOOS_transport_h', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .TRUE. ) 
     255           ELSE 
     256               if ( ln_dct_calc_noos_25h ) CALL ctl_opn( numdct_NOOS  ,'NOOS_transport_bin'  , 'REPLACE', 'UNFORMATTED', 'SEQUENTIAL', -1, numout,  .TRUE. ) 
     257               if ( ln_dct_calc_noos_hr )  CALL ctl_opn( numdct_NOOS_h,'NOOS_transport_bin_h', 'REPLACE', 'UNFORMATTED', 'SEQUENTIAL', -1, numout,  .TRUE. ) 
     258           ENDIF 
    206259        ELSE 
    207            CALL ctl_opn( numdct_vol,  'volume_transport', 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
    208            CALL ctl_opn( numdct_heat, 'heat_transport'  , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
    209            CALL ctl_opn( numdct_salt, 'salt_transport'  , 'NEW', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
     260           CALL ctl_opn( numdct_vol,  'volume_transport', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
     261           CALL ctl_opn( numdct_heat, 'heat_transport'  , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
     262           CALL ctl_opn( numdct_salt, 'salt_transport'  , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout,  .FALSE. ) 
    210263        ENDIF 
    211264     ENDIF 
    212265 
    213266     ! Initialise arrays to zero  
    214      transports_3d(:,:,:,:)  =0.0  
    215      transports_2d(:,:,:)    =0.0  
    216      transports_3d_h(:,:,:,:)=0._wp 
    217      transports_2d_h(:,:,:)  =0._wp 
    218      z_hr_output(:,:,:)      =0._wp 
     267     transports_3d(:,:,:,:)   =0._wp 
     268     transports_2d(:,:,:)     =0._wp 
     269     transports_3d_h(:,:,:,:) =0._wp 
     270     transports_2d_h(:,:,:)   =0._wp 
     271     z_hr_output(:,:,:)       =0._wp 
    219272 
    220273     IF( nn_timing == 1 )   CALL timing_stop('dia_dct_init') 
     274 
     275     IF (ln_dct_iom_cont) THEN 
     276        IF( lwp ) THEN 
     277            WRITE(numout,*) " " 
     278            WRITE(numout,*) "diadct_init: using xios iom_put for output: field_def.xml and iodef.xml code" 
     279            WRITE(numout,*) "~~~~~~~~~~~~~~~~~~~~~" 
     280            WRITE(numout,*) "" 
     281            WRITE(numout,*) "      field_def.xml" 
     282            WRITE(numout,*) "      ~~~~~~~~~~~~~" 
     283            WRITE(numout,*) "" 
     284            WRITE(numout,*) "" 
     285       
     286            WRITE(numout,*)  '      <field_group id="noos_cross_section" domain_ref="1point" axis_ref="noos" operation="average">' 
     287 
     288            DO jsec=1,nb_sec 
     289               WRITE (jsec_str, "(I3.3)") jsec 
     290                
     291               WRITE(numout,*)  '          <field id="noos_'//jsec_str//'_trans" long_name="' // TRIM(secs(jsec)%name) // ' 25h mean NOOS transport cross-section number: '//jsec_str//' (total, positive, negative)" unit="m^3/s" />' 
     292               WRITE(numout,*)  '          <field id="noos_'//jsec_str//'_heat" long_name="' // TRIM(secs(jsec)%name) // ' 25h mean NOOS heat cross-section number: '//jsec_str//' (total, positive, negative)" unit="J/s" />' 
     293               WRITE(numout,*)  '          <field id="noos_'//jsec_str//'_salt" long_name="' // TRIM(secs(jsec)%name) // ' 25h mean NOOS salt cross-section number: '//jsec_str//' (total, positive, negative)" unit="g/s" />' 
     294                
     295            ENDDO 
     296             
     297            WRITE(numout,*)  '      </field_group>' 
     298             
     299            WRITE(numout,*) "" 
     300            WRITE(numout,*) "" 
     301            WRITE(numout,*) "      iodef.xml" 
     302            WRITE(numout,*) "      ~~~~~~~~~" 
     303            WRITE(numout,*) "" 
     304            WRITE(numout,*) "" 
     305             
     306            WRITE(numout,*)  '      <file_group id="1d" output_freq="1d" output_level="10" enabled=".TRUE.">' 
     307            WRITE(numout,*) "" 
     308            WRITE(numout,*)  '          <file id="noos_cross_section" name="NOOS_transport">' 
     309            DO jsec=1,nb_sec 
     310               WRITE (jsec_str, "(I3.3)") jsec 
     311                
     312               WRITE(numout,*)  '              <field field_ref="noos_'//jsec_str//'_trans" />' 
     313               WRITE(numout,*)  '              <field field_ref="noos_'//jsec_str//'_heat" />' 
     314               WRITE(numout,*)  '              <field field_ref="noos_'//jsec_str//'_salt" />' 
     315                
     316            ENDDO 
     317            WRITE(numout,*)  '          </file>' 
     318            WRITE(numout,*) "" 
     319            WRITE(numout,*)  '      </file_group>' 
     320             
     321            WRITE(numout,*) "" 
     322            WRITE(numout,*) "" 
     323            WRITE(numout,*) "~~~~~~~~~~~~~~~~~~~~~" 
     324            WRITE(numout,*) "" 
     325         
     326        ENDIF 
     327     ENDIF 
     328 
     329 
    221330     ! 
    222331  END SUBROUTINE dia_dct_init 
     
    231340     !!  Method  :: All arrays initialised to zero in dct_init  
    232341     !!             Each nn_dct time step call subroutine 'transports' for  
    233      !!               each section to sum the transports over each grid cell.  
     342     !!               each section to sum the transports. 
    234343     !!             Each nn_dctwri time step:  
    235344     !!               Divide the arrays by the number of summations to gain  
     
    252361     REAL(wp), POINTER, DIMENSION(:)    :: zwork !   "   
    253362     REAL(wp), POINTER, DIMENSION(:,:,:):: zsum  !   " 
     363     LOGICAL       ::   verbose      
     364     verbose = .false. 
    254365 
    255366     !!---------------------------------------------------------------------     
     
    266377     zsum(:,:,:) = 0.0 
    267378 
    268      IF( lwp .AND. kt==nit000+nn_dct-1 ) THEN 
     379     IF( lwp .AND. kt==nit000+nn_dct-1 .AND. verbose ) THEN 
    269380         WRITE(numout,*) " " 
    270381         WRITE(numout,*) "diadct: compute transport" 
    271382         WRITE(numout,*) "~~~~~~~~~~~~~~~~~~~~~~~~~" 
    272383         WRITE(numout,*) "nb_sec = ",nb_sec 
     384         WRITE(numout,*) "nn_dct = ",nn_dct 
     385         WRITE(numout,*) "ln_NOOS = ",ln_NOOS 
     386         WRITE(numout,*) "nb_sec = ",nb_sec 
     387         WRITE(numout,*) "nb_sec_max = ",nb_sec_max 
     388         WRITE(numout,*) "nb_type_class = ",nb_type_class 
     389         WRITE(numout,*) "nb_class_max = ",nb_class_max 
    273390     ENDIF 
    274391 
    275   
    276      ! Compute transport and write only at nn_dctwri 
    277      IF( MOD(kt,nn_dct)==0 .or. &                ! compute transport every nn_dct time steps 
    278          (ln_NOOS .and. kt==nn_it000 ) )  THEN   ! also include first time step when calculating NOOS 25 hour averages 
    279  
    280         DO jsec=1,nb_sec 
    281  
    282            !debug this section computing ? 
    283            IF( (jsec==nn_secdebug .OR. nn_secdebug==-1) .AND.  kt==nit000+nn_dct-1 .AND. lwp ) lldebug=.TRUE.  
    284  
    285            !Compute transport through section   
    286            CALL transport(secs(jsec),lldebug,jsec)  
    287  
    288         ENDDO 
    289               
    290         IF( MOD(kt,nn_dctwri)==0 )THEN 
    291  
    292            IF( lwp .AND. kt==nit000+nn_dctwri-1 )WRITE(numout,*)"      diadct: average transports and write at kt = ",kt          
    293    
    294            !! divide arrays by nn_dctwri/nn_dct to obtain average  
    295            transports_3d(:,:,:,:)=transports_3d(:,:,:,:)/(nn_dctwri/nn_dct)  
    296            transports_2d(:,:,:)  =transports_2d(:,:,:)  /(nn_dctwri/nn_dct)  
    297   
    298            ! Sum over each class  
    299            DO jsec=1,nb_sec  
    300               CALL dia_dct_sum(secs(jsec),jsec)  
    301            ENDDO  
    302  
    303            !Sum on all procs  
    304            IF( lk_mpp )THEN 
    305               zsum(:,:,:)=0.0_wp 
    306               ish(1)  =  nb_sec_max*nb_type_class*nb_class_max  
    307               ish2    = (/nb_sec_max,nb_type_class,nb_class_max/) 
    308               DO jsec=1,nb_sec ; zsum(jsec,:,:) = secs(jsec)%transport(:,:) ; ENDDO 
    309               zwork(:)= RESHAPE(zsum(:,:,:), ish ) 
    310               CALL mpp_sum(zwork, ish(1)) 
    311               zsum(:,:,:)= RESHAPE(zwork,ish2) 
    312               DO jsec=1,nb_sec ; secs(jsec)%transport(:,:) = zsum(jsec,:,:) ; ENDDO 
    313            ENDIF 
    314  
    315            !Write the transport 
    316            DO jsec=1,nb_sec 
    317  
    318               IF( lwm .and. .not. ln_NOOS )CALL dia_dct_wri(kt,jsec,secs(jsec)) 
    319               IF( lwm .and.       ln_NOOS )CALL dia_dct_wri_NOOS(kt,jsec,secs(jsec))   ! use NOOS specific formatting 
     392     
     393    IF ( ln_dct_calc_noos_25h ) THEN 
     394  
     395        ! Compute transport and write only at nn_dctwri 
     396        IF ( MOD(kt,nn_dct)==0 .or. &               ! compute transport every nn_dct time steps 
     397            (ln_NOOS .and. kt==nn_it000 ) )  THEN   ! also include first time step when calculating NOOS 25 hour averages 
    320398             
    321               !nullify transports values after writing 
    322               transports_3d(:,jsec,:,:)=0. 
    323               transports_2d(:,jsec,:  )=0. 
    324               secs(jsec)%transport(:,:)=0.  
    325               IF ( ln_NOOS ) CALL transport(secs(jsec),lldebug,jsec)  ! reinitialise for next 25 hour instantaneous average (overlapping values) 
    326  
    327            ENDDO 
    328  
    329         ENDIF  
    330  
     399             
     400 
     401            DO jsec=1,nb_sec 
     402 
     403              lldebug=.FALSE. 
     404              IF( (jsec==nn_secdebug .OR. nn_secdebug==-1) .AND.  kt==nit000+nn_dct-1 .AND. lwp ) lldebug=.TRUE.  
     405 
     406              !Compute transport through section   
     407              CALL transport(secs(jsec),lldebug,jsec)  
     408               
     409 
     410            ENDDO 
     411                 
     412            IF( MOD(kt,nn_dctwri)==0 )THEN 
     413             
     414             
     415 
     416              IF( lwp .AND. kt==nit000+nn_dctwri-1 .AND. verbose ) WRITE(numout,*)"      diadct: average and write at kt = ",kt 
     417 
     418 
     419              ! Not 24 values, but 25! divide by ((nn_dctwri/nn_dct) +1) 
     420              !! divide arrays by nn_dctwri/nn_dct  to obtain average 
     421              transports_3d(:,:,:,:)= transports_3d(:,:,:,:)/((nn_dctwri/nn_dct)+1.) 
     422              transports_2d(:,:,:)  = transports_2d(:,:,:)  /((nn_dctwri/nn_dct)+1.) 
     423 
     424              ! Sum over each class 
     425              DO jsec=1,nb_sec 
     426                  CALL dia_dct_sum(secs(jsec),jsec) 
     427              ENDDO 
     428     
     429              !Sum on all procs  
     430              IF( lk_mpp )THEN 
     431                  zsum(:,:,:)=0.0_wp 
     432                  ish(1)  =  nb_sec_max*nb_type_class*nb_class_max  
     433                  ish2    = (/nb_sec_max,nb_type_class,nb_class_max/) 
     434                  DO jsec=1,nb_sec ; zsum(jsec,:,:) = secs(jsec)%transport(:,:) ; ENDDO 
     435                  zwork(:)= RESHAPE(zsum(:,:,:), ish ) 
     436                  CALL mpp_sum(zwork, ish(1)) 
     437                  zsum(:,:,:)= RESHAPE(zwork,ish2) 
     438                  DO jsec=1,nb_sec ; secs(jsec)%transport(:,:) = zsum(jsec,:,:) ; ENDDO 
     439              ENDIF 
     440 
     441              !Write the transport 
     442              DO jsec=1,nb_sec 
     443 
     444                  IF( lwp .and. .not. ln_NOOS )CALL dia_dct_wri(kt,jsec,secs(jsec)) 
     445                  !IF( lwp .and.       ln_NOOS )CALL dia_dct_wri_NOOS(kt,jsec,secs(jsec))   ! use NOOS specific formatting 
     446                  IF(  ln_NOOS )CALL dia_dct_wri_NOOS(kt,jsec,secs(jsec))   ! use NOOS specific formatting 
     447                 
     448                 
     449                  !nullify transports values after writing 
     450                  transports_3d(:,jsec,:,:)=0.0 
     451                  transports_2d(:,jsec,:  )=0.0 
     452                  secs(jsec)%transport(:,:)=0.   
     453                   
     454                   
     455                  IF ( ln_NOOS ) CALL transport(secs(jsec),lldebug,jsec)  ! reinitialise for next 25 hour instantaneous average (overlapping values) 
     456 
     457 
     458 
     459              ENDDO 
     460 
     461            ENDIF  
     462 
     463        ENDIF 
     464         
     465    ENDIF 
     466    IF ( ln_dct_calc_noos_hr ) THEN 
     467        IF ( MOD(kt,nn_dct_h)==0 ) THEN            ! compute transport every nn_dct_h time steps 
     468 
     469            DO jsec=1,nb_sec 
     470 
     471              lldebug=.FALSE. 
     472              IF( (jsec==nn_secdebug .OR. nn_secdebug==-1) .AND.  kt==nit000+nn_dct_h-1 .AND. lwp ) lldebug=.TRUE.  
     473 
     474              !Compute transport through section   
     475              CALL transport_h(secs(jsec),lldebug,jsec)  
     476 
     477            ENDDO 
     478                 
     479            IF( MOD(kt,nn_dctwri_h)==0 )THEN 
     480 
     481              IF( lwp .AND. kt==nit000+nn_dctwri_h-1 .AND. verbose )WRITE(numout,*)"      diadct: average and write hourly files at kt = ",kt          
     482       
     483              !! divide arrays by nn_dctwri/nn_dct to obtain average 
     484                ! 
     485                ! JT - I think this is wrong. I think it is trying to sum over 25 hours, but only dividing by 24. 
     486                ! I think it might work for daily cycles, but not for monthly cycles, 
     487                ! 
     488              transports_3d_h(:,:,:,:)=transports_3d_h(:,:,:,:)/(nn_dctwri_h/nn_dct_h) 
     489              transports_2d_h(:,:,:)  =transports_2d_h(:,:,:)  /(nn_dctwri_h/nn_dct_h) 
     490 
     491              ! Sum over each class 
     492              DO jsec=1,nb_sec 
     493                  CALL dia_dct_sum_h(secs(jsec),jsec) 
     494              ENDDO 
     495 
     496              !Sum on all procs  
     497              IF( lk_mpp )THEN 
     498                  ish(1)  =  nb_sec_max*nb_type_class*nb_class_max  
     499                  ish2    = (/nb_sec_max,nb_type_class,nb_class_max/) 
     500                  DO jsec=1,nb_sec ; zsum(jsec,:,:) = secs(jsec)%transport_h(:,:) ; ENDDO 
     501                  zwork(:)= RESHAPE(zsum(:,:,:), ish ) 
     502                  CALL mpp_sum(zwork, ish(1)) 
     503                  zsum(:,:,:)= RESHAPE(zwork,ish2) 
     504                  DO jsec=1,nb_sec ; secs(jsec)%transport_h(:,:) = zsum(jsec,:,:) ; ENDDO 
     505              ENDIF 
     506 
     507              !Write the transport 
     508              DO jsec=1,nb_sec 
     509 
     510                  IF( lwp .and. ln_NOOS ) THEN 
     511                    CALL dia_dct_wri_NOOS_h(kt/nn_dctwri_h,jsec,secs(jsec))   ! use NOOS specific formatting 
     512                  endif 
     513                  !nullify transports values after writing 
     514                  transports_3d_h(:,jsec,:,:)=0.0 
     515                  transports_2d_h(:,jsec,:)=0.0 
     516                  secs(jsec)%transport_h(:,:)=0.0 
     517                   
     518                  ! for hourly mean or hourly instantaneous, you don't initialise! start with zero! 
     519                  !IF ( ln_NOOS ) CALL transport_h(secs(jsec),lldebug,jsec)  ! reinitialise for next 25 hour instantaneous average (overlapping values) 
     520 
     521              ENDDO 
     522 
     523            ENDIF  
     524 
     525        ENDIF     
     526         
    331527     ENDIF 
    332  
    333      IF ( MOD(kt,nn_dct_h)==0 ) THEN            ! compute transport every nn_dct_h time steps 
    334  
    335         DO jsec=1,nb_sec 
    336  
    337            !lldebug=.FALSE. 
    338            IF( (jsec==nn_secdebug .OR. nn_secdebug==-1) .AND.  kt==nit000+nn_dct_h-1 .AND. lwp ) lldebug=.TRUE.  
    339  
    340            !Compute transport through section   
    341            CALL transport_h(secs(jsec),lldebug,jsec)  
    342  
    343         ENDDO 
    344               
    345         IF( MOD(kt,nn_dctwri_h)==0 )THEN 
    346  
    347            IF( lwp .AND. kt==nit000+nn_dctwri_h-1 )WRITE(numout,*)"      diadct: average and write hourly files at kt = ",kt          
    348    
    349            !! divide arrays by nn_dctwri/nn_dct to obtain average 
    350            transports_3d_h(:,:,:,:)=transports_3d_h(:,:,:,:)/(nn_dctwri_h/nn_dct_h) 
    351            transports_2d_h(:,:,:)  =transports_2d_h(:,:,:)  /(nn_dctwri_h/nn_dct_h) 
    352  
    353            ! Sum over each class 
    354            DO jsec=1,nb_sec 
    355               CALL dia_dct_sum_h(secs(jsec),jsec) 
    356            ENDDO 
    357   
    358            !Sum on all procs  
    359           IF( lk_mpp )THEN 
    360               ish(1)  =  nb_sec_max*nb_type_class*nb_class_max  
    361               ish2    = (/nb_sec_max,nb_type_class,nb_class_max/) 
    362               DO jsec=1,nb_sec ; zsum(jsec,:,:) = secs(jsec)%transport_h(:,:) ; ENDDO 
    363               zwork(:)= RESHAPE(zsum(:,:,:), ish ) 
    364               CALL mpp_sum(zwork, ish(1)) 
    365               zsum(:,:,:)= RESHAPE(zwork,ish2) 
    366               DO jsec=1,nb_sec ; secs(jsec)%transport_h(:,:) = zsum(jsec,:,:) ; ENDDO 
    367            ENDIF 
    368  
    369            !Write the transport 
    370            DO jsec=1,nb_sec 
    371  
    372               IF( lwp .and.       ln_NOOS )CALL dia_dct_wri_NOOS_h(kt/nn_dctwri_h,jsec,secs(jsec))   ! use NOOS specific formatting 
    373              
    374               !nullify transports values after writing 
    375               transports_3d_h(:,jsec,:,:)=0.0 
    376               transports_2d_h(:,jsec,:)=0.0 
    377               secs(jsec)%transport_h(:,:)=0.   
    378               IF ( ln_NOOS ) CALL transport_h(secs(jsec),lldebug,jsec)  ! reinitialise for next 25 hour instantaneous average (overlapping values) 
    379  
    380            ENDDO 
    381  
    382         ENDIF  
    383  
    384      ENDIF     
    385528 
    386529     IF( lk_mpp )THEN 
     
    419562     LOGICAL :: llbon                                       ,&!local logical 
    420563                lldebug                                       !debug the section 
     564     LOGICAL       ::   verbose      
     565     verbose = .false. 
    421566     !!------------------------------------------------------------------------------------- 
    422567     CALL wrk_alloc( nb_point_max, directemp ) 
     
    424569     !open input file 
    425570     !--------------- 
    426      CALL ctl_opn( numdct_in, 'section_ijglobal.diadct', 'OLD', 'UNFORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
     571     !write(numout,*) 'dct low-level pre open: little endian ' 
     572     !OPEN(UNIT=107,FILE='section_ijglobal.diadct', FORM='UNFORMATTED', ACCESS='SEQUENTIAL', STATUS='OLD',convert='LITTLE_ENDIAN') 
     573      
     574     IF ( verbose ) write(numout,*) 'dct low-level pre open: big endian :',nproc,narea 
     575     OPEN(UNIT=107,FILE='section_ijglobal.diadct', FORM='UNFORMATTED', ACCESS='SEQUENTIAL', STATUS='OLD',convert='BIG_ENDIAN') 
     576      
     577     !write(numout,*) 'dct low-level pre open: SWAP ' 
     578     !OPEN(UNIT=107,FILE='section_ijglobal.diadct', FORM='UNFORMATTED', ACCESS='SEQUENTIAL', STATUS='OLD',convert='SWAP') 
     579      
     580     !write(numout,*) 'dct low-level pre open: NATIVE ' 
     581     !OPEN(UNIT=107,FILE='section_ijglobal.diadct', FORM='UNFORMATTED', ACCESS='SEQUENTIAL', STATUS='OLD',convert='NATIVE') 
     582      
     583     READ(107) isec 
     584     CLOSE(107) 
     585      
     586     CALL ctl_opn( numdct_in, 'section_ijglobal.diadct', 'OLD', 'UNFORMATTED', 'SEQUENTIAL', -1, numout, .TRUE. ) 
    427587  
    428588     !--------------- 
     
    433593 
    434594        IF ( lwp .AND. ( jsec==nn_secdebug .OR. nn_secdebug==-1 ) ) & 
    435            & WRITE(numout,*)'debuging for section number: ',jsec  
     595           & WRITE(numout,*)'debugging for section number: ',jsec  
    436596 
    437597        !initialization 
    438598        !--------------- 
    439599        secs(jsec)%name='' 
    440         secs(jsec)%llstrpond    = .FALSE.  ; secs(jsec)%ll_ice_section = .FALSE. 
    441         secs(jsec)%ll_date_line = .FALSE.  ; secs(jsec)%nb_class       = 0 
    442         secs(jsec)%zsigi        = 99._wp   ; secs(jsec)%zsigp          = 99._wp 
    443         secs(jsec)%zsal         = 99._wp   ; secs(jsec)%ztem           = 99._wp 
    444         secs(jsec)%zlay         = 99._wp          
    445         secs(jsec)%transport    =  0._wp   ; secs(jsec)%nb_point       = 0 
    446         secs(jsec)%transport_h  =  0._wp   ; secs(jsec)%nb_point       = 0 
     600        secs(jsec)%llstrpond      = .FALSE. 
     601        secs(jsec)%ll_ice_section = .FALSE. 
     602        secs(jsec)%ll_date_line   = .FALSE. 
     603        secs(jsec)%nb_class       = 0 
     604        secs(jsec)%zsigi          = 99._wp 
     605        secs(jsec)%zsigp          = 99._wp 
     606        secs(jsec)%zsal           = 99._wp 
     607        secs(jsec)%ztem           = 99._wp 
     608        secs(jsec)%zlay           = 99._wp 
     609        secs(jsec)%transport      =  0._wp 
     610        secs(jsec)%transport_h    =  0._wp 
     611        secs(jsec)%nb_point       = 0 
    447612 
    448613        !read section's number / name / computing choices / classes / slopeSection / points number 
    449614        !----------------------------------------------------------------------------------------- 
    450         READ(numdct_in,iostat=iost)isec 
    451         IF (iost .NE. 0 )EXIT !end of file 
     615         
     616        READ(numdct_in,iostat=iost) isec 
     617        IF (iost .NE. 0 ) then 
     618          write(numout,*) 'reached end of section_ijglobal.diadct. iost = ',iost, & 
     619                          ', number of sections read = ', jsec-1 
     620          EXIT !end of file  
     621        ENDIF 
     622         
     623         
    452624        WRITE(cltmp,'(a,i4.4,a,i4.4)')'diadct: read sections : Problem of section number: isec= ',isec,' and jsec= ',jsec 
    453         IF( jsec .NE. isec )CALL ctl_stop( cltmp ) 
    454  
    455         IF( lwp .AND. ( jsec==nn_secdebug .OR. nn_secdebug==-1 ) )WRITE(numout,*)"isec ",isec  
     625         
     626         
     627        IF( jsec .NE. isec )  CALL ctl_stop( cltmp ) 
    456628 
    457629        READ(numdct_in)secs(jsec)%name 
     
    469641        READ(numdct_in)iptglo 
    470642 
    471         IF ( ln_NOOS ) THEN 
     643        IF ( ln_NOOS .AND. verbose ) THEN 
    472644           WRITE(numout,*) 'Section name = ',TRIM(secs(jsec)%name) 
    473645           WRITE(numout,*) 'coordSec = ',secs(jsec)%coordSec 
     
    483655 
    484656            WRITE(numout,*)       "   Section name :                       ",TRIM(secs(jsec)%name) 
    485             WRITE(numout,*)       "      Compute heat and salt transport ? ",secs(jsec)%llstrpond 
     657            WRITE(numout,*)       "      Compute temperature and salinity transports ? ",secs(jsec)%llstrpond 
    486658            WRITE(numout,*)       "      Compute ice transport ?           ",secs(jsec)%ll_ice_section 
    487659            WRITE(numout,*)       "      Section crosses date-line ?       ",secs(jsec)%ll_date_line 
     
    500672           !read points'coordinates and directions  
    501673           !-------------------------------------- 
    502            IF ( ln_NOOS ) THEN 
     674           IF ( ln_NOOS .AND. verbose ) THEN 
    503675              WRITE(numout,*) 'Coords and direction read' 
    504676           ENDIF 
     
    558730           ENDIF 
    559731 
    560               IF(jsec==nn_secdebug .AND. secs(jsec)%nb_point .NE. 0)THEN 
     732           IF(jsec==nn_secdebug .AND. secs(jsec)%nb_point .NE. 0)THEN 
    561733              DO jpt = 1,iptloc 
    562734                 iiglo = secs(jsec)%listPoint(jpt)%I + jpizoom - 1 + nimpp - 1 
    563735                 ijglo = secs(jsec)%listPoint(jpt)%J + jpjzoom - 1 + njmpp - 1 
    564736              ENDDO 
    565               ENDIF 
     737           ENDIF 
    566738 
    567739           !remove redundant points between processors 
     
    602774  
    603775     nb_sec = jsec-1   !number of section read in the file 
     776 
     777     IF( lwp .AND. verbose )  WRITE(numout,*)'diadct: read sections: Finished readsec.' 
    604778 
    605779     CALL wrk_dealloc( nb_point_max, directemp ) 
     
    703877     !!              loop on the level jk !! 
    704878     !!  
    705      !!  Output  ::  Arrays containing the volume,density,heat,salt transports for each i 
    706      !!              point in a section, summed over each nn_dct.  
     879     !! ** Output: Arrays containing the volume,density,salinity,temperature etc 
     880     !!            transports for each point in a section, summed over each nn_dct. 
    707881     !! 
    708882     !!------------------------------------------------------------------------------------------- 
     
    713887     
    714888     !! * Local variables 
    715      INTEGER             :: jk, jseg, jclass,jl,                 &!loop on level/segment/classes/ice categories 
    716                             isgnu, isgnv                          !  
    717      REAL(wp)            :: zumid, zvmid,                        &!U/V velocity on a cell segment  
    718                             zumid_ice, zvmid_ice,                &!U/V ice velocity  
    719                             zTnorm                                !transport of velocity through one cell's sides  
    720      REAL(wp)            :: ztn, zsn, zrhoi, zrhop, zsshn, zfsdep !temperature/salinity/potential density/ssh/depth at u/v point 
     889     INTEGER             :: jk,jseg,jclass,    &!loop on level/segment/classes  
     890                            isgnu  , isgnv      ! 
     891     REAL(wp):: zumid        , zvmid        ,  &!U/V velocity on a cell segment 
     892                zumid_ice    , zvmid_ice    ,  &!U/V ice velocity 
     893                zTnorm                          !transport of velocity through one cell's sides 
     894     REAL(wp):: ztn, zsn, zrhoi, zrhop, zsshn, zfsdep ! temperature/salinity/ssh/potential density /depth at u/v point 
    721895 
    722896     TYPE(POINT_SECTION) :: k 
    723897     !!-------------------------------------------------------- 
    724898 
    725      !!NIALL IF( ld_debug )WRITE(numout,*)'      Compute transport' 
     899     IF( ld_debug )WRITE(numout,*)'      Compute transport (jsec,sec%nb_point,sec%slopeSection) : ', jsec,sec%nb_point,sec%slopeSection 
    726900 
    727901     !---------------------------! 
     
    730904     IF(sec%nb_point .NE. 0)THEN    
    731905 
     906        !---------------------------------------------------------------------------------------------------- 
     907        !---------------------------------------------------------------------------------------------------- 
     908        !---------------------------------------------------------------------------------------------------- 
     909        ! 
     910        ! 
     911        ! ! ! ! JT 1/09/2018 - changing convention. Always direction + is toward left hand of section 
     912        ! 
     913        !    Making sign of the velocities used to calculate the volume transport a function of direction, not slopesection 
     914        !    (isgnu, isgnv) 
     915        !     
     916        !    They vary for each segment of the section.  
     917        ! 
     918        !---------------------------------------------------------------------------------------------------- 
     919        !---------------------------------------------------------------------------------------------------- 
    732920        !---------------------------------------------------------------------------------------------------- 
    733921        !Compute sign for velocities: 
     
    751939        !                                                       
    752940        !---------------------------------------------------------------------------------------------------- 
    753         isgnu = 1 
    754         IF( sec%slopeSection .GT. 0 ) THEN  ; isgnv = -1  
    755         ELSE                                ; isgnv =  1 
    756         ENDIF 
    757         IF( sec%slopeSection .GE. 9999. )     isgnv =  1 
    758941 
    759942        IF( ld_debug )write(numout,*)"sec%slopeSection isgnu isgnv ",sec%slopeSection,isgnu,isgnv 
     
    763946        !--------------------------------------! 
    764947        DO jseg=1,MAX(sec%nb_point-1,0) 
    765                
     948            
     949            
     950           !Compute sign for velocities: 
     951            
     952           !isgnu =  1 
     953           !isgnv =  1 
     954           ! 
     955           !changing sign of u and v is dependent on the direction of the section.  
     956           !isgnu =  1 
     957           !isgnv =  1 
     958           !SELECT CASE( sec%direction(jseg) ) 
     959           !CASE(0)  ;   isgnv = -1 
     960           !CASE(3)  ;   isgnu = -1 
     961           !END SELECT 
     962            
     963            
     964           SELECT CASE( sec%direction(jseg) ) 
     965           CASE(0)   
     966              isgnu =  1 
     967              isgnv = -1 
     968           CASE(1) 
     969              isgnu =  1 
     970              isgnv =  1 
     971           CASE(2)   
     972              isgnu =  1 
     973              isgnv =  1 
     974           CASE(3)   
     975              isgnu = -1 
     976              isgnv =  1 
     977           END SELECT 
     978            
    766979           !------------------------------------------------------------------------------------------- 
    767980           ! Select the appropriate coordinate for computing the velocity of the segment 
     981           ! Corrected by JT 01/09/2018 (#) 
    768982           ! 
    769983           !                      CASE(0)                                    Case (2) 
    770984           !                      -------                                    -------- 
    771985           !  listPoint(jseg)                 listPoint(jseg+1)       listPoint(jseg)  F(i,j)       
    772            !      F(i,j)----------V(i+1,j)-------F(i+1,j)                               | 
    773            !                                                                            | 
    774            !                                                                            | 
    775            !                                                                            | 
    776            !                      Case (3)                                            U(i,j) 
    777            !                      --------                                              | 
    778            !                                                                            | 
     986           !      F(i,j)---------#V(i,j)-------F(i+1,j)                                 | 
     987           !                     -------->                                              | 
     988           !                                                                        |   | 
     989           !                                                                        |   | 
     990           !                      Case (3)                                          | U(i,j) 
     991           !                      --------                                          |   | 
     992           !                                                                        V   | 
    779993           !  listPoint(jseg+1) F(i,j+1)                                                | 
    780994           !                        |                                                   | 
    781995           !                        |                                                   | 
    782996           !                        |                                 listPoint(jseg+1) F(i,j-1) 
    783            !                        |                                             
    784            !                        |                                             
    785            !                     U(i,j+1)                                             
    786            !                        |                                       Case(1)      
    787            !                        |                                       ------       
     997           !                   ^    |                                             
     998           !                   |    |                                             
     999           !                   | U(i,j+1)                                             
     1000           !                   |    |                                       Case(1)      
     1001           !                   |    |                                       ------       
    7881002           !                        |                                             
    7891003           !                        |                 listPoint(jseg+1)             listPoint(jseg)                            
    790            !                        |                 F(i-1,j)-----------V(i,j) -------f(jseg)                            
    791            ! listPoint(jseg)     F(i,j) 
     1004           !                        |                 F(i-1,j)----------#V(i-1,j) ------#f(i,j)                            
     1005           ! listPoint(jseg)     F(i,j)                                 <------- 
    7921006           !  
    7931007           !------------------------------------------------------------------------------------------- 
     
    8001014           END SELECT 
    8011015 
    802            !---------------------------|  
    803            !     LOOP ON THE LEVEL     |  
    804            !---------------------------|  
    805            !Sum of the transport on the vertical   
    806            DO jk=1,mbathy(k%I,k%J)  
    807   
    808               ! compute temperature, salinity, insitu & potential density, ssh and depth at U/V point  
    809               SELECT CASE( sec%direction(jseg) )  
    810               CASE(0,1)  
    811                  ztn   = interp(k%I,k%J,jk,'V',0 )  
    812                  zsn   = interp(k%I,k%J,jk,'V',1 )  
    813                  zrhop = interp(k%I,k%J,jk,'V',2 )  
    814                  zrhoi = interp(k%I,k%J,jk,'V',3 )  
    815                  zsshn =  0.5*( sshn(k%I,k%J)    + sshn(k%I,k%J+1)    ) * vmask(k%I,k%J,1)  
    816               CASE(2,3)  
    817                  ztn   = interp(k%I,k%J,jk,'U',0 )  
    818                  zsn   = interp(k%I,k%J,jk,'U',1 )  
    819                  zrhop = interp(k%I,k%J,jk,'U',2 )  
    820                  zrhoi = interp(k%I,k%J,jk,'U',3 )  
    821                  zsshn =  0.5*( sshn(k%I,k%J)    + sshn(k%I+1,k%J)    ) * umask(k%I,k%J,1)   
    822               END SELECT  
    823   
    824               zfsdep= fsdept(k%I,k%J,jk)  
    825    
    826               !compute velocity with the correct direction  
    827               SELECT CASE( sec%direction(jseg) )  
    828               CASE(0,1)    
    829                  zumid=0.  
    830                  zvmid=isgnv*vn(k%I,k%J,jk)*vmask(k%I,k%J,jk)  
    831               CASE(2,3)  
    832                  zumid=isgnu*un(k%I,k%J,jk)*umask(k%I,k%J,jk)  
    833                  zvmid=0.  
    834               END SELECT  
    835   
    836               !zTnorm=transport through one cell;  
    837               !velocity* cell's length * cell's thickness  
    838               zTnorm=zumid*e2u(k%I,k%J)*  fse3u(k%I,k%J,jk)+     &  
    839                      zvmid*e1v(k%I,k%J)*  fse3v(k%I,k%J,jk)  
     1016           !---------------------------| 
     1017           !     LOOP ON THE LEVEL     | 
     1018           !---------------------------| 
     1019           !Sum of the transport on the vertical  
     1020           DO jk=1,mbathy(k%I,k%J) 
     1021 
     1022              ! compute temperature, salinity, insitu & potential density, ssh and depth at U/V point 
     1023              SELECT CASE( sec%direction(jseg) ) 
     1024              CASE(0,1) 
     1025                 ztn   = interp(k%I,k%J,jk,'V',0 ) 
     1026                 zsn   = interp(k%I,k%J,jk,'V',1 ) 
     1027                 zrhop = interp(k%I,k%J,jk,'V',2) 
     1028                 zrhoi = interp(k%I,k%J,jk,'V',3) 
     1029                 zsshn =  0.5*( sshn(k%I,k%J)    + sshn(k%I,k%J+1)    ) * vmask(k%I,k%J,1) 
     1030              CASE(2,3) 
     1031                 ztn   = interp(k%I,k%J,jk,'U',0) 
     1032                 zsn   = interp(k%I,k%J,jk,'U',1) 
     1033                 zrhop = interp(k%I,k%J,jk,'U',2) 
     1034                 zrhoi = interp(k%I,k%J,jk,'U',3) 
     1035                 zsshn =  0.5*( sshn(k%I,k%J)    + sshn(k%I+1,k%J)    ) * umask(k%I,k%J,1)  
     1036              END SELECT 
     1037 
     1038              zfsdep= fsdept(k%I,k%J,jk) 
     1039  
     1040              !compute velocity with the correct direction 
     1041              SELECT CASE( sec%direction(jseg) ) 
     1042              CASE(0,1)   
     1043                 zumid=0. 
     1044                 zvmid=isgnv*vn(k%I,k%J,jk)*vmask(k%I,k%J,jk) 
     1045              CASE(2,3) 
     1046                 zumid=isgnu*un(k%I,k%J,jk)*umask(k%I,k%J,jk) 
     1047                 zvmid=0. 
     1048              END SELECT 
     1049 
     1050              !zTnorm=transport through one cell; 
     1051              !velocity* cell's length * cell's thickness 
     1052              zTnorm=zumid*e2u(k%I,k%J)*  fse3u(k%I,k%J,jk)+     & 
     1053                     zvmid*e1v(k%I,k%J)*  fse3v(k%I,k%J,jk) 
    8401054 
    8411055#if ! defined key_vvl 
    842               !add transport due to free surface  
    843               IF( jk==1 )THEN  
    844                  zTnorm = zTnorm + zumid* e2u(k%I,k%J) * zsshn * umask(k%I,k%J,jk) + &  
    845                                    zvmid* e1v(k%I,k%J) * zsshn * vmask(k%I,k%J,jk)  
    846               ENDIF  
     1056              !add transport due to free surface 
     1057              IF( jk==1 )THEN 
     1058                 zTnorm = zTnorm + zumid* e2u(k%I,k%J) * zsshn * umask(k%I,k%J,jk) + & 
     1059                                   zvmid* e1v(k%I,k%J) * zsshn * vmask(k%I,k%J,jk) 
     1060              ENDIF 
    8471061#endif 
    8481062              !COMPUTE TRANSPORT   
    849   
    850               transports_3d(1,jsec,jseg,jk) = transports_3d(1,jsec,jseg,jk) + zTnorm  
    851    
    852               IF ( sec%llstrpond ) THEN  
    853                  transports_3d(2,jsec,jseg,jk) = transports_3d(2,jsec,jseg,jk)  + zTnorm * ztn * zrhop * rcp 
    854                  transports_3d(3,jsec,jseg,jk) = transports_3d(3,jsec,jseg,jk)  + zTnorm * zsn * zrhop * 0.001 
     1063 
     1064              transports_3d(1,jsec,jseg,jk) = transports_3d(1,jsec,jseg,jk) + zTnorm 
     1065  
     1066              IF ( sec%llstrpond ) THEN 
     1067                 transports_3d(2,jsec,jseg,jk) = transports_3d(2,jsec,jseg,jk)  + zTnorm * zrhoi 
     1068                 transports_3d(3,jsec,jseg,jk) = transports_3d(3,jsec,jseg,jk)  + zTnorm * zrhop 
    8551069                 transports_3d(4,jsec,jseg,jk) = transports_3d(4,jsec,jseg,jk)  + zTnorm * 4.e+3_wp * (ztn+273.15) * 1026._wp 
    8561070                 transports_3d(5,jsec,jseg,jk) = transports_3d(5,jsec,jseg,jk)  + zTnorm * 0.001 * zsn * 1026._wp 
     
    8801094    
    8811095              zTnorm=zumid_ice*e2u(k%I,k%J)+zvmid_ice*e1v(k%I,k%J) 
    882  
    883 #if defined key_lim2    
    884               transports_2d(1,jsec,jseg) = transports_2d(1,jsec,jseg) + (zTnorm)*   &  
    885                                    (1.0 - frld(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J))  &  
    886                                   *(hsnif(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J) +  &  
    887                                     hicif(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J)) 
    888               transports_2d(2,jsec,jseg) = transports_2d(2,jsec,jseg) + (zTnorm)*   &  
    889                                     (1.0 -  frld(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J)) 
    890 #endif 
    891 #if defined key_lim3 
    892               DO jl=1,jpl 
    893                  transports_2d(1,jsec,jseg) = transports_2d(1,jsec,jseg) + (zTnorm)*     & 
    894                                    a_i(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J,jl) * & 
    895                                   ( ht_i(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J,jl) +  & 
    896                                     ht_s(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J,jl) ) 
    897                                     
    898                  transports_2d(2,jsec,jseg) = transports_2d(2,jsec,jseg) + (zTnorm)*   & 
    899                                    a_i(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J,jl) 
    900               ENDDO 
    901 #endif 
     1096    
     1097              transports_2d(1,jsec,jseg) = transports_2d(1,jsec,jseg) + (zTnorm)*   & 
     1098                                   (1.0 - frld(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J))  & 
     1099                                  *(hsnif(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J) +  & 
     1100                                    hicif(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J)) & 
     1101                                   +zice_vol_pos 
     1102              transports_2d(2,jsec,jseg) = transports_2d(2,jsec,jseg) + (zTnorm)*   & 
     1103                                    (1.0 -  frld(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J))  & 
     1104                                   +zice_surf_pos 
    9021105    
    9031106           ENDIF !end of ice case 
     
    9571160 
    9581161        !---------------------------------------------------------------------------------------------------- 
     1162        !---------------------------------------------------------------------------------------------------- 
     1163        !---------------------------------------------------------------------------------------------------- 
     1164        ! 
     1165        ! 
     1166        ! ! ! ! JT 1/09/2018 - changing convention. Always direction + is toward left hand of section 
     1167        ! 
     1168        !    Making sign of the velocities used to calculate the volume transport a function of direction, not slopesection 
     1169        !    (isgnu, isgnv) 
     1170        !     
     1171        !    They vary for each segment of the section.  
     1172        ! 
     1173        !---------------------------------------------------------------------------------------------------- 
     1174        !---------------------------------------------------------------------------------------------------- 
     1175        !---------------------------------------------------------------------------------------------------- 
    9591176        !Compute sign for velocities: 
    9601177        ! 
     
    9771194        !                                                       
    9781195        !---------------------------------------------------------------------------------------------------- 
    979         isgnu = 1 
    980         IF( sec%slopeSection .GT. 0 ) THEN  ; isgnv = -1  
    981         ELSE                                ; isgnv =  1 
    982         ENDIF 
    9831196 
    9841197        IF( ld_debug )write(numout,*)"isgnu isgnv ",isgnu,isgnv 
     
    9881201        !--------------------------------------! 
    9891202        DO jseg=1,MAX(sec%nb_point-1,0) 
    990                
     1203            
     1204            
     1205           !Compute sign for velocities: 
     1206            
     1207           !isgnu =  1 
     1208           !isgnv =  1 
     1209           ! 
     1210           ! changing sign of u and v is dependent on the direction of the section.  
     1211           !isgnu =  1 
     1212           !isgnv =  1 
     1213           !SELECT CASE( sec%direction(jseg) ) 
     1214           !CASE(0)  ;   isgnv = -1 
     1215           !CASE(3)  ;   isgnu = -1 
     1216           !END SELECT 
     1217            
     1218            
     1219           SELECT CASE( sec%direction(jseg) ) 
     1220           CASE(0)   
     1221              isgnu =  1 
     1222              isgnv = -1 
     1223           CASE(1) 
     1224              isgnu =  1 
     1225              isgnv =  1 
     1226           CASE(2)   
     1227              isgnu =  1 
     1228              isgnv =  1 
     1229           CASE(3)   
     1230              isgnu = -1 
     1231              isgnv =  1 
     1232           END SELECT 
     1233            
    9911234           !------------------------------------------------------------------------------------------- 
    9921235           ! Select the appropriate coordinate for computing the velocity of the segment 
     1236           ! Corrected by JT 01/09/2018 (#) 
    9931237           ! 
    9941238           !                      CASE(0)                                    Case (2) 
    9951239           !                      -------                                    -------- 
    9961240           !  listPoint(jseg)                 listPoint(jseg+1)       listPoint(jseg)  F(i,j)       
    997            !      F(i,j)----------V(i+1,j)-------F(i+1,j)                               | 
    998            !                                                                            | 
    999            !                                                                            | 
    1000            !                                                                            | 
    1001            !                      Case (3)                                            U(i,j) 
    1002            !                      --------                                              | 
    1003            !                                                                            | 
     1241           !      F(i,j)---------#V(i,j)-------F(i+1,j)                                 | 
     1242           !                     -------->                                              | 
     1243           !                                                                        |   | 
     1244           !                                                                        |   | 
     1245           !                      Case (3)                                          | U(i,j) 
     1246           !                      --------                                          |   | 
     1247           !                                                                        V   | 
    10041248           !  listPoint(jseg+1) F(i,j+1)                                                | 
    10051249           !                        |                                                   | 
    10061250           !                        |                                                   | 
    10071251           !                        |                                 listPoint(jseg+1) F(i,j-1) 
    1008            !                        |                                             
    1009            !                        |                                             
    1010            !                     U(i,j+1)                                             
    1011            !                        |                                       Case(1)      
    1012            !                        |                                       ------       
     1252           !                   ^    |                                             
     1253           !                   |    |                                             
     1254           !                   | U(i,j+1)                                             
     1255           !                   |    |                                       Case(1)      
     1256           !                   |    |                                       ------       
    10131257           !                        |                                             
    10141258           !                        |                 listPoint(jseg+1)             listPoint(jseg)                            
    1015            !                        |                 F(i-1,j)-----------V(i,j) -------f(jseg)                            
    1016            ! listPoint(jseg)     F(i,j) 
     1259           !                        |                 F(i-1,j)----------#V(i-1,j) ------#f(i,j)                            
     1260           ! listPoint(jseg)     F(i,j)                                 <------- 
    10171261           !  
    10181262           !------------------------------------------------------------------------------------------- 
     
    10311275           DO jk=1,mbathy(k%I,k%J) 
    10321276 
    1033               ! compute temparature, salinity, insitu & potential density, ssh and depth at U/V point 
     1277              ! compute temperature, salinity, insitu & potential density, ssh and depth at U/V point 
    10341278              SELECT CASE( sec%direction(jseg) ) 
    10351279              CASE(0,1) 
    1036                  ztn   = interp(k%I,k%J,jk,'V',0 ) 
     1280                 ztn   = interp(k%I,k%J,jk,'V',0) 
    10371281                 zsn   = interp(k%I,k%J,jk,'V',1) 
    10381282                 zrhop = interp(k%I,k%J,jk,'V',2) 
     
    11511395     REAL(wp) :: ztn, zsn, zrhoi, zrhop, zsshn, zfsdep ! temperature/salinity/ssh/potential density /depth at u/v point  
    11521396     !!-------------------------------------------------------------  
    1153   
    1154      !! Sum the relevant segments to obtain values for each class  
    1155      IF(sec%nb_point .NE. 0)THEN     
    1156   
    1157         !--------------------------------------!  
    1158         ! LOOP ON THE SEGMENT BETWEEN 2 NODES  !  
    1159         !--------------------------------------!  
    1160         DO jseg=1,MAX(sec%nb_point-1,0)  
    1161              
    1162            !-------------------------------------------------------------------------------------------  
    1163            ! Select the appropriate coordinate for computing the velocity of the segment  
    1164            !  
    1165            !                      CASE(0)                                    Case (2)  
    1166            !                      -------                                    --------  
    1167            !  listPoint(jseg)                 listPoint(jseg+1)       listPoint(jseg)  F(i,j)        
    1168            !      F(i,j)----------V(i+1,j)-------F(i+1,j)                               |  
    1169            !                                                                            |  
    1170            !                                                                            |  
    1171            !                                                                            |  
    1172            !                      Case (3)                                            U(i,j)  
    1173            !                      --------                                              |  
    1174            !                                                                            |  
    1175            !  listPoint(jseg+1) F(i,j+1)                                                |  
    1176            !                        |                                                   |  
    1177            !                        |                                                   |  
    1178            !                        |                                 listPoint(jseg+1) F(i,j-1)  
    1179            !                        |                                              
    1180            !                        |                                              
    1181            !                     U(i,j+1)                                              
    1182            !                        |                                       Case(1)       
    1183            !                        |                                       ------        
    1184            !                        |                                              
    1185            !                        |                 listPoint(jseg+1)             listPoint(jseg)                             
    1186            !                        |                 F(i-1,j)-----------V(i,j) -------f(jseg)                             
    1187            ! listPoint(jseg)     F(i,j)  
    1188            !   
    1189            !-------------------------------------------------------------------------------------------  
    1190   
    1191            SELECT CASE( sec%direction(jseg) )  
    1192            CASE(0)  ;   k = sec%listPoint(jseg)  
    1193            CASE(1)  ;   k = POINT_SECTION(sec%listPoint(jseg)%I+1,sec%listPoint(jseg)%J)  
    1194            CASE(2)  ;   k = sec%listPoint(jseg)  
    1195            CASE(3)  ;   k = POINT_SECTION(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J+1)  
    1196            END SELECT  
    1197   
    1198            !---------------------------|  
    1199            !     LOOP ON THE LEVEL     |  
    1200            !---------------------------|  
    1201            !Sum of the transport on the vertical   
    1202            DO jk=1,mbathy(k%I,k%J)  
    1203   
    1204               ! compute temperature, salinity, insitu & potential density, ssh and depth at U/V point  
    1205               SELECT CASE( sec%direction(jseg) )  
    1206               CASE(0,1)  
    1207                  ztn   = interp(k%I,k%J,jk,'V',0 )  
    1208                  zsn   = interp(k%I,k%J,jk,'V',1 )  
    1209                  zrhop = interp(k%I,k%J,jk,'V',2)  
    1210                  zrhoi = interp(k%I,k%J,jk,'V',3)  
    1211  
    1212               CASE(2,3)  
    1213                  ztn   = interp(k%I,k%J,jk,'U',0 )  
    1214                  zsn   = interp(k%I,k%J,jk,'U',1 )  
    1215                  zrhop = interp(k%I,k%J,jk,'U',2 )  
    1216                  zrhoi = interp(k%I,k%J,jk,'U',3 )  
    1217                  zsshn =  0.5*( sshn(k%I,k%J)    + sshn(k%I+1,k%J)    ) * umask(k%I,k%J,1)   
    1218               END SELECT  
    1219   
    1220               zfsdep= fsdept(k%I,k%J,jk)  
    1221    
    1222               !-------------------------------  
    1223               !  LOOP ON THE DENSITY CLASSES |  
    1224               !-------------------------------  
    1225               !The computation is made for each density/temperature/salinity/depth class  
    1226               DO jclass=1,MAX(1,sec%nb_class-1)  
    1227   
    1228                  !----------------------------------------------!  
    1229                  !TEST ON THE DENSITY/SALINITY/TEMPERATURE/LEVEL!   
    1230                  !----------------------------------------------!  
    1231  
    1232                  IF ( (                                                    &  
    1233                     ((( zrhop .GE. (sec%zsigp(jclass)+1000.  )) .AND.      &  
    1234                     (   zrhop .LE. (sec%zsigp(jclass+1)+1000. ))) .OR.     &  
    1235                     ( sec%zsigp(jclass) .EQ. 99.)) .AND.                   &  
    1236   
    1237                     ((( zrhoi .GE. (sec%zsigi(jclass) + 1000.  )) .AND.    &  
    1238                     (   zrhoi .LE. (sec%zsigi(jclass+1)+1000. ))) .OR.     &  
    1239                     ( sec%zsigi(jclass) .EQ. 99.)) .AND.                   &  
    1240   
    1241                     ((( zsn .GT. sec%zsal(jclass)) .AND.                   &  
    1242                     (   zsn .LE. sec%zsal(jclass+1))) .OR.                 &  
    1243                     ( sec%zsal(jclass) .EQ. 99.)) .AND.                    &  
    1244   
    1245                     ((( ztn .GE. sec%ztem(jclass)) .AND.                   &  
    1246                     (   ztn .LE. sec%ztem(jclass+1))) .OR.                 &  
    1247                     ( sec%ztem(jclass) .EQ.99.)) .AND.                     &  
    1248   
    1249                     ((( zfsdep .GE. sec%zlay(jclass)) .AND.                &  
    1250                     (   zfsdep .LE. sec%zlay(jclass+1))) .OR.              &  
    1251                     ( sec%zlay(jclass) .EQ. 99. ))                         &  
    1252                                                                    ))   THEN  
    1253   
    1254                     !SUM THE TRANSPORTS FOR EACH CLASSES FOR THE POSITIVE AND NEGATIVE DIRECTIONS  
    1255                     !----------------------------------------------------------------------------  
    1256                     IF (transports_3d(1,jsec,jseg,jk) .GE. 0.0) THEN   
    1257                        sec%transport(1,jclass) = sec%transport(1,jclass)+transports_3d(1,jsec,jseg,jk)*1.E-6  
    1258                     ELSE  
    1259                        sec%transport(2,jclass) = sec%transport(2,jclass)+transports_3d(1,jsec,jseg,jk)*1.E-6  
    1260                     ENDIF  
    1261                     IF( sec%llstrpond )THEN  
    1262   
    1263                        IF ( transports_3d(2,jsec,jseg,jk) .GE. 0.0 ) THEN  
    1264                           sec%transport(3,jclass) = sec%transport(3,jclass)+transports_3d(2,jsec,jseg,jk)  
    1265                        ELSE  
    1266                           sec%transport(4,jclass) = sec%transport(4,jclass)+transports_3d(2,jsec,jseg,jk)  
    1267                        ENDIF  
    1268   
    1269                        IF ( transports_3d(3,jsec,jseg,jk) .GE. 0.0 ) THEN  
    1270                           sec%transport(5,jclass) = sec%transport(5,jclass)+transports_3d(3,jsec,jseg,jk)  
    1271                        ELSE  
    1272                           sec%transport(6,jclass) = sec%transport(6,jclass)+transports_3d(3,jsec,jseg,jk)  
    1273                        ENDIF  
    1274  
    1275                        IF ( transports_3d(4,jsec,jseg,jk) .GE. 0.0 ) THEN 
    1276                           sec%transport(7,jclass) = sec%transport(7,jclass)+transports_3d(4,jsec,jseg,jk) 
    1277                        ELSE 
    1278                           sec%transport(8,jclass) = sec%transport(8,jclass)+transports_3d(4,jsec,jseg,jk) 
    1279                        ENDIF 
    1280  
    1281                        IF ( transports_3d(5,jsec,jseg,jk) .GE. 0.0 ) THEN 
    1282                           sec%transport( 9,jclass) = sec%transport( 9,jclass)+transports_3d(5,jsec,jseg,jk) 
    1283                        ELSE 
    1284                           sec%transport(10,jclass) = sec%transport(10,jclass)+transports_3d(5,jsec,jseg,jk) 
    1285                        ENDIF 
    1286   
    1287                     ELSE  
    1288                        sec%transport( 3,jclass) = 0._wp  
    1289                        sec%transport( 4,jclass) = 0._wp  
    1290                        sec%transport( 5,jclass) = 0._wp  
    1291                        sec%transport( 6,jclass) = 0._wp  
    1292                        sec%transport( 7,jclass) = 0._wp 
    1293                        sec%transport( 8,jclass) = 0._wp 
    1294                        sec%transport( 9,jclass) = 0._wp 
    1295                        sec%transport(10,jclass) = 0._wp 
    1296                     ENDIF  
    1297   
    1298                  ENDIF ! end of test if point is in class  
    1299      
    1300               ENDDO ! end of loop on the classes  
    1301   
    1302            ENDDO ! loop over jk  
    1303   
    1304 #if defined key_lim2 || defined key_lim3  
    1305   
    1306            !ICE CASE      
    1307            IF( sec%ll_ice_section )THEN  
    1308   
    1309               IF ( transports_2d(1,jsec,jseg) .GE. 0.0 ) THEN  
    1310                  sec%transport(11,1) = sec%transport(11,1)+transports_2d(1,jsec,jseg)*1.E-6  
    1311               ELSE  
    1312                  sec%transport(12,1) = sec%transport(12,1)+transports_2d(1,jsec,jseg)*1.E-6  
    1313               ENDIF  
    1314   
    1315               IF ( transports_2d(3,jsec,jseg) .GE. 0.0 ) THEN  
    1316                  sec%transport(13,1) = sec%transport(13,1)+transports_2d(2,jsec,jseg)*1.E-6  
    1317               ELSE  
    1318                  sec%transport(14,1) = sec%transport(14,1)+transports_2d(2,jsec,jseg)*1.E-6  
    1319               ENDIF  
    1320   
    1321            ENDIF !end of ice case  
    1322 #endif  
    1323    
    1324         ENDDO !end of loop on the segment  
    1325   
    1326      ELSE  !if sec%nb_point =0  
    1327         sec%transport(1:2,:)=0.  
    1328         IF (sec%llstrpond) sec%transport(3:10,:)=0.  
    1329         IF (sec%ll_ice_section) sec%transport(11:14,:)=0.  
    1330      ENDIF !end of sec%nb_point =0 case  
    1331   
    1332   END SUBROUTINE dia_dct_sum  
    1333  
    1334   SUBROUTINE dia_dct_sum_h(sec,jsec) 
    1335      !!------------------------------------------------------------- 
    1336      !! Exactly as dia_dct_sum but for hourly files containing data summed at each time step 
    1337      !! 
    1338      !! Purpose: Average the transport over nn_dctwri time steps  
    1339      !! and sum over the density/salinity/temperature/depth classes 
    1340      !! 
    1341      !! Method:  
    1342      !!           Sum over relevant grid cells to obtain values 
    1343      !!           for each 
    1344      !!              There are several loops:                  
    1345      !!              loop on the segment between 2 nodes 
    1346      !!              loop on the level jk 
    1347      !!              loop on the density/temperature/salinity/level classes 
    1348      !!              test on the density/temperature/salinity/level 
    1349      !! 
    1350      !!  ** Method  :Transport through a given section is equal to the sum of transports 
    1351      !!              computed on each proc. 
    1352      !!              On each proc,transport is equal to the sum of transport computed through 
    1353      !!              segments linking each point of sec%listPoint  with the next one.    
    1354      !! 
    1355      !!------------------------------------------------------------- 
    1356      !! * arguments 
    1357      TYPE(SECTION),INTENT(INOUT) :: sec 
    1358      INTEGER      ,INTENT(IN)    :: jsec        ! numeric identifier of section 
    1359  
    1360      TYPE(POINT_SECTION) :: k 
    1361      INTEGER  :: jk,jseg,jclass                        !loop on level/segment/classes  
    1362      REAL(wp) :: ztn, zsn, zrhoi, zrhop, zsshn, zfsdep ! temperature/salinity/ssh/potential density /depth at u/v point 
    1363      !!------------------------------------------------------------- 
     1397 
    13641398 
    13651399     !! Sum the relevant segments to obtain values for each class 
     
    14161450              SELECT CASE( sec%direction(jseg) ) 
    14171451              CASE(0,1) 
    1418                  ztn   = interp(k%I,k%J,jk,'V',0 ) 
    1419                  zsn   = interp(k%I,k%J,jk,'V',1 ) 
    1420                  zrhop = interp(k%I,k%J,jk,'V',2 ) 
    1421                  zrhoi = interp(k%I,k%J,jk,'V',3 ) 
     1452                 ztn   = interp(k%I,k%J,jk,'V',0) 
     1453                 zsn   = interp(k%I,k%J,jk,'V',1) 
     1454                 zrhop = interp(k%I,k%J,jk,'V',2) 
     1455                 zrhoi = interp(k%I,k%J,jk,'V',3) 
    14221456                 zsshn =  0.5*( sshn(k%I,k%J)    + sshn(k%I,k%J+1)    ) * vmask(k%I,k%J,1) 
    14231457              CASE(2,3) 
    1424                  ztn   = interp(k%I,k%J,jk,'U',0 ) 
    1425                  zsn   = interp(k%I,k%J,jk,'U',1 ) 
    1426                  zrhop = interp(k%I,k%J,jk,'U',2 ) 
    1427                  zrhoi = interp(k%I,k%J,jk,'U',3 ) 
     1458                 ztn   = interp(k%I,k%J,jk,'U',0) 
     1459                 zsn   = interp(k%I,k%J,jk,'U',1) 
     1460                 zrhop = interp(k%I,k%J,jk,'U',2) 
     1461                 zrhoi = interp(k%I,k%J,jk,'U',3) 
     1462                 zsshn =  0.5*( sshn(k%I,k%J)    + sshn(k%I+1,k%J)    ) * umask(k%I,k%J,1)  
     1463              END SELECT 
     1464 
     1465              zfsdep= fsdept(k%I,k%J,jk)  
     1466  
     1467              !------------------------------- 
     1468              !  LOOP ON THE DENSITY CLASSES | 
     1469              !------------------------------- 
     1470              !The computation is made for each density/temperature/salinity/depth class 
     1471              DO jclass=1,MAX(1,sec%nb_class-1) 
     1472  
     1473                 !----------------------------------------------! 
     1474                 !TEST ON THE DENSITY/SALINITY/TEMPERATURE/LEVEL!  
     1475                 !----------------------------------------------! 
     1476  
     1477                 IF ( (                                                    & 
     1478                    ((( zrhop .GE. (sec%zsigp(jclass)+1000.  )) .AND.      & 
     1479                    (   zrhop .LE. (sec%zsigp(jclass+1)+1000. ))) .OR.     & 
     1480                    ( sec%zsigp(jclass) .EQ. 99.)) .AND.                   & 
     1481 
     1482                    ((( zrhoi .GE. (sec%zsigi(jclass) + 1000.  )) .AND.    & 
     1483                    (   zrhoi .LE. (sec%zsigi(jclass+1)+1000. ))) .OR.     & 
     1484                    ( sec%zsigi(jclass) .EQ. 99.)) .AND.                   & 
     1485 
     1486                    ((( zsn .GT. sec%zsal(jclass)) .AND.                   & 
     1487                    (   zsn .LE. sec%zsal(jclass+1))) .OR.                 & 
     1488                    ( sec%zsal(jclass) .EQ. 99.)) .AND.                    & 
     1489 
     1490                    ((( ztn .GE. sec%ztem(jclass)) .AND.                   & 
     1491                    (   ztn .LE. sec%ztem(jclass+1))) .OR.                 & 
     1492                    ( sec%ztem(jclass) .EQ.99.)) .AND.                     & 
     1493 
     1494                    ((( zfsdep .GE. sec%zlay(jclass)) .AND.                & 
     1495                    (   zfsdep .LE. sec%zlay(jclass+1))) .OR.              & 
     1496                    ( sec%zlay(jclass) .EQ. 99. ))                         & 
     1497                                                                   ))   THEN 
     1498 
     1499                    !SUM THE TRANSPORTS FOR EACH CLASSES FOR THE POSITIVE AND NEGATIVE DIRECTIONS 
     1500                    !---------------------------------------------------------------------------- 
     1501                    IF (transports_3d(1,jsec,jseg,jk) .GE. 0.0) THEN  
     1502                       sec%transport(1,jclass) = sec%transport(1,jclass)+transports_3d(1,jsec,jseg,jk) 
     1503                    ELSE 
     1504                       sec%transport(2,jclass) = sec%transport(2,jclass)+transports_3d(1,jsec,jseg,jk) 
     1505                    ENDIF 
     1506                    IF( sec%llstrpond )THEN 
     1507 
     1508                       IF( transports_3d(1,jsec,jseg,jk) .NE. 0._wp ) THEN 
     1509 
     1510                          IF (transports_3d(2,jsec,jseg,jk)/transports_3d(1,jsec,jseg,jk) .GE. 0.0 ) THEN 
     1511                             sec%transport(3,jclass) = sec%transport(3,jclass)+transports_3d(2,jsec,jseg,jk)/transports_3d(1,jsec,jseg,jk) 
     1512                          ELSE 
     1513                             sec%transport(4,jclass) = sec%transport(4,jclass)+transports_3d(2,jsec,jseg,jk)/transports_3d(1,jsec,jseg,jk) 
     1514                          ENDIF 
     1515 
     1516                          IF ( transports_3d(3,jsec,jseg,jk)/transports_3d(1,jsec,jseg,jk) .GE. 0.0 ) THEN 
     1517                             sec%transport(5,jclass) = sec%transport(5,jclass)+transports_3d(3,jsec,jseg,jk)/transports_3d(1,jsec,jseg,jk) 
     1518                          ELSE 
     1519                             sec%transport(6,jclass) = sec%transport(6,jclass)+transports_3d(3,jsec,jseg,jk)/transports_3d(1,jsec,jseg,jk) 
     1520                          ENDIF 
     1521 
     1522                       ENDIF 
     1523 
     1524                       IF ( transports_3d(4,jsec,jseg,jk) .GE. 0.0 ) THEN 
     1525                          sec%transport(7,jclass) = sec%transport(7,jclass)+transports_3d(4,jsec,jseg,jk) 
     1526                       ELSE 
     1527                          sec%transport(8,jclass) = sec%transport(8,jclass)+transports_3d(4,jsec,jseg,jk) 
     1528                       ENDIF 
     1529 
     1530                       IF ( transports_3d(5,jsec,jseg,jk) .GE. 0.0 ) THEN 
     1531                          sec%transport( 9,jclass) = sec%transport( 9,jclass)+transports_3d(5,jsec,jseg,jk) 
     1532                       ELSE 
     1533                          sec%transport(10,jclass) = sec%transport(10,jclass)+transports_3d(5,jsec,jseg,jk) 
     1534                       ENDIF 
     1535  
     1536                    ELSE  
     1537                       sec%transport( 3,jclass) = 0._wp  
     1538                       sec%transport( 4,jclass) = 0._wp  
     1539                       sec%transport( 5,jclass) = 0._wp  
     1540                       sec%transport( 6,jclass) = 0._wp  
     1541                       sec%transport( 7,jclass) = 0._wp 
     1542                       sec%transport( 8,jclass) = 0._wp 
     1543                       sec%transport( 9,jclass) = 0._wp 
     1544                       sec%transport(10,jclass) = 0._wp 
     1545                    ENDIF  
     1546  
     1547                 ENDIF ! end of test if point is in class  
     1548     
     1549              ENDDO ! end of loop on the classes  
     1550  
     1551           ENDDO ! loop over jk  
     1552  
     1553#if defined key_lim2 || defined key_lim3  
     1554  
     1555           !ICE CASE      
     1556           IF( sec%ll_ice_section )THEN  
     1557  
     1558              IF ( transports_2d(1,jsec,jseg) .GE. 0.0 ) THEN  
     1559                 sec%transport(11,1) = sec%transport(11,1)+transports_2d(1,jsec,jseg) 
     1560              ELSE  
     1561                 sec%transport(12,1) = sec%transport(12,1)+transports_2d(1,jsec,jseg) 
     1562              ENDIF  
     1563  
     1564              IF ( transports_2d(3,jsec,jseg) .GE. 0.0 ) THEN  
     1565                 sec%transport(13,1) = sec%transport(13,1)+transports_2d(2,jsec,jseg) 
     1566              ELSE  
     1567                 sec%transport(14,1) = sec%transport(14,1)+transports_2d(2,jsec,jseg) 
     1568              ENDIF  
     1569  
     1570           ENDIF !end of ice case  
     1571#endif  
     1572  
     1573        ENDDO !end of loop on the segment 
     1574 
     1575     ELSE  !if sec%nb_point =0 
     1576        sec%transport(1:2,:)=0. 
     1577        IF (sec%llstrpond) sec%transport(3:10,:)=0. 
     1578        IF (sec%ll_ice_section) sec%transport( 11:14,:)=0. 
     1579     ENDIF !end of sec%nb_point =0 case 
     1580 
     1581  END SUBROUTINE dia_dct_sum 
     1582  
     1583  SUBROUTINE dia_dct_sum_h(sec,jsec) 
     1584     !!------------------------------------------------------------- 
     1585     !! Exactly as dia_dct_sum but for hourly files containing data summed at each time step 
     1586     !! 
     1587     !! Purpose: Average the transport over nn_dctwri time steps  
     1588     !! and sum over the density/salinity/temperature/depth classes 
     1589     !! 
     1590     !! Method:  
     1591     !!           Sum over relevant grid cells to obtain values 
     1592     !!           for each 
     1593     !!              There are several loops:                  
     1594     !!              loop on the segment between 2 nodes 
     1595     !!              loop on the level jk 
     1596     !!              loop on the density/temperature/salinity/level classes 
     1597     !!              test on the density/temperature/salinity/level 
     1598     !! 
     1599     !!  ** Method  :Transport through a given section is equal to the sum of transports 
     1600     !!              computed on each proc. 
     1601     !!              On each proc,transport is equal to the sum of transport computed through 
     1602     !!              segments linking each point of sec%listPoint  with the next one.    
     1603     !! 
     1604     !!------------------------------------------------------------- 
     1605     !! * arguments 
     1606     TYPE(SECTION),INTENT(INOUT) :: sec 
     1607     INTEGER      ,INTENT(IN)    :: jsec        ! numeric identifier of section 
     1608 
     1609     TYPE(POINT_SECTION) :: k 
     1610     INTEGER  :: jk,jseg,jclass                        !loop on level/segment/classes  
     1611     REAL(wp) :: ztn, zsn, zrhoi, zrhop, zsshn, zfsdep ! temperature/salinity/ssh/potential density /depth at u/v point 
     1612     !!------------------------------------------------------------- 
     1613 
     1614     !! Sum the relevant segments to obtain values for each class 
     1615     IF(sec%nb_point .NE. 0)THEN    
     1616 
     1617        !--------------------------------------! 
     1618        ! LOOP ON THE SEGMENT BETWEEN 2 NODES  ! 
     1619        !--------------------------------------! 
     1620        DO jseg=1,MAX(sec%nb_point-1,0) 
     1621            
     1622           !------------------------------------------------------------------------------------------- 
     1623           ! Select the appropriate coordinate for computing the velocity of the segment 
     1624           ! 
     1625           !                      CASE(0)                                    Case (2) 
     1626           !                      -------                                    -------- 
     1627           !  listPoint(jseg)                 listPoint(jseg+1)       listPoint(jseg)  F(i,j)       
     1628           !      F(i,j)----------V(i+1,j)-------F(i+1,j)                               | 
     1629           !                                                                            | 
     1630           !                                                                            | 
     1631           !                                                                            | 
     1632           !                      Case (3)                                            U(i,j) 
     1633           !                      --------                                              | 
     1634           !                                                                            | 
     1635           !  listPoint(jseg+1) F(i,j+1)                                                | 
     1636           !                        |                                                   | 
     1637           !                        |                                                   | 
     1638           !                        |                                 listPoint(jseg+1) F(i,j-1) 
     1639           !                        |                                             
     1640           !                        |                                             
     1641           !                     U(i,j+1)                                             
     1642           !                        |                                       Case(1)      
     1643           !                        |                                       ------       
     1644           !                        |                                             
     1645           !                        |                 listPoint(jseg+1)             listPoint(jseg)                            
     1646           !                        |                 F(i-1,j)-----------V(i,j) -------f(jseg)                            
     1647           ! listPoint(jseg)     F(i,j) 
     1648           !  
     1649           !------------------------------------------------------------------------------------------- 
     1650 
     1651           SELECT CASE( sec%direction(jseg) ) 
     1652           CASE(0)  ;   k = sec%listPoint(jseg) 
     1653           CASE(1)  ;   k = POINT_SECTION(sec%listPoint(jseg)%I+1,sec%listPoint(jseg)%J) 
     1654           CASE(2)  ;   k = sec%listPoint(jseg) 
     1655           CASE(3)  ;   k = POINT_SECTION(sec%listPoint(jseg)%I,sec%listPoint(jseg)%J+1) 
     1656           END SELECT 
     1657 
     1658           !---------------------------| 
     1659           !     LOOP ON THE LEVEL     | 
     1660           !---------------------------| 
     1661           !Sum of the transport on the vertical  
     1662           DO jk=1,mbathy(k%I,k%J) 
     1663 
     1664              ! compute temperature, salinity, insitu & potential density, ssh and depth at U/V point 
     1665              SELECT CASE( sec%direction(jseg) ) 
     1666              CASE(0,1) 
     1667                 ztn   = interp(k%I,k%J,jk,'V',0) 
     1668                 zsn   = interp(k%I,k%J,jk,'V',1) 
     1669                 zrhop = interp(k%I,k%J,jk,'V',2) 
     1670                 zrhoi = interp(k%I,k%J,jk,'V',3) 
     1671                 zsshn =  0.5*( sshn(k%I,k%J)    + sshn(k%I,k%J+1)    ) * vmask(k%I,k%J,1) 
     1672              CASE(2,3) 
     1673                 ztn   = interp(k%I,k%J,jk,'U',0) 
     1674                 zsn   = interp(k%I,k%J,jk,'U',1) 
     1675                 zrhop = interp(k%I,k%J,jk,'U',2) 
     1676                 zrhoi = interp(k%I,k%J,jk,'U',3) 
    14281677                 zsshn =  0.5*( sshn(k%I,k%J)    + sshn(k%I+1,k%J)    ) * umask(k%I,k%J,1)  
    14291678              END SELECT 
     
    14721721                    IF( sec%llstrpond )THEN 
    14731722 
    1474                        IF ( transports_3d_h(2,jsec,jseg,jk) .GE. 0.0 ) THEN  
    1475                           sec%transport_h(3,jclass) = sec%transport_h(3,jclass)+transports_3d_h(2,jsec,jseg,jk)  
    1476                        ELSE  
    1477                           sec%transport_h(4,jclass) = sec%transport_h(4,jclass)+transports_3d_h(2,jsec,jseg,jk)  
    1478                        ENDIF  
    1479   
    1480                        IF ( transports_3d_h(3,jsec,jseg,jk) .GE. 0.0 ) THEN  
    1481                           sec%transport_h(5,jclass) = sec%transport_h(5,jclass)+transports_3d_h(3,jsec,jseg,jk)  
    1482                        ELSE  
    1483                           sec%transport_h(6,jclass) = sec%transport_h(6,jclass)+transports_3d_h(3,jsec,jseg,jk)  
    1484                        ENDIF  
     1723                       IF( transports_3d_h(1,jsec,jseg,jk) .NE. 0._wp ) THEN 
     1724 
     1725                          IF (transports_3d_h(2,jsec,jseg,jk)/transports_3d_h(1,jsec,jseg,jk) .GE. 0.0 ) THEN 
     1726                             sec%transport_h(3,jclass) = sec%transport_h(3,jclass)+transports_3d_h(2,jsec,jseg,jk)/transports_3d_h(1,jsec,jseg,jk) 
     1727                          ELSE 
     1728                             sec%transport_h(4,jclass) = sec%transport_h(4,jclass)+transports_3d_h(2,jsec,jseg,jk)/transports_3d_h(1,jsec,jseg,jk) 
     1729                          ENDIF 
     1730 
     1731                          IF ( transports_3d_h(3,jsec,jseg,jk)/transports_3d_h(1,jsec,jseg,jk) .GE. 0.0 ) THEN 
     1732                             sec%transport_h(5,jclass) = sec%transport_h(5,jclass)+transports_3d_h(3,jsec,jseg,jk)/transports_3d_h(1,jsec,jseg,jk) 
     1733                          ELSE 
     1734                             sec%transport_h(6,jclass) = sec%transport_h(6,jclass)+transports_3d_h(3,jsec,jseg,jk)/transports_3d_h(1,jsec,jseg,jk) 
     1735                          ENDIF 
     1736 
     1737                       ENDIF 
    14851738 
    14861739                       IF ( transports_3d_h(4,jsec,jseg,jk) .GE. 0.0 ) THEN 
     
    15721825     ! 
    15731826     REAL(wp), POINTER, DIMENSION(:):: zsumclasses ! 1D workspace  
     1827     CHARACTER(len=3)      :: noos_sect_name             ! Classname  
     1828     CHARACTER(len=25)      :: noos_var_sect_name 
     1829     REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   noos_iom_dummy 
     1830     INTEGER               :: IERR 
     1831      
     1832     REAL(wp), DIMENSION(3) :: tmp_iom_output 
     1833     REAL(wp)               :: max_iom_val 
     1834     LOGICAL       ::   verbose      
     1835     verbose = .false. 
     1836      
    15741837     !!-------------------------------------------------------------  
     1838      
     1839      
     1840      
     1841     IF( lwp .AND. verbose ) THEN 
     1842        WRITE(numout,*) " " 
     1843        WRITE(numout,*) "dia_dct_wri_NOOS: write transports through sections at timestep: ", kt 
     1844        WRITE(numout,*) "~~~~~~~~~~~~~~~~~~~~~" 
     1845     ENDIF    
     1846         
    15751847     CALL wrk_alloc(nb_type_class , zsumclasses )   
    15761848 
    15771849     zsumclasses(:)=0._wp 
    15781850     zslope = sec%slopeSection        
    1579  
    1580      WRITE(numdct_NOOS,'(I4,a1,I2,a1,I2,a12,i3,a17,i3,a10,a25)') nyear,'.',nmonth,'.',nday,'   Transect:',ksec-1,'   No. of layers:',sec%nb_class-1,'   Name: ',sec%name 
    1581  
     1851      
     1852     IF( lwp ) THEN 
     1853         IF  ( ln_dct_ascii ) THEN 
     1854             WRITE(numdct_NOOS,'(I4,a1,I2,a1,I2,a12,i3,a17,i3,a10,a25)') nyear,'.',nmonth,'.',nday,'   Transect:',ksec-1,'   No. of layers:',sec%nb_class-1,'   Name: ',sec%name 
     1855         ELSE 
     1856             WRITE(numdct_NOOS) nyear,nmonth,nday,ksec-1,sec%nb_class-1,sec%name 
     1857         ENDIF   
     1858     ENDIF 
     1859     
     1860     ! Sum all classes together, to give one values per type (pos tran, neg vol trans etc...).  
    15821861     DO jclass=1,MAX(1,sec%nb_class-1) 
    15831862        zsumclasses(1:nb_type_class)=zsumclasses(1:nb_type_class)+sec%transport(1:nb_type_class,jclass) 
     
    15871866     zbnd1   = 0._wp 
    15881867     zbnd2   = 0._wp 
    1589  
    1590      IF ( zslope .gt. 0._wp .and. zslope .ne. 10000._wp ) THEN 
    1591         WRITE(numdct_NOOS,'(9e12.4E2)') -(zsumclasses( 1)+zsumclasses( 2)), -zsumclasses( 2),-zsumclasses( 1),   & 
    1592                                         -(zsumclasses( 7)+zsumclasses( 8)), -zsumclasses( 8),-zsumclasses( 7),   & 
    1593                                         -(zsumclasses( 9)+zsumclasses(10)), -zsumclasses(10),-zsumclasses( 9) 
    1594      ELSE 
    1595         WRITE(numdct_NOOS,'(9e12.4E2)')   zsumclasses( 1)+zsumclasses( 2) ,  zsumclasses( 1), zsumclasses( 2),   & 
    1596                                           zsumclasses( 7)+zsumclasses( 8) ,  zsumclasses( 7), zsumclasses( 8),   & 
    1597                                           zsumclasses( 9)+zsumclasses(10) ,  zsumclasses( 9), zsumclasses(10) 
    1598      ENDIF  
     1868      
     1869      
     1870      
     1871     write (noos_sect_name, "(I0.3)")  ksec 
     1872      
     1873     IF ( ln_dct_iom_cont ) THEN 
     1874         max_iom_val = 1.e10 
     1875         ALLOCATE( noos_iom_dummy(jpi,jpj,3),  STAT= ierr ) 
     1876            IF( ierr /= 0 )   CALL ctl_stop( 'dia_dct_wri_NOOS: failed to allocate noos_iom_dummy array' ) 
     1877     ENDIF 
     1878      
     1879!     JT   I think changing the sign on the output based on the zslope value is redunant. 
     1880! 
     1881!     IF ( zslope .gt. 0._wp .and. zslope .ne. 10000._wp ) THEN 
     1882!          
     1883!         IF( lwp ) THEN 
     1884!             WRITE(numdct_NOOS,'(9e12.4E2)') -(zsumclasses( 1)+zsumclasses( 2)), -zsumclasses( 2),-zsumclasses( 1),   & 
     1885!                                            -(zsumclasses( 7)+zsumclasses( 8)), -zsumclasses( 8),-zsumclasses( 7),   & 
     1886!                                            -(zsumclasses( 9)+zsumclasses(10)), -zsumclasses(10),-zsumclasses( 9) 
     1887!             CALL FLUSH(numdct_NOOS)  
     1888!         endif 
     1889 
     1890!          
     1891!         IF ( ln_dct_iom_cont ) THEN 
     1892!          
     1893!             noos_iom_dummy(:,:,:) = 0. 
     1894!              
     1895!             tmp_iom_output(:) = 0. 
     1896!             tmp_iom_output(1) = -(zsumclasses( 1)+zsumclasses( 2)) 
     1897!             tmp_iom_output(2) = -zsumclasses( 2) 
     1898!             tmp_iom_output(3) = -zsumclasses( 1) 
     1899!              
     1900!             ! Convert to Sv  
     1901!             tmp_iom_output(1) = tmp_iom_output(1)*1.E-6 
     1902!             tmp_iom_output(2) = tmp_iom_output(2)*1.E-6 
     1903!             tmp_iom_output(3) = tmp_iom_output(3)*1.E-6 
     1904!              
     1905!             ! limit maximum and minimum values in iom_put 
     1906!             if ( tmp_iom_output(1) .gt.  max_iom_val ) tmp_iom_output(1) =  max_iom_val 
     1907!             if ( tmp_iom_output(1) .lt. -max_iom_val ) tmp_iom_output(1) = -max_iom_val 
     1908!             if ( tmp_iom_output(2) .gt.  max_iom_val ) tmp_iom_output(2) =  max_iom_val 
     1909!             if ( tmp_iom_output(2) .lt. -max_iom_val ) tmp_iom_output(2) = -max_iom_val 
     1910!             if ( tmp_iom_output(3) .gt.  max_iom_val ) tmp_iom_output(3) =  max_iom_val 
     1911!             if ( tmp_iom_output(3) .lt. -max_iom_val ) tmp_iom_output(3) = -max_iom_val 
     1912!              
     1913!             ! Set NaN's to Zero          
     1914!             if ( tmp_iom_output(1) .ne.  tmp_iom_output(1) ) tmp_iom_output(1) =  max_iom_val*2 
     1915!             if ( tmp_iom_output(2) .ne.  tmp_iom_output(2) ) tmp_iom_output(1) =  max_iom_val*2 
     1916!             if ( tmp_iom_output(3) .ne.  tmp_iom_output(3) ) tmp_iom_output(1) =  max_iom_val*2 
     1917!              
     1918!             noos_iom_dummy(:,:,1) = tmp_iom_output(1) 
     1919!             noos_iom_dummy(:,:,2) = tmp_iom_output(2) 
     1920!             noos_iom_dummy(:,:,3) = tmp_iom_output(3) 
     1921!              
     1922!             noos_var_sect_name = "noos_" // trim(noos_sect_name) // '_trans' 
     1923!             if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 
     1924!             CALL iom_put( noos_var_sect_name,  noos_iom_dummy ) 
     1925!             noos_iom_dummy(:,:,:) = 0.          
     1926!             tmp_iom_output(:) = 0. 
     1927!             tmp_iom_output(1) = -(zsumclasses( 7)+zsumclasses( 8)) 
     1928!             tmp_iom_output(2) = -zsumclasses( 8) 
     1929!             tmp_iom_output(3) = -zsumclasses( 7) 
     1930!              
     1931!             ! Convert to TJ/s 
     1932!             tmp_iom_output(1) = tmp_iom_output(1)*1.E-12 
     1933!             tmp_iom_output(2) = tmp_iom_output(2)*1.E-12 
     1934!             tmp_iom_output(3) = tmp_iom_output(3)*1.E-12 
     1935!              
     1936!             ! limit maximum and minimum values in iom_put 
     1937!             if ( tmp_iom_output(1) .gt.  max_iom_val ) tmp_iom_output(1) =  max_iom_val 
     1938!             if ( tmp_iom_output(1) .lt. -max_iom_val ) tmp_iom_output(1) = -max_iom_val 
     1939!             if ( tmp_iom_output(2) .gt.  max_iom_val ) tmp_iom_output(2) =  max_iom_val 
     1940!             if ( tmp_iom_output(2) .lt. -max_iom_val ) tmp_iom_output(2) = -max_iom_val 
     1941!             if ( tmp_iom_output(3) .gt.  max_iom_val ) tmp_iom_output(3) =  max_iom_val 
     1942!             if ( tmp_iom_output(3) .lt. -max_iom_val ) tmp_iom_output(3) = -max_iom_val 
     1943!              
     1944!             ! Set NaN's to Zero          
     1945!             if ( tmp_iom_output(1) .ne.  tmp_iom_output(1) ) tmp_iom_output(1) =  max_iom_val*2 
     1946!             if ( tmp_iom_output(2) .ne.  tmp_iom_output(2) ) tmp_iom_output(1) =  max_iom_val*2 
     1947!             if ( tmp_iom_output(3) .ne.  tmp_iom_output(3) ) tmp_iom_output(1) =  max_iom_val*2 
     1948!              
     1949!             noos_iom_dummy(:,:,1) = tmp_iom_output(1) 
     1950!             noos_iom_dummy(:,:,2) = tmp_iom_output(2) 
     1951!             noos_iom_dummy(:,:,3) = tmp_iom_output(3) 
     1952!              
     1953!             !noos_iom_dummy(:,:,1) = -(zsumclasses( 7)+zsumclasses( 8)) 
     1954!             !noos_iom_dummy(:,:,2) = -zsumclasses( 8) 
     1955!             !noos_iom_dummy(:,:,3) = -zsumclasses( 7) 
     1956!              
     1957!             noos_var_sect_name =  "noos_" // trim(noos_sect_name) // '_heat' 
     1958!             if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 
     1959!             CALL iom_put( noos_var_sect_name,  noos_iom_dummy ) 
     1960!               
     1961!             noos_iom_dummy(:,:,:) = 0.          
     1962!             tmp_iom_output(:) = 0.          
     1963!             tmp_iom_output(1) = -(zsumclasses( 9)+zsumclasses( 10)) 
     1964!             tmp_iom_output(2) = -zsumclasses( 10) 
     1965!             tmp_iom_output(3) = -zsumclasses( 9) 
     1966!              
     1967!             ! Convert to  MT/s 
     1968!             tmp_iom_output(1) = tmp_iom_output(1)*1.E-6 
     1969!             tmp_iom_output(2) = tmp_iom_output(2)*1.E-6 
     1970!             tmp_iom_output(3) = tmp_iom_output(3)*1.E-6 
     1971!              
     1972!             ! limit maximum and minimum values in iom_put 
     1973!             if ( tmp_iom_output(1) .gt.  max_iom_val ) tmp_iom_output(1) =  max_iom_val 
     1974!             if ( tmp_iom_output(1) .lt. -max_iom_val ) tmp_iom_output(1) = -max_iom_val 
     1975!             if ( tmp_iom_output(2) .gt.  max_iom_val ) tmp_iom_output(2) =  max_iom_val 
     1976!             if ( tmp_iom_output(2) .lt. -max_iom_val ) tmp_iom_output(2) = -max_iom_val 
     1977!             if ( tmp_iom_output(3) .gt.  max_iom_val ) tmp_iom_output(3) =  max_iom_val 
     1978!             if ( tmp_iom_output(3) .lt. -max_iom_val ) tmp_iom_output(3) = -max_iom_val 
     1979!              
     1980!             ! Set NaN's to Zero          
     1981!             if ( tmp_iom_output(1) .ne.  tmp_iom_output(1) ) tmp_iom_output(1) =  max_iom_val*2 
     1982!             if ( tmp_iom_output(2) .ne.  tmp_iom_output(2) ) tmp_iom_output(1) =  max_iom_val*2 
     1983!             if ( tmp_iom_output(3) .ne.  tmp_iom_output(3) ) tmp_iom_output(1) =  max_iom_val*2 
     1984!              
     1985!             noos_iom_dummy(:,:,1) = tmp_iom_output(1) 
     1986!             noos_iom_dummy(:,:,2) = tmp_iom_output(2) 
     1987!             noos_iom_dummy(:,:,3) = tmp_iom_output(3) 
     1988!              
     1989!             !noos_iom_dummy(:,:,1) = -(zsumclasses( 9)+zsumclasses( 10)) 
     1990!             !noos_iom_dummy(:,:,2) = -zsumclasses( 10) 
     1991!             !noos_iom_dummy(:,:,3) = -zsumclasses( 9) 
     1992!              
     1993!             noos_var_sect_name =  "noos_" // trim(noos_sect_name) // '_salt' 
     1994!             if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 
     1995!             CALL iom_put( noos_var_sect_name,  noos_iom_dummy ) 
     1996!             noos_iom_dummy(:,:,:) = 0.      
     1997!             tmp_iom_output(:) = 0.     
     1998!         ENDIF 
     1999!     ELSE 
     2000!        IF( lwp ) THEN 
     2001!            WRITE(numdct_NOOS,'(9e12.4E2)')   zsumclasses( 1)+zsumclasses( 2) ,  zsumclasses( 1), zsumclasses( 2),   & 
     2002!                                            zsumclasses( 7)+zsumclasses( 8) ,  zsumclasses( 7), zsumclasses( 8),   & 
     2003!                                            zsumclasses( 9)+zsumclasses(10) ,  zsumclasses( 9), zsumclasses(10) 
     2004!            CALL FLUSH(numdct_NOOS)  
     2005!        endif 
     2006!          
     2007!          
     2008!        IF ( ln_dct_iom_cont ) THEN 
     2009!             
     2010!             noos_iom_dummy(:,:,:) = 0. 
     2011!             tmp_iom_output(:) = 0. 
     2012!              
     2013!             tmp_iom_output(1) = (zsumclasses( 1)+zsumclasses( 2)) 
     2014!             tmp_iom_output(2) = zsumclasses( 1) 
     2015!             tmp_iom_output(3) = zsumclasses( 2) 
     2016!              
     2017!             ! Convert to Sv 
     2018!             tmp_iom_output(1) = tmp_iom_output(1)*1.E-6 
     2019!             tmp_iom_output(2) = tmp_iom_output(2)*1.E-6 
     2020!             tmp_iom_output(3) = tmp_iom_output(3)*1.E-6 
     2021!              
     2022!             ! limit maximum and minimum values in iom_put 
     2023!             if ( tmp_iom_output(1) .gt.  max_iom_val ) tmp_iom_output(1) =  max_iom_val 
     2024!             if ( tmp_iom_output(1) .lt. -max_iom_val ) tmp_iom_output(1) = -max_iom_val 
     2025!             if ( tmp_iom_output(2) .gt.  max_iom_val ) tmp_iom_output(2) =  max_iom_val 
     2026!             if ( tmp_iom_output(2) .lt. -max_iom_val ) tmp_iom_output(2) = -max_iom_val 
     2027!             if ( tmp_iom_output(3) .gt.  max_iom_val ) tmp_iom_output(3) =  max_iom_val 
     2028!             if ( tmp_iom_output(3) .lt. -max_iom_val ) tmp_iom_output(3) = -max_iom_val 
     2029!              
     2030!             ! Set NaN's to Zero          
     2031!             if ( tmp_iom_output(1) .ne.  tmp_iom_output(1) ) tmp_iom_output(1) =  max_iom_val*2 
     2032!             if ( tmp_iom_output(2) .ne.  tmp_iom_output(2) ) tmp_iom_output(1) =  max_iom_val*2 
     2033!             if ( tmp_iom_output(3) .ne.  tmp_iom_output(3) ) tmp_iom_output(1) =  max_iom_val*2 
     2034!              
     2035!             noos_iom_dummy(:,:,1) = tmp_iom_output(1) 
     2036!             noos_iom_dummy(:,:,2) = tmp_iom_output(2) 
     2037!             noos_iom_dummy(:,:,3) = tmp_iom_output(3) 
     2038!              
     2039!             !noos_iom_dummy(:,:,1) = (zsumclasses( 1)+zsumclasses( 2)) 
     2040!             !noos_iom_dummy(:,:,2) = zsumclasses( 1) 
     2041!             !noos_iom_dummy(:,:,3) = zsumclasses( 2) 
     2042!              
     2043!              
     2044!              
     2045!             noos_var_sect_name = "noos_" // trim(noos_sect_name) // '_trans' 
     2046!             if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 
     2047!             CALL iom_put( noos_var_sect_name,  noos_iom_dummy ) 
     2048!             noos_iom_dummy(:,:,:) = 0. 
     2049!             tmp_iom_output(:) = 0. 
     2050!              
     2051!             tmp_iom_output(1) = (zsumclasses( 7)+zsumclasses( 8)) 
     2052!             tmp_iom_output(2) = zsumclasses( 7) 
     2053!             tmp_iom_output(3) = zsumclasses( 8) 
     2054!              
     2055!             ! Convert to TJ/s 
     2056!             tmp_iom_output(1) = tmp_iom_output(1)*1.E-12 
     2057!             tmp_iom_output(2) = tmp_iom_output(2)*1.E-12 
     2058!             tmp_iom_output(3) = tmp_iom_output(3)*1.E-12 
     2059!              
     2060!             ! limit maximum and minimum values in iom_put 
     2061!             if ( tmp_iom_output(1) .gt.  max_iom_val ) tmp_iom_output(1) =  max_iom_val 
     2062!             if ( tmp_iom_output(1) .lt. -max_iom_val ) tmp_iom_output(1) = -max_iom_val 
     2063!             if ( tmp_iom_output(2) .gt.  max_iom_val ) tmp_iom_output(2) =  max_iom_val 
     2064!             if ( tmp_iom_output(2) .lt. -max_iom_val ) tmp_iom_output(2) = -max_iom_val 
     2065!             if ( tmp_iom_output(3) .gt.  max_iom_val ) tmp_iom_output(3) =  max_iom_val 
     2066!             if ( tmp_iom_output(3) .lt. -max_iom_val ) tmp_iom_output(3) = -max_iom_val 
     2067!              
     2068!             ! Set NaN's to Zero          
     2069!             if ( tmp_iom_output(1) .ne.  tmp_iom_output(1) ) tmp_iom_output(1) =  max_iom_val*2 
     2070!             if ( tmp_iom_output(2) .ne.  tmp_iom_output(2) ) tmp_iom_output(1) =  max_iom_val*2 
     2071!             if ( tmp_iom_output(3) .ne.  tmp_iom_output(3) ) tmp_iom_output(1) =  max_iom_val*2 
     2072!              
     2073!             noos_iom_dummy(:,:,1) = tmp_iom_output(1) 
     2074!             noos_iom_dummy(:,:,2) = tmp_iom_output(2) 
     2075!             noos_iom_dummy(:,:,3) = tmp_iom_output(3) 
     2076!              
     2077!             !noos_iom_dummy(:,:,1) = (zsumclasses( 7)+zsumclasses( 8)) 
     2078!             !noos_iom_dummy(:,:,2) = zsumclasses( 7) 
     2079!             !noos_iom_dummy(:,:,3) = zsumclasses( 8) 
     2080!              
     2081!             noos_var_sect_name =  "noos_" // trim(noos_sect_name) // '_heat' 
     2082!             if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 
     2083!             CALL iom_put(noos_var_sect_name,  noos_iom_dummy )   
     2084!             noos_iom_dummy(:,:,:) = 0. 
     2085!             tmp_iom_output(:) = 0. 
     2086!              
     2087!             tmp_iom_output(1) = (zsumclasses( 9)+zsumclasses( 10)) 
     2088!             tmp_iom_output(2) = zsumclasses( 9) 
     2089!             tmp_iom_output(3) = zsumclasses( 10) 
     2090!              
     2091!             ! Convert to  MT/s 
     2092!             tmp_iom_output(1) = tmp_iom_output(1)*1.E-6 
     2093!             tmp_iom_output(2) = tmp_iom_output(2)*1.E-6 
     2094!             tmp_iom_output(3) = tmp_iom_output(3)*1.E-6 
     2095!              
     2096!              
     2097!             ! limit maximum and minimum values in iom_put 
     2098!             if ( tmp_iom_output(1) .gt.  max_iom_val ) tmp_iom_output(1) =  max_iom_val 
     2099!             if ( tmp_iom_output(1) .lt. -max_iom_val ) tmp_iom_output(1) = -max_iom_val 
     2100!             if ( tmp_iom_output(2) .gt.  max_iom_val ) tmp_iom_output(2) =  max_iom_val 
     2101!             if ( tmp_iom_output(2) .lt. -max_iom_val ) tmp_iom_output(2) = -max_iom_val 
     2102!             if ( tmp_iom_output(3) .gt.  max_iom_val ) tmp_iom_output(3) =  max_iom_val 
     2103!             if ( tmp_iom_output(3) .lt. -max_iom_val ) tmp_iom_output(3) = -max_iom_val 
     2104!              
     2105!             ! Set NaN's to Zero          
     2106!             if ( tmp_iom_output(1) .ne.  tmp_iom_output(1) ) tmp_iom_output(1) =  max_iom_val*2 
     2107!             if ( tmp_iom_output(2) .ne.  tmp_iom_output(2) ) tmp_iom_output(1) =  max_iom_val*2 
     2108!             if ( tmp_iom_output(3) .ne.  tmp_iom_output(3) ) tmp_iom_output(1) =  max_iom_val*2 
     2109!              
     2110!             noos_iom_dummy(:,:,1) = tmp_iom_output(1) 
     2111!             noos_iom_dummy(:,:,2) = tmp_iom_output(2) 
     2112!             noos_iom_dummy(:,:,3) = tmp_iom_output(3) 
     2113!              
     2114!             !noos_iom_dummy(:,:,1) = (zsumclasses( 9)+zsumclasses( 10)) 
     2115!             !noos_iom_dummy(:,:,2) = zsumclasses( 9) 
     2116!             !noos_iom_dummy(:,:,3) = zsumclasses( 10) 
     2117!              
     2118!             noos_var_sect_name = "noos_" // trim(noos_sect_name) // '_salt' 
     2119!             if ( lwp ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 
     2120!             CALL iom_put(noos_var_sect_name,  noos_iom_dummy ) 
     2121!             noos_iom_dummy(:,:,:) = 0.          
     2122!             tmp_iom_output(:) = 0. 
     2123!         ENDIF 
     2124!          
     2125!     ENDIF  
     2126      
     2127 
     2128 
     2129 
     2130 
     2131 
     2132 
     2133 
     2134      
     2135      
     2136     IF( lwp ) THEN 
     2137        IF  ( ln_dct_ascii ) THEN 
     2138             !WRITE(numdct_NOOS,'(9e12.4E2)')   zsumclasses( 1)+zsumclasses( 2) ,  zsumclasses( 1), zsumclasses( 2),   & 
     2139             WRITE(numdct_NOOS,'(3F18.3,6e16.8E2)')   zsumclasses( 1)+zsumclasses( 2) ,  zsumclasses( 1), zsumclasses( 2),   & 
     2140                                             zsumclasses( 7)+zsumclasses( 8) ,  zsumclasses( 7), zsumclasses( 8),   & 
     2141                                             zsumclasses( 9)+zsumclasses(10) ,  zsumclasses( 9), zsumclasses(10) 
     2142             CALL FLUSH(numdct_NOOS) 
     2143        ELSE 
     2144             WRITE(numdct_NOOS)   zsumclasses( 1)+zsumclasses( 2) ,  zsumclasses( 1), zsumclasses( 2),   & 
     2145                                  zsumclasses( 7)+zsumclasses( 8) ,  zsumclasses( 7), zsumclasses( 8),   & 
     2146                                  zsumclasses( 9)+zsumclasses(10) ,  zsumclasses( 9), zsumclasses(10) 
     2147             CALL FLUSH(numdct_NOOS)  
     2148         ENDIF 
     2149     ENDIF 
     2150          
     2151    IF ( ln_dct_iom_cont ) THEN 
     2152         
     2153         noos_iom_dummy(:,:,:) = 0. 
     2154         tmp_iom_output(:) = 0. 
     2155          
     2156         tmp_iom_output(1) = (zsumclasses( 1)+zsumclasses( 2)) 
     2157         tmp_iom_output(2) = zsumclasses( 1) 
     2158         tmp_iom_output(3) = zsumclasses( 2) 
     2159          
     2160         ! Convert to Sv 
     2161         tmp_iom_output(1) = tmp_iom_output(1)*1.E-6 
     2162         tmp_iom_output(2) = tmp_iom_output(2)*1.E-6 
     2163         tmp_iom_output(3) = tmp_iom_output(3)*1.E-6 
     2164          
     2165         ! limit maximum and minimum values in iom_put 
     2166         if ( tmp_iom_output(1) .gt.  max_iom_val ) tmp_iom_output(1) =  max_iom_val 
     2167         if ( tmp_iom_output(1) .lt. -max_iom_val ) tmp_iom_output(1) = -max_iom_val 
     2168         if ( tmp_iom_output(2) .gt.  max_iom_val ) tmp_iom_output(2) =  max_iom_val 
     2169         if ( tmp_iom_output(2) .lt. -max_iom_val ) tmp_iom_output(2) = -max_iom_val 
     2170         if ( tmp_iom_output(3) .gt.  max_iom_val ) tmp_iom_output(3) =  max_iom_val 
     2171         if ( tmp_iom_output(3) .lt. -max_iom_val ) tmp_iom_output(3) = -max_iom_val 
     2172          
     2173         ! Set NaN's to Zero          
     2174         if ( tmp_iom_output(1) .ne.  tmp_iom_output(1) ) tmp_iom_output(1) =  max_iom_val*2 
     2175         if ( tmp_iom_output(2) .ne.  tmp_iom_output(2) ) tmp_iom_output(1) =  max_iom_val*2 
     2176         if ( tmp_iom_output(3) .ne.  tmp_iom_output(3) ) tmp_iom_output(1) =  max_iom_val*2 
     2177          
     2178         noos_iom_dummy(:,:,1) = tmp_iom_output(1) 
     2179         noos_iom_dummy(:,:,2) = tmp_iom_output(2) 
     2180         noos_iom_dummy(:,:,3) = tmp_iom_output(3) 
     2181          
     2182         !noos_iom_dummy(:,:,1) = (zsumclasses( 1)+zsumclasses( 2)) 
     2183         !noos_iom_dummy(:,:,2) = zsumclasses( 1) 
     2184         !noos_iom_dummy(:,:,3) = zsumclasses( 2) 
     2185          
     2186          
     2187          
     2188         noos_var_sect_name = "noos_" // trim(noos_sect_name) // '_trans' 
     2189         if ( lwp .AND. verbose ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 
     2190         CALL iom_put( noos_var_sect_name,  noos_iom_dummy ) 
     2191         noos_iom_dummy(:,:,:) = 0. 
     2192         tmp_iom_output(:) = 0. 
     2193          
     2194         tmp_iom_output(1) = (zsumclasses( 7)+zsumclasses( 8)) 
     2195         tmp_iom_output(2) = zsumclasses( 7) 
     2196         tmp_iom_output(3) = zsumclasses( 8) 
     2197          
     2198         ! Convert to TJ/s 
     2199         tmp_iom_output(1) = tmp_iom_output(1)*1.E-12 
     2200         tmp_iom_output(2) = tmp_iom_output(2)*1.E-12 
     2201         tmp_iom_output(3) = tmp_iom_output(3)*1.E-12 
     2202          
     2203         ! limit maximum and minimum values in iom_put 
     2204         if ( tmp_iom_output(1) .gt.  max_iom_val ) tmp_iom_output(1) =  max_iom_val 
     2205         if ( tmp_iom_output(1) .lt. -max_iom_val ) tmp_iom_output(1) = -max_iom_val 
     2206         if ( tmp_iom_output(2) .gt.  max_iom_val ) tmp_iom_output(2) =  max_iom_val 
     2207         if ( tmp_iom_output(2) .lt. -max_iom_val ) tmp_iom_output(2) = -max_iom_val 
     2208         if ( tmp_iom_output(3) .gt.  max_iom_val ) tmp_iom_output(3) =  max_iom_val 
     2209         if ( tmp_iom_output(3) .lt. -max_iom_val ) tmp_iom_output(3) = -max_iom_val 
     2210          
     2211         ! Set NaN's to Zero          
     2212         if ( tmp_iom_output(1) .ne.  tmp_iom_output(1) ) tmp_iom_output(1) =  max_iom_val*2 
     2213         if ( tmp_iom_output(2) .ne.  tmp_iom_output(2) ) tmp_iom_output(1) =  max_iom_val*2 
     2214         if ( tmp_iom_output(3) .ne.  tmp_iom_output(3) ) tmp_iom_output(1) =  max_iom_val*2 
     2215          
     2216         noos_iom_dummy(:,:,1) = tmp_iom_output(1) 
     2217         noos_iom_dummy(:,:,2) = tmp_iom_output(2) 
     2218         noos_iom_dummy(:,:,3) = tmp_iom_output(3) 
     2219          
     2220         !noos_iom_dummy(:,:,1) = (zsumclasses( 7)+zsumclasses( 8)) 
     2221         !noos_iom_dummy(:,:,2) = zsumclasses( 7) 
     2222         !noos_iom_dummy(:,:,3) = zsumclasses( 8) 
     2223          
     2224         noos_var_sect_name =  "noos_" // trim(noos_sect_name) // '_heat' 
     2225         if ( lwp .AND. verbose ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 
     2226         CALL iom_put(noos_var_sect_name,  noos_iom_dummy )   
     2227         noos_iom_dummy(:,:,:) = 0. 
     2228         tmp_iom_output(:) = 0. 
     2229          
     2230         tmp_iom_output(1) = (zsumclasses( 9)+zsumclasses( 10)) 
     2231         tmp_iom_output(2) = zsumclasses( 9) 
     2232         tmp_iom_output(3) = zsumclasses( 10) 
     2233          
     2234         ! Convert to  MT/s 
     2235         tmp_iom_output(1) = tmp_iom_output(1)*1.E-6 
     2236         tmp_iom_output(2) = tmp_iom_output(2)*1.E-6 
     2237         tmp_iom_output(3) = tmp_iom_output(3)*1.E-6 
     2238          
     2239          
     2240         ! limit maximum and minimum values in iom_put 
     2241         if ( tmp_iom_output(1) .gt.  max_iom_val ) tmp_iom_output(1) =  max_iom_val 
     2242         if ( tmp_iom_output(1) .lt. -max_iom_val ) tmp_iom_output(1) = -max_iom_val 
     2243         if ( tmp_iom_output(2) .gt.  max_iom_val ) tmp_iom_output(2) =  max_iom_val 
     2244         if ( tmp_iom_output(2) .lt. -max_iom_val ) tmp_iom_output(2) = -max_iom_val 
     2245         if ( tmp_iom_output(3) .gt.  max_iom_val ) tmp_iom_output(3) =  max_iom_val 
     2246         if ( tmp_iom_output(3) .lt. -max_iom_val ) tmp_iom_output(3) = -max_iom_val 
     2247          
     2248         ! Set NaN's to Zero          
     2249         if ( tmp_iom_output(1) .ne.  tmp_iom_output(1) ) tmp_iom_output(1) =  max_iom_val*2 
     2250         if ( tmp_iom_output(2) .ne.  tmp_iom_output(2) ) tmp_iom_output(1) =  max_iom_val*2 
     2251         if ( tmp_iom_output(3) .ne.  tmp_iom_output(3) ) tmp_iom_output(1) =  max_iom_val*2 
     2252          
     2253         noos_iom_dummy(:,:,1) = tmp_iom_output(1) 
     2254         noos_iom_dummy(:,:,2) = tmp_iom_output(2) 
     2255         noos_iom_dummy(:,:,3) = tmp_iom_output(3) 
     2256          
     2257         !noos_iom_dummy(:,:,1) = (zsumclasses( 9)+zsumclasses( 10)) 
     2258         !noos_iom_dummy(:,:,2) = zsumclasses( 9) 
     2259         !noos_iom_dummy(:,:,3) = zsumclasses( 10) 
     2260          
     2261         noos_var_sect_name = "noos_" // trim(noos_sect_name) // '_salt' 
     2262         if ( lwp .AND. verbose ) WRITE(numout,*) 'dia_dct_wri_NOOS iom_put: ', kt,ksec, noos_var_sect_name 
     2263         CALL iom_put(noos_var_sect_name,  noos_iom_dummy ) 
     2264         noos_iom_dummy(:,:,:) = 0.          
     2265         tmp_iom_output(:) = 0. 
     2266 
     2267 
     2268        DEALLOCATE(noos_iom_dummy) 
     2269     ENDIF 
     2270      
    15992271 
    16002272     DO jclass=1,MAX(1,sec%nb_class-1) 
     
    16412313                   
    16422314        !write volume transport per class 
    1643         IF ( zslope .gt. 0._wp .and. zslope .ne. 10000._wp ) THEN 
    1644            WRITE(numdct_NOOS,'(9e12.4E2)') -(sec%transport( 1,jclass)+sec%transport( 2,jclass)),-sec%transport( 2,jclass),-sec%transport( 1,jclass), & 
    1645                                            -(sec%transport( 7,jclass)+sec%transport( 8,jclass)),-sec%transport( 8,jclass),-sec%transport( 7,jclass), & 
    1646                                            -(sec%transport( 9,jclass)+sec%transport(10,jclass)),-sec%transport(10,jclass),-sec%transport( 9,jclass) 
    1647         ELSE 
    1648            WRITE(numdct_NOOS,'(9e12.4E2)')   sec%transport( 1,jclass)+sec%transport( 2,jclass) , sec%transport( 1,jclass), sec%transport( 2,jclass), & 
    1649                                              sec%transport( 7,jclass)+sec%transport( 8,jclass) , sec%transport( 7,jclass), sec%transport( 8,jclass), & 
    1650                                              sec%transport( 9,jclass)+sec%transport(10,jclass) , sec%transport( 9,jclass), sec%transport(10,jclass) 
     2315        IF( lwp ) THEN 
     2316             
     2317            IF  ( ln_dct_ascii ) THEN 
     2318                CALL FLUSH(numdct_NOOS) 
     2319 
     2320                !WRITE(numdct_NOOS,'(9e12.4E2)')   sec%transport( 1,jclass)+sec%transport( 2,jclass) , sec%transport( 1,jclass), sec%transport( 2,jclass), & 
     2321                !                                  sec%transport( 7,jclass)+sec%transport( 8,jclass) , sec%transport( 7,jclass), sec%transport( 8,jclass), & 
     2322                !                                  sec%transport( 9,jclass)+sec%transport(10,jclass) , sec%transport( 9,jclass), sec%transport(10,jclass) 
     2323                WRITE(numdct_NOOS,'(3F18.3,6e16.8E2)')   sec%transport( 1,jclass)+sec%transport( 2,jclass) , sec%transport( 1,jclass), sec%transport( 2,jclass), & 
     2324                                                         sec%transport( 7,jclass)+sec%transport( 8,jclass) , sec%transport( 7,jclass), sec%transport( 8,jclass), & 
     2325                                                         sec%transport( 9,jclass)+sec%transport(10,jclass) , sec%transport( 9,jclass), sec%transport(10,jclass) 
     2326            ELSE 
     2327 
     2328                CALL FLUSH(numdct_NOOS) 
     2329                WRITE(numdct_NOOS)   sec%transport( 1,jclass)+sec%transport( 2,jclass) , sec%transport( 1,jclass), sec%transport( 2,jclass), & 
     2330                                     sec%transport( 7,jclass)+sec%transport( 8,jclass) , sec%transport( 7,jclass), sec%transport( 8,jclass), & 
     2331                                     sec%transport( 9,jclass)+sec%transport(10,jclass) , sec%transport( 9,jclass), sec%transport(10,jclass) 
     2332            ENDIF 
    16512333        ENDIF 
    16522334 
    16532335     ENDDO 
     2336      
     2337     !IF  ( ln_dct_ascii ) THEN 
     2338        if ( lwp ) CALL FLUSH(numdct_NOOS) 
     2339     !ENDIF 
    16542340 
    16552341     CALL wrk_dealloc(nb_type_class , zsumclasses )   
     
    16712357     !!-------------------------------------------------------------  
    16722358     !!arguments 
    1673      INTEGER, INTENT(IN)          :: hr          ! hour 
     2359     INTEGER, INTENT(IN)          :: hr          ! hour => effectively kt/12 
    16742360     TYPE(SECTION), INTENT(INOUT) :: sec         ! section to write    
    16752361     INTEGER ,INTENT(IN)          :: ksec        ! section number 
     
    16822368     ! 
    16832369     REAL(wp), POINTER, DIMENSION(:):: zsumclasses ! 1D workspace  
     2370     CHARACTER(len=3)      :: noos_sect_name             ! Classname  
     2371     CHARACTER(len=25)      :: noos_var_sect_name 
     2372     REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   noos_iom_dummy 
     2373     INTEGER               :: IERR 
     2374     LOGICAL       ::   verbose      
     2375     verbose = .false. 
     2376      
    16842377     !!-------------------------------------------------------------  
    16852378 
     2379     IF( lwp .AND. verbose ) THEN 
     2380        WRITE(numout,*) " " 
     2381        WRITE(numout,*) "dia_dct_wri_NOOS_h: write transports through section Transect:",ksec-1," at timestep: ", hr 
     2382        WRITE(numout,*) "~~~~~~~~~~~~~~~~~~~~~" 
     2383     ENDIF    
     2384      
    16862385     CALL wrk_alloc(nb_type_class , zsumclasses )  
     2386      
     2387      
     2388     write (noos_sect_name, "(I03)")  ksec 
     2389      
     2390     ALLOCATE( noos_iom_dummy(jpi,jpj,3),  STAT= ierr ) 
     2391        IF( ierr /= 0 )   CALL ctl_stop( 'dia_dct_wri_NOOS_h: failed to allocate noos_iom_dummy array' ) 
     2392 
     2393 
     2394 
     2395      
    16872396 
    16882397     zsumclasses(:)=0._wp 
    16892398     zslope = sec%slopeSection        
    16902399 
     2400     ! Sum up all classes, to give the total per type (pos vol trans, neg vol trans etc...) 
    16912401     DO jclass=1,MAX(1,sec%nb_class-1) 
    16922402        zsumclasses(1:nb_type_class)=zsumclasses(1:nb_type_class)+sec%transport_h(1:nb_type_class,jclass) 
    16932403     ENDDO 
    1694   
     2404         
     2405      
     2406     ! JT I think changing the sign of output according to the zslope is redundant 
     2407      
    16952408     !write volume transport per class 
    1696      IF ( zslope .gt. 0._wp .and. zslope .ne. 10000._wp ) THEN 
    1697         z_hr_output(ksec,hr,1)=-(zsumclasses(1)+zsumclasses(2)) 
    1698      ELSE 
    1699         z_hr_output(ksec,hr,1)= (zsumclasses(1)+zsumclasses(2)) 
    1700      ENDIF 
    1701  
     2409     ! Sum positive and vol trans for all classes in first cell of array 
     2410 
     2411     z_hr_output(ksec,1,1)= (zsumclasses(1)+zsumclasses(2)) 
     2412     z_hr_output(ksec,2,1)= zsumclasses(1) 
     2413     z_hr_output(ksec,3,1)= zsumclasses(2) 
     2414 
     2415     ! Sum positive and vol trans for each classes in following cell of array 
    17022416     DO jclass=1,MAX(1,sec%nb_class-1) 
    1703         IF ( zslope .gt. 0._wp .and. zslope .ne. 10000._wp ) THEN 
    1704            z_hr_output(ksec,hr,jclass+1)=-(sec%transport_h(1,jclass)+sec%transport_h(2,jclass)) 
     2417        z_hr_output(ksec,1,jclass+1)= (sec%transport_h(1,jclass)+sec%transport_h(2,jclass)) 
     2418        z_hr_output(ksec,2,jclass+1)= sec%transport_h(1,jclass) 
     2419        z_hr_output(ksec,3,jclass+1)= sec%transport_h(2,jclass) 
     2420     ENDDO 
     2421 
     2422     
     2423    IF( lwp )  THEN 
     2424        ! JT IF ( hr .eq. 48._wp ) THEN 
     2425        ! JT    WRITE(numdct_NOOS_h,'(I4,a1,I2,a1,I2,a12,i3,a17,i3)') nyear,'.',nmonth,'.',nday,'   Transect:',ksec-1,'   No. of layers:',sec%nb_class-1 
     2426        ! JT    DO jhr=25,48 
     2427        ! JT       WRITE(numdct_NOOS_h,'(11F12.1)')  z_hr_output(ksec,jhr,1), (z_hr_output(ksec,jhr,jclass+1), jclass=1,MAX(1,10) ) 
     2428        ! JT    ENDDO 
     2429        ! JT ENDIF 
     2430 
     2431 
     2432 
     2433        IF ( ln_dct_ascii ) THEN 
     2434            WRITE(numdct_NOOS_h,'(I4,a1,I2,a1,I2,a1,I2,a1,I2,a12,i3,a17,i3)') nyear,'.',nmonth,'.',nday,'.',MOD(hr,24),'.',0,'   Transect:',ksec-1,'   No. of layers:',sec%nb_class-1 
     2435            WRITE(numdct_NOOS_h,'(11F18.3)')  z_hr_output(ksec,1,1), (z_hr_output(ksec,1,jclass+1), jclass=1,MAX(1,10) ) 
     2436            WRITE(numdct_NOOS_h,'(11F18.3)')  z_hr_output(ksec,2,1), (z_hr_output(ksec,2,jclass+1), jclass=1,MAX(1,10) ) 
     2437            WRITE(numdct_NOOS_h,'(11F18.3)')  z_hr_output(ksec,3,1), (z_hr_output(ksec,3,jclass+1), jclass=1,MAX(1,10) ) 
     2438            CALL FLUSH(numdct_NOOS_h) 
    17052439        ELSE 
    1706            z_hr_output(ksec,hr,jclass+1)= (sec%transport_h(1,jclass)+sec%transport_h(2,jclass)) 
     2440            WRITE(numdct_NOOS_h) nyear,nmonth,nday,MOD(hr,24),ksec-1,sec%nb_class-1 
     2441            WRITE(numdct_NOOS_h)  z_hr_output(ksec,1,1), (z_hr_output(ksec,1,jclass+1), jclass=1,MAX(1,10) ) 
     2442            WRITE(numdct_NOOS_h)  z_hr_output(ksec,2,1), (z_hr_output(ksec,2,jclass+1), jclass=1,MAX(1,10) ) 
     2443            WRITE(numdct_NOOS_h)  z_hr_output(ksec,3,1), (z_hr_output(ksec,3,jclass+1), jclass=1,MAX(1,10) ) 
     2444            CALL FLUSH(numdct_NOOS_h) 
    17072445        ENDIF 
    1708      ENDDO 
    1709  
    1710      IF ( hr .eq. 48._wp ) THEN 
    1711         WRITE(numdct_NOOS_h,'(I4,a1,I2,a1,I2,a12,i3,a17,i3)') nyear,'.',nmonth,'.',nday,'   Transect:',ksec-1,'   No. of layers:',sec%nb_class-1 
    1712         DO jhr=25,48 
    1713            WRITE(numdct_NOOS_h,'(11F12.1)')  z_hr_output(ksec,jhr,1), (z_hr_output(ksec,jhr,jclass+1), jclass=1,MAX(1,10) ) 
    1714         ENDDO 
    1715      ENDIF 
     2446 
     2447 
     2448     ENDIF  
     2449 
    17162450 
    17172451     CALL wrk_dealloc(nb_type_class , zsumclasses ) 
     2452      
     2453     DEALLOCATE(noos_iom_dummy) 
     2454 
     2455 
    17182456 
    17192457  END SUBROUTINE dia_dct_wri_NOOS_h 
     
    17302468     !!  
    17312469     !!        2. Write heat transports in "heat_transport" 
    1732      !!           Unit: Peta W : area * Velocity * T * rhop * Cp * 1.e-15 
     2470     !!           Unit: Peta W : area * Velocity * T * rhau * Cp / 1.e15 
    17332471     !!  
    17342472     !!        3. Write salt transports in "salt_transport" 
    1735      !!           Unit: 10^9 Kg/m^2/s : area * Velocity * S * rhop * 1.e-9  
     2473     !!           Unit: 10^9 g m^3 / s : area * Velocity * S / 1.e6 
    17362474     !! 
    17372475     !!-------------------------------------------------------------  
     
    18102548           WRITE(numdct_heat,119) ndastp,kt,ksec,sec%name,zslope,  & 
    18112549                              jclass,classe,zbnd1,zbnd2,& 
    1812                               sec%transport(7,jclass)*1.e-15,sec%transport(8,jclass)*1.e-15, & 
    1813                               ( sec%transport(7,jclass)+sec%transport(8,jclass) )*1.e-15 
     2550                              sec%transport(7,jclass)*1000._wp*rcp/1.e15,sec%transport(8,jclass)*1000._wp*rcp/1.e15, & 
     2551                              ( sec%transport(7,jclass)+sec%transport(8,jclass) )*1000._wp*rcp/1.e15 
    18142552           !write salt transport per class 
    18152553           WRITE(numdct_salt,119) ndastp,kt,ksec,sec%name,zslope,  & 
    18162554                              jclass,classe,zbnd1,zbnd2,& 
    1817                               sec%transport(9,jclass)*1.e-9,sec%transport(10,jclass)*1.e-9,& 
    1818                               (sec%transport(9,jclass)+sec%transport(10,jclass))*1.e-9 
     2555                              sec%transport(9,jclass)*1000._wp/1.e9,sec%transport(10,jclass)*1000._wp/1.e9,& 
     2556                              (sec%transport(9,jclass)+sec%transport(10,jclass))*1000._wp/1.e9 
    18192557        ENDIF 
    18202558 
     
    18352573        WRITE(numdct_heat,119) ndastp,kt,ksec,sec%name,zslope, & 
    18362574                           jclass,"total",zbnd1,zbnd2,& 
    1837                            zsumclasses(7)*1.e-15,zsumclasses(8)*1.e-15,& 
    1838                            (zsumclasses(7)+zsumclasses(8) )*1.e-15 
     2575                           zsumclasses(7)* 1000._wp*rcp/1.e15,zsumclasses(8)* 1000._wp*rcp/1.e15,& 
     2576                           (zsumclasses(7)+zsumclasses(8) )* 1000._wp*rcp/1.e15 
    18392577        !write total salt transport 
    18402578        WRITE(numdct_salt,119) ndastp,kt,ksec,sec%name,zslope, & 
    18412579                           jclass,"total",zbnd1,zbnd2,& 
    1842                            zsumclasses(9)*1.e-9,zsumclasses(10)*1.e-9,& 
    1843                            (zsumclasses(9)+zsumclasses(10))*1.e-9 
     2580                           zsumclasses(9)*1000._wp/1.e9,zsumclasses(10)*1000._wp/1.e9,& 
     2581                           (zsumclasses(9)+zsumclasses(10))*1000._wp/1.e9 
    18442582     ENDIF 
    18452583 
     
    18782616  !!    |    I          |    I+1           |    Z=temperature/salinity/density at U-poinT 
    18792617  !!    |               |                  | 
    1880   !!  ----------------------------------------  1. Veritcal interpolation: compute zbis 
     2618  !!  ----------------------------------------  1. Veritcale interpolation: compute zbis 
    18812619  !!    |               |                  |       interpolation between ptab(I,J,K) and ptab(I,J,K+1) 
    18822620  !!    |               |                  |       zbis =  
  • branches/UKMO/AMM15_v3_6_STABLE_package_reanalysis4/NEMOGCM/NEMO/OPA_SRC/DIA/diatmb.F90

    r10390 r11639  
    1111   USE iom             ! I/0 library 
    1212   USE wrk_nemo        ! working arrays 
     13   USE diaregmean 
    1314#if defined key_fabm 
    1415   USE trc, ONLY: trn 
  • branches/UKMO/AMM15_v3_6_STABLE_package_reanalysis4/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r11277 r11639  
    4848   USE dia25h          ! 25h Mean output 
    4949   USE diaopfoam       ! Diaopfoam output 
     50   USE diaregmean      ! regionalmean 
     51   USE diapea          ! pea 
    5052   USE iom 
    5153   USE ioipsl 
     
    406408      IF (ln_diaopfoam) THEN 
    407409         CALL dia_diaopfoam 
     410      ENDIF 
     411      if ( ln_pea ) THEN 
     412         CALL dia_pea( kt ) 
     413      ENDIF 
     414      IF (ln_diaregmean) THEN 
     415         CALL dia_regmean( kt ) 
    408416      ENDIF 
    409417      ! 
  • branches/UKMO/AMM15_v3_6_STABLE_package_reanalysis4/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r8058 r11639  
    5656   PUBLIC iom_getatt, iom_use, iom_context_finalize 
    5757 
     58   INTEGER , PUBLIC ::   n_regions_output 
     59 
    5860   PRIVATE iom_rp0d, iom_rp1d, iom_rp2d, iom_rp3d 
    5961   PRIVATE iom_g0d, iom_g1d, iom_g2d, iom_g3d, iom_get_123d 
     
    106108      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_bnds 
    107109      !!---------------------------------------------------------------------- 
     110       
     111       
     112       
     113       
     114       
     115      REAL(wp),  ALLOCATABLE,   DIMENSION(:,:) ::   tmpregion !: temporary region_mask 
     116      INTEGER, DIMENSION(3) ::   zdimsz   ! number of elements in each of the 3 dimensions (i.e., lon, lat, no of masks, 297,  375,  4) for an array 
     117      INTEGER               ::   zndims   ! number of dimensions in an array (i.e. 3, ) 
     118      INTEGER :: inum, nmasks,ierr,maskno,idmaskvar,tmpint 
     119      REAL(wp), ALLOCATABLE,   DIMENSION(:,:,:)  ::   tmp_region_mask_real   ! tempory region_mask of reals 
     120       
     121      LOGICAL ::   ln_diaregmean  ! region mean calculation 
     122    
     123     
     124      INTEGER ::   ios                  ! Local integer output status for namelist read 
     125      LOGICAL :: ln_diaregmean_ascii  ! region mean calculation ascii output 
     126      LOGICAL :: ln_diaregmean_bin  ! region mean calculation binary output 
     127      LOGICAL :: ln_diaregmean_nc  ! region mean calculation netcdf output 
     128      LOGICAL :: ln_diaregmean_karamld  ! region mean calculation including kara mld terms 
     129      LOGICAL :: ln_diaregmean_pea  ! region mean calculation including pea terms 
     130      LOGICAL :: ln_diaregmean_diaar5  ! region mean calculation including AR5 SLR terms 
     131      LOGICAL :: ln_diaregmean_diasbc  ! region mean calculation including Surface BC 
     132     
     133#if defined key_fabm 
     134      LOGICAL :: ln_diaregmean_bgc  ! region mean calculation including BGC 
     135#endif 
     136      ! Read the number region mask to work out how many regions are needed. 
     137       
     138#if defined key_fabm 
     139      NAMELIST/nam_diaregmean/ ln_diaregmean,ln_diaregmean_ascii,ln_diaregmean_bin,ln_diaregmean_nc,& 
     140        & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc,ln_diaregmean_bgc 
     141#else 
     142      NAMELIST/nam_diaregmean/ ln_diaregmean,ln_diaregmean_ascii,ln_diaregmean_bin,ln_diaregmean_nc,& 
     143        & ln_diaregmean_karamld, ln_diaregmean_pea,ln_diaregmean_diaar5,ln_diaregmean_diasbc 
     144#endif 
     145       
     146      ! read in Namelist.  
     147      !!---------------------------------------------------------------------- 
     148      ! 
     149      REWIND ( numnam_ref )              ! Read Namelist nam_diatmb in referdiatmbence namelist : TMB diagnostics 
     150      READ   ( numnam_ref, nam_diaregmean, IOSTAT=ios, ERR= 901 ) 
     151901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diaregmean in reference namelist', lwp ) 
     152 
     153      REWIND( numnam_cfg )              ! Namelist nam_diatmb in configuration namelist  TMB diagnostics 
     154      READ  ( numnam_cfg, nam_diaregmean, IOSTAT = ios, ERR = 902 ) 
     155902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diaregmean in configuration namelist', lwp ) 
     156      IF(lwm) WRITE ( numond, nam_diaregmean ) 
     157 
     158      IF (ln_diaregmean) THEN 
     159       
     160        ! Open region mask for region means, and retrieve the size of the mask (number of levels)           
     161          CALL iom_open ( 'region_mask.nc', inum ) 
     162          idmaskvar = iom_varid( inum, 'mask', kdimsz=zdimsz, kndims=zndims, ldstop = .FALSE.)           
     163          nmasks = zdimsz(3) 
     164           
     165          ! read in the region mask (which contains floating point numbers) into a temporary array of reals. 
     166          ALLOCATE( tmp_region_mask_real(jpi,jpj,nmasks),  STAT= ierr ) 
     167          IF( ierr /= 0 )   CALL ctl_stop( 'dia_regmean_init: failed to allocate tmp_region_mask_real array' ) 
     168           
     169          ! Use jpdom_unknown to read in a n layer mask. 
     170          tmp_region_mask_real(:,:,:) = 0 
     171          CALL iom_get( inum, jpdom_unknown, 'mask', tmp_region_mask_real(1:nlci,1:nlcj,1:nmasks),   & 
     172              &          kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,nmasks /) ) 
     173           
     174          CALL iom_close( inum ) 
     175          !Convert the region mask of reals into one of integers.  
     176           
     177           
     178          n_regions_output = 0 
     179          DO maskno = 1,nmasks 
     180              tmpint = maxval(int(tmp_region_mask_real(:,:,maskno))) 
     181              CALL mpp_max( tmpint ) 
     182              n_regions_output = n_regions_output + (tmpint + 1) 
     183          END DO 
     184       
     185           
     186         
     187      ELSE 
     188        n_regions_output = 1 
     189      ENDIF 
     190       
     191       
     192       
    108193#if ! defined key_xios2 
    109194      ALLOCATE( z_bnds(jpk,2) ) 
     
    227312      CALL iom_set_axis_attr( "iax_20C", (/ REAL(20,wp) /) ) 
    228313      CALL iom_set_axis_attr( "iax_28C", (/ REAL(28,wp) /) ) 
     314       
     315       
     316       
     317      CALL iom_set_axis_attr( "region", (/ (REAL(ji,wp), ji=1,n_regions_output) /) ) 
     318 
     319      CALL iom_set_axis_attr( "noos", (/ (REAL(ji,wp), ji=1,3) /) ) 
     320 
    229321       
    230322      ! automatic definitions of some of the xml attributs 
  • branches/UKMO/AMM15_v3_6_STABLE_package_reanalysis4/NEMOGCM/NEMO/OPA_SRC/OBS/obs_level_search.h90

    r8058 r11639  
    2121      !!        !  2006-10  (A. Weaver) Cleanup 
    2222      !!        !  2008-10  (K. Mogensen) Remove assumptions on grid. 
     23      !!        !  2019-07  (R. Renshaw) Don't exceed model bottom. 
    2324      !!---------------------------------------------------------------------- 
    2425 
     
    4647            IF ( pgrddep(jk) >= pobsdep(ji) ) EXIT depk 
    4748         END DO depk 
    48          kobsk(ji) = jk 
     49         kobsk(ji) = MIN( jk, kgrd ) 
    4950      END DO 
    5051 
  • branches/UKMO/AMM15_v3_6_STABLE_package_reanalysis4/NEMOGCM/NEMO/OPA_SRC/OBS/obsinter_z1d.h90

    r8058 r11639  
    2626      !!      ! 06-10 (A. Weaver) Cleanup 
    2727      !!      ! 07-01 (K. Mogensen) Use profile rather than single level 
     28      !!      ! 19-07 (R. Renshaw) Avoid division by zero 
    2829      !!--------------------------------------------------------------------- 
    2930 
     
    6263         z1dm = ( pdep(kkco(jdep)) - pobsdep(jdep)      ) 
    6364         z1dp = ( pobsdep(jdep)    - pdep(kkco(jdep)-1) ) 
     65!        Where ob is below model bottom, use model bottom rather than extrapolate 
     66         IF ( pdep(kkco(jdep)) <= pobsdep(jdep) ) z1dm = 0.0_wp 
     67!        Where lower level is missing, use higher level 
    6468         IF ( pobsmask(kkco(jdep)) == 0.0_wp ) z1dp = 0.0_wp 
    6569 
    6670         zsum = z1dm + z1dp 
     71         ! if pobsmask==0 and model level depth==observed depth, we get zsum=0 
     72         IF ( zsum > 0.0_wp ) THEN 
    6773          
    6874         IF ( k1dint == 0 ) THEN 
     
    8894 
    8995         ENDIF 
     96 
     97         ELSE  ! take value directly from the higher model level 
     98            pobs(jdep)  = pobsk(kkco(jdep)-1) 
     99         ENDIF 
     100 
    90101      END DO 
    91102 
  • branches/UKMO/AMM15_v3_6_STABLE_package_reanalysis4/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r11277 r11639  
    8888   USE stopts 
    8989   USE diatmb          ! Top,middle,bottom output 
     90   USE diaregmean      ! regional means output 
     91   USE diapea          ! potential energy anomaly output 
    9092   USE dia25h          ! 25h mean output 
    9193   USE diaopfoam       ! FOAM operational output 
     
    506508      IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler 
    507509                            CALL dia_tmb_init  ! TMB outputs 
     510                            CALL dia_regmean_init  ! TMB outputs 
     511                            CALL dia_pea_init  ! TMB outputs 
    508512                            CALL dia_25h_init  ! 25h mean  outputs 
    509513                            CALL dia_diaopfoam_init  ! FOAM operational output 
     
    643647      IF( numdct_heat     /= -1 )   CLOSE( numdct_heat     )   ! heat transports 
    644648      IF( numdct_salt     /= -1 )   CLOSE( numdct_salt     )   ! salt transports 
     649      IF( numdct_NOOS     /= -1 )   CLOSE( numdct_NOOS     )   ! NOOS transports 
    645650 
    646651      ! 
  • branches/UKMO/AMM15_v3_6_STABLE_package_reanalysis4/NEMOGCM/NEMO/TOP_SRC/trcbdy.F90

    r10270 r11639  
    109109            ii = idx%nbi(ib,igrd) 
    110110            ij = idx%nbj(ib,igrd) 
    111             zwgt = idx%nbw(ib,igrd) 
     111            zwgt = idx%nbw(ib,igrd) * rdttrc(ik) / 86400.d0  ! damping with a timescale of day 
    112112            tra(ii,ij,ik,jn) = ( tra(ii,ij,ik,jn) + zwgt * ( ( dta%trc(ib,ik) * dta%rn_fac)  &  
    113113                        &  - tra(ii,ij,ik,jn) ) ) * tmask(ii,ij,ik) 
    114114         END DO 
    115115      END DO  
     116! tra is overwritten at the boundary so damping doesn't work here - need neumann in addition 
     117! to duplicate the internal value at the boundary 
     118      CALL bdy_trc_nmn( jn,  idx, dta, kt ) 
     119 
     120 
    116121      ! 
    117122      IF( kt .eq. nit000 ) CLOSE( unit = 102 ) 
Note: See TracChangeset for help on using the changeset viewer.