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 6772 for branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC – NEMO

Ignore:
Timestamp:
2016-07-01T18:02:45+02:00 (8 years ago)
Author:
cbricaud
Message:

clean in coarsening branch

Location:
branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC
Files:
1 deleted
11 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/MY_TRC/trcini_my_trc.F90

    r5602 r6772  
    5858 
    5959       
    60       IF( .NOT. ln_rsttr ) trb(:,:,:,jp_myt0:jp_myt1) = 0. 
    61       IF( .NOT. ln_rsttr ) trn(:,:,:,jp_myt0:jp_myt1) = 0. 
     60      IF( .NOT. ln_rsttr ) trb(:,:,:,jp_myt0:jp_myt1) = 0._wp 
     61      IF( .NOT. ln_rsttr ) trn(:,:,:,jp_myt0:jp_myt1) = 0._wp 
    6262      ! 
    6363   END SUBROUTINE trc_ini_my_trc 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/MY_TRC/trcwri_my_trc.F90

    r5602 r6772  
    1616   USE crs, ONLY : ln_crs,ln_crs_top,ahtt_crs,ahtu_crs,ahtv_crs,ahtw_crs,jpi_crs,jpj_crs 
    1717   USE iom, ONLY : iom_swap, iom_put 
     18   USE ieee_arithmetic 
    1819 
    1920   IMPLICIT NONE 
     
    3637      IF( ln_crs_top ) CALL iom_swap( "nemo_crs" ) 
    3738 
    38       CALL iom_put("ahtt_crs",ahtt_crs) 
    39       CALL iom_put("ahtu_crs",ahtu_crs) 
    40       CALL iom_put("ahtv_crs",ahtv_crs) 
    41       CALL iom_put("ahtw_crs",ahtw_crs) 
    42  
    43   
    4439      ! write the tracer concentrations in the file 
    4540      ! --------------------------------------- 
     41      WHERE(ieee_is_nan(trn))trn=1.e30 
    4642      DO jn = jp_myt0, jp_myt1 
    4743         cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer 
    48          IF( lk_vvl ) THEN 
    49             CALL iom_put( TRIM(cltra), trn(:,:,:,jn) * fse3t_n(:,:,:) ) 
    50          ELSE 
    51             CALL iom_put( TRIM(cltra), trn(:,:,:,jn) ) 
     44         CALL iom_put( TRIM(cltra), trn(:,:,:,jn) ) 
    5245         ENDIF 
    5346      END DO 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trcadv_crs.F90

    r5105 r6772  
    2929   USE crs , ONLY : e2e3u_msk , e1e3v_msk , e1e2w_msk,jpi_crs,jpj_crs 
    3030   USE timing 
     31   USE iom, ONLY: iom_put,iom_swap 
    3132 
    3233   IMPLICIT NONE 
     
    9798#endif 
    9899 
    99   !    IF(lwp) WRITE(numout,*) 'TEST', e1e2t 
    100       !                                                   ! effective transport 
    101 !         IF(lwp) WRITE(numout,*) 'un', maxval(un(:,:,:)) 
    102 !         IF(lwp) WRITE(numout,*) 'un', minval(un(:,:,:)) 
    103 !         IF(lwp) WRITE(numout,*) 'vn', maxval(vn(:,:,:)) 
    104 !         IF(lwp) WRITE(numout,*) 'vn', minval(vn(:,:,:)) 
    105 !         IF(lwp) WRITE(numout,*) 'wn', maxval(wn(:,:,:)) 
    106 !         IF(lwp) WRITE(numout,*) 'wn', minval(wn(:,:,:)) 
    107100      DO jk = 1, jpkm1 
    108101         !                                                ! eulerian transport only 
     
    113106      END DO 
    114107 
    115          IF(lwp)WRITE(numout,*)"jpi_crs jpj_crs jpk ",jpi_crs,jpj_crs,jpk 
    116          DO jk=1,jpk 
    117            DO jj = 1, jpj_crs 
    118                DO ji = 1, jpi_crs 
    119                   IF( zwn(ji,jj,jk) .NE. zwn(ji,jj,jk) )WRITE(narea+200,*)"trcadv_zwn",zwn(ji,jj,jk) ; call flush(narea+200) 
    120                END DO 
    121             END DO 
    122          END DO 
    123  
    124  
    125108      zwn(:,:,jpk) = 0.e0                                 ! no transport trough the bottom 
    126109 
     
    129112      ! 
    130113      SELECT CASE ( nadv )                            !==  compute advection trend and add it to general trend  ==! 
    131 !cbr      CASE ( 1 )   ;    CALL tra_adv_cen2  ( kt, nittrc000, 'TRC',       zun, zvn, zwn, trb, trn, tra, jptra )   !  2nd order centered 
    132114      CASE ( 2 )   ;    CALL tra_adv_tvd_crs   ( kt, nittrc000, 'TRC', r2dt, zun, zvn, zwn, trb, trn, tra, jptra )   !  TVD  
    133 !cbr      CASE ( 3 )   ;    CALL tra_adv_muscl ( kt, nittrc000, 'TRC', r2dt, zun, zvn, zwn, trb,      tra, jptra )   !  MUSCL  
    134 !cbr      CASE ( 4 )   ;    CALL tra_adv_muscl2( kt, nittrc000, 'TRC', r2dt, zun, zvn, zwn, trb, trn, tra, jptra )   !  MUSCL2  
    135 !cbr      CASE ( 5 )   ;    CALL tra_adv_ubs   ( kt, nittrc000, 'TRC', r2dt, zun, zvn, zwn, trb, trn, tra, jptra )   !  UBS  
    136 !cbr      CASE ( 6 )   ;    CALL tra_adv_qck   ( kt, nittrc000, 'TRC', r2dt, zun, zvn, zwn, trb, trn, tra, jptra )   !  QUICKEST  
    137115      ! 
    138116      CASE (-1 )                                      !==  esopa: test all possibility with control print  ==! 
    139 !         CALL tra_adv_cen2  ( kt, nittrc000, 'TRC',       zun, zvn, zwn, trb, trn, tra, jptra )           
    140 !         WRITE(charout, FMT="('adv1')")  ; CALL prt_ctl_trc_info(charout) 
    141 !                                           CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
    142117         CALL tra_adv_tvd_crs   ( kt, nittrc000, 'TRC', r2dt, zun, zvn, zwn, trb, trn, tra, jptra )           
    143118         WRITE(charout, FMT="('adv2')")  ; CALL prt_ctl_trc_info(charout) 
    144                                            CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
    145 !         CALL tra_adv_muscl ( kt, nittrc000, 'TRC', r2dt, zun, zvn, zwn, trb,      tra, jptra )           
    146 !         WRITE(charout, FMT="('adv3')")  ; CALL prt_ctl_trc_info(charout) 
    147 !                                           CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
    148 !         CALL tra_adv_muscl2( kt, nittrc000, 'TRC', r2dt, zun, zvn, zwn, trb, trn, tra, jptra )           
    149 !         WRITE(charout, FMT="('adv4')")  ; CALL prt_ctl_trc_info(charout) 
    150 !                                           CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
    151 !         CALL tra_adv_ubs   ( kt, nittrc000, 'TRC', r2dt, zun, zvn, zwn, trb, trn, tra, jptra )           
    152 !         WRITE(charout, FMT="('adv5')")  ; CALL prt_ctl_trc_info(charout) 
    153 !                                           CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
    154 !         CALL tra_adv_qck   ( kt, nittrc000, 'TRC', r2dt, zun, zvn, zwn, trb, trn, tra, jptra )           
    155 !         WRITE(charout, FMT="('adv6')")  ; CALL prt_ctl_trc_info(charout) 
    156119                                           CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
    157120         ! 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90

    r5602 r6772  
    2727   !!---------------------------------------------------------------------- 
    2828   USE oce_trc         ! ocean dynamics and tracers variables 
    29    USE trc             ! ocean passive tracers variables 
     29   USE trc, ONLY : nittrc000, tra, jptra,rdttrc,trb, trn,tra,ctrcnm            ! ocean passive tracers variables 
    3030   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    3131   USE prtctl_trc      ! Print control for debbuging 
     
    3636   USE agrif_top_interp 
    3737# endif 
     38   USE crs, ONLY : ln_crs_top 
     39   USE ieee_arithmetic 
    3840 
    3941   IMPLICIT NONE 
     
    8991      INTEGER, INTENT( in ) ::   kt     ! ocean time-step index 
    9092      ! 
    91       INTEGER  ::   jk, jn   ! dummy loop indices 
     93      INTEGER  ::   ji,jj,jk, jn   ! dummy loop indices 
    9294      REAL(wp) ::   zfact            ! temporary scalar 
    9395      CHARACTER (len=22) :: charout 
     
    137139      ELSE 
    138140         ! Leap-Frog + Asselin filter time stepping 
    139          IF( lk_vvl ) THEN   ;   CALL tra_nxt_vvl( kt, nittrc000, rdttrc, 'TRC', trb, trn, tra,      & 
    140            &                                                                sbc_trc, sbc_trc_b, jptra )      ! variable volume level (vvl)  
    141          ELSE                ;   CALL tra_nxt_fix( kt, nittrc000,         'TRC', trb, trn, tra, jptra )      ! fixed    volume level  
     141         IF( lk_vvl ) THEN    
     142 
     143            IF( ln_crs_top )THEN  
     144               CALL tra_nxt_vvl_crs( kt, nittrc000, rdttrc, 'TRC', trb, trn, tra,      & 
     145              &                                              sbc_trc, sbc_trc_b, jptra )      ! variable volume level (vvl)  
     146            ELSE 
     147               CALL tra_nxt_vvl( kt, nittrc000, rdttrc, 'TRC', trb, trn, tra,      & 
     148              &                                          sbc_trc, sbc_trc_b, jptra )      ! variable volume level (vvl)  
     149            ENDIF 
     150         ELSE                   ;   CALL tra_nxt_fix( kt, nittrc000,         'TRC', trb, trn, tra, jptra )      ! fixed    volume level  
    142151         ENDIF 
    143152      ENDIF 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trcsbc.F90

    r6101 r6772  
    1717   !!---------------------------------------------------------------------- 
    1818   USE oce_trc         ! ocean dynamics and active tracers variables 
    19    USE trc             ! ocean  passive tracers variables 
     19   USE trc , ONLY  : trn,tra,ln_top_euler,rdttrc,nittrc000,ln_rsttr,numrtr,ctrcnm,jptra,numrtw,nn_ice_tr,lrst_trc 
    2020   USE prtctl_trc      ! Print control for debbuging 
    21    USE iom, ONLY : iom_varid, iom_get, iom_rstput,jpdom_autoglo 
     21   USE iom  , ONLY : iom_varid, iom_get, iom_rstput,jpdom_autoglo 
    2222   USE trd_oce 
    2323   USE trdtra 
     24   USE ieee_arithmetic 
    2425 
    2526   IMPLICIT NONE 
     
    135136 
    136137      ! 0. initialization 
     138      sbc_trc(:,:,:)=0._wp 
    137139      DO jn = 1, jptra 
    138140         ! 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp.F90

    r6101 r6772  
    1414   !!---------------------------------------------------------------------- 
    1515   USE oce_trc         ! ocean dynamics and active tracers variables 
     16   USE crs, ONLY: fmmflx_crs 
    1617   USE trc             ! ocean passive tracers variables  
    1718   USE trcnam_trp      ! passive tracers transport namelist variables 
     
    3132   USE trcrad          ! positivity                          (trc_rad routine) 
    3233   USE trcsbc          ! surface boundary condition          (trc_sbc routine) 
    33    USE trcsbc_crs      ! surface boundary condition          (trc_sbc routine) 
    3434   USE zpshde          ! partial step: hor. derivative       (zps_hde routine) 
    3535   USE zpshde_crs      ! partial step: hor. derivative       (zps_hde routine) 
    3636   USE dom_oce , ONLY : ln_crs, ln_isfcav 
    37    USE crs     , ONLY : jpi_crs,jpj_crs,wn_crs,ln_crs_top !cbr 
     37   USE crs     , ONLY : jpi_crs,jpj_crs,wn_crs,ln_crs_top,sbc_trc_crs,sbc_trc_b_crs 
    3838   USE ldfslp_crs 
    3939#if defined key_agrif 
     
    4141   USE agrif_top_update ! tracers updates 
    4242#endif 
     43   USE ieee_arithmetic 
    4344 
    4445   IMPLICIT NONE 
     
    7576      IF( .NOT. lk_c1d ) THEN 
    7677         ! 
    77          IF( ln_crs_top ) THEN ;    CALL trc_sbc_crs( kstp ) 
    78          ELSE              ;    CALL trc_sbc( kstp ) 
    79          ENDIF 
     78         CALL test(kstp,1) 
     79                               CALL trc_sbc( kstp ) 
     80         CALL test(kstp,2) 
    8081         IF( ln_crs_top ) THEN ;    CALL trc_bbl_crs( kstp ) 
    8182         ELSE              ;    CALL trc_bbl( kstp ) 
     
    8384         IF( ln_trcdmp )        CALL trc_dmp( kstp )            ! internal damping trends 
    8485 
     86         CALL test(kstp,3) 
    8587         IF( ln_crs_top ) THEN ;    CALL trc_adv_crs( kstp ) 
    8688         ELSE              ;    CALL trc_adv( kstp ) 
    8789         ENDIF 
    8890 
     91         CALL test(kstp,4) 
    8992         IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kstp )        ! internal damping trends on closed seas only 
    9093         IF( ln_crs_top ) THEN ;    CALL trc_ldf_crs( kstp ) 
    9194         ELSE              ;    CALL trc_ldf( kstp ) 
    9295         ENDIF 
     96         CALL test(kstp,5) 
    9397         IF( .NOT. lk_offline .AND. lk_zdfkpp )    & 
    9498            &                   CALL trc_kpp( kstp )            ! KPP non-local tracer fluxes 
     
    99103         ELSE              ;    CALL trc_zdf( kstp ) 
    100104         ENDIF 
     105         CALL test(kstp,6) 
     106 
    101107                                CALL trc_nxt( kstp )            ! tracer fields at next time step      
     108         CALL test(kstp,10) 
    102109         IF( ln_trcrad )        CALL trc_rad( kstp )            ! Correct artificial negative concentrations 
    103110 
     
    132139      ! 
    133140   END SUBROUTINE trc_trp 
     141 
    134142   SUBROUTINE test(kt,i) 
    135143   INTEGER,INTENT(IN) :: kt,i 
    136144   REAL(wp)::zmin,zmax 
    137    INTEGER :: ii,jj,kk 
     145   INTEGER :: ji,jj,jk 
    138146   zmin=MINVAL( trb(2:jpi-1,2:jpj-1,:,1),mask=(tmask(2:jpi-1,2:jpj-1,:)==1)) ; CALL mpp_min(zmin) 
    139147   zmax=MAXVAL( trb(2:jpi-1,2:jpj-1,:,1),mask=(tmask(2:jpi-1,2:jpj-1,:)==1)) ; CALL mpp_max(zmax) 
     
    145153   zmax=MAXVAL( tra(2:jpi-1,2:jpj-1,:,1),mask=(tmask(2:jpi-1,2:jpj-1,:)==1)) ; CALL mpp_max(zmax) 
    146154   IF(lwp)WRITE(numout,*)"trctrp a ",kt,i,zmin,zmax    
    147    zmin=MINVAL( tra(2:jpi-1,2:jpj-1,30,1),mask=(tmask(2:jpi-1,2:jpj-1,30)==1)) ; CALL mpp_min(zmin) 
    148    zmax=MAXVAL( tra(2:jpi-1,2:jpj-1,30,1),mask=(tmask(2:jpi-1,2:jpj-1,30)==1)) ; CALL mpp_max(zmax) 
    149155 
    150156   END SUBROUTINE test 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/oce_trc.F90

    r6101 r6772  
    102102   USE crs , ONLY :   e1v        =>   e1v_crs        !: horizontal scale factors at v-point (m) 
    103103   USE crs , ONLY :   e2v        =>   e2v_crs        !: horizontal scale factors at v-point (m)   
    104    USE crs , ONLY :   e3t        =>  e3t_crs         !: vertical scale factors at t- 
    105    USE crs , ONLY :   e3t_0      =>  e3t_crs         !: vertical scale factors at t- 
    106    USE crs , ONLY :   fse3t      =>  e3t_crs 
    107    USE crs , ONLY :   fse3t_b      =>  e3t_crs 
    108    USE crs , ONLY :   fse3t_a      =>  e3t_crs 
    109    USE crs , ONLY :   fse3w      =>  e3w_crs 
    110    USE crs , ONLY :   e3u        =>  e3u_crs         !: vertical scale factors at u- 
    111    USE crs , ONLY :   e3u_0      =>  e3u_crs         !: vertical scale factors at u- 
    112    USE crs , ONLY :   e3v        =>  e3v_crs         !: vertical scale factors v- 
    113    USE crs , ONLY :   e3v_0      =>  e3v_crs         !: vertical scale factors v- 
    114    USE crs , ONLY :   e3w        =>  e3w_crs         !: w-points (m) 
    115    USE crs , ONLY :   e3w_0      =>  e3w_crs         !: w-points (m) 
    116    USE crs , ONLY :   e3f        =>  e3f_crs         !: f-points (m) 
     104 
     105#if defined key_vvl  
     106   USE crs , ONLY :   e3t        =>  e3t_n_crs         !: vertical scale factors at t- 
     107   USE crs , ONLY :   e3u        =>  e3u_n_crs         !: vertical scale factors at u- 
     108   USE crs , ONLY :   e3v        =>  e3v_n_crs         !: vertical scale factors v- 
     109   USE crs , ONLY :   e3w        =>  e3w_n_crs         !: w-points (m) 
     110   USE crs , ONLY :   e3t_n      =>  e3t_n_crs         !: vertical scale factors at t- 
     111   USE crs , ONLY :   e3u_n      =>  e3u_n_crs         !: vertical scale factors at u- 
     112   USE crs , ONLY :   e3v_n      =>  e3v_n_crs         !: vertical scale factors v- 
     113   USE crs , ONLY :   e3w_n      =>  e3w_n_crs         !: w-points (m) 
     114   USE crs , ONLY :   e3t_a      =>  e3t_a_crs         !: vertical scale factors at t- 
     115   USE crs , ONLY :   e3u_a      =>  e3u_a_crs         !: vertical scale factors at u- 
     116   USE crs , ONLY :   e3v_a      =>  e3v_a_crs         !: vertical scale factors v- 
     117   USE crs , ONLY :   e3w_a      =>  e3w_a_crs         !: w-points (m) 
     118   USE crs , ONLY :   fse3t      =>  e3t_n_crs         !: vertical scale factors at t- 
     119   USE crs , ONLY :   fse3u      =>  e3u_n_crs         !: vertical scale factors at u- 
     120   USE crs , ONLY :   fse3v      =>  e3v_n_crs         !: vertical scale factors v- 
     121   USE crs , ONLY :   fse3w      =>  e3w_n_crs         !: w-points (m) 
     122   USE crs , ONLY :   gdept      =>  gdept_n_crs       !: depth of t-points (m) 
     123   USE crs , ONLY :   gdept_crs  =>  gdept_n_crs       !: depth of t-points (m) 
     124   USE crs , ONLY :   gdept_n    =>  gdept_n_crs       !: depth of t-points (m) 
     125   USE crs , ONLY :   fse3t_b    =>  e3t_b_crs         !: vertical scale factors at t- 
     126   USE crs , ONLY :   fse3t_n    =>  e3t_n_crs         !: vertical scale factors at t- 
     127   USE crs , ONLY :   fse3t_a    =>  e3t_a_crs         !: vertical scale factors at t- 
     128   USE crs , ONLY :   fsdept_n   =>  gdept_n_crs       !: depth of t-points (m) 
     129   USE crs , ONLY :   e3t_max_crs => e3t_max_n_crs 
     130   USE crs , ONLY :   e3u_max_crs => e3u_max_n_crs 
     131   USE crs , ONLY :   e3v_max_crs => e3v_max_n_crs 
     132   USE crs , ONLY :   e3w_max_crs => e3w_max_n_crs 
     133#else 
     134   USE crs , ONLY :   e3t        =>  e3t_0_crs         !: vertical scale factors at t- 
     135   USE crs , ONLY :   e3u        =>  e3u_0_crs         !: vertical scale factors at u- 
     136   USE crs , ONLY :   e3v        =>  e3v_0_crs         !: vertical scale factors v- 
     137   USE crs , ONLY :   e3w        =>  e3w_0_crs         !: w-points (m) 
     138   USE crs , ONLY :   e3t_n      =>  e3t_0_crs         !: vertical scale factors at t- 
     139   USE crs , ONLY :   e3u_n      =>  e3u_0_crs         !: vertical scale factors at u- 
     140   USE crs , ONLY :   e3v_n      =>  e3v_0_crs         !: vertical scale factors v- 
     141   USE crs , ONLY :   e3w_n      =>  e3w_0_crs         !: w-points (m) 
     142   USE crs , ONLY :   e3t_a      =>  e3t_0_crs         !: vertical scale factors at t- 
     143   USE crs , ONLY :   e3u_a      =>  e3u_0_crs         !: vertical scale factors at u- 
     144   USE crs , ONLY :   e3v_a      =>  e3v_0_crs         !: vertical scale factors v- 
     145   USE crs , ONLY :   e3w_a      =>  e3w_0_crs         !: w-points (m) 
     146   USE crs , ONLY :   fse3t      =>  e3t_0_crs         !: vertical scale factors at t- 
     147   USE crs , ONLY :   fse3u      =>  e3u_0_crs         !: vertical scale factors at u- 
     148   USE crs , ONLY :   fse3v      =>  e3v_0_crs         !: vertical scale factors v- 
     149   USE crs , ONLY :   fse3w      =>  e3w_0_crs         !: w-points (m) 
     150   USE crs , ONLY :   gdept      =>  gdept_0_crs       !: depth of t-points (m) 
     151   USE crs , ONLY :   gdepw      =>  gdepw_0_crs       !: depth of t-points (m) 
     152   USE crs , ONLY :   gdept_crs  =>  gdept_0_crs       !: depth of t-points (m) 
     153   USE crs , ONLY :   gdepw_crs  =>  gdepw_0_crs       !: depth of t-points (m) 
     154   USE crs , ONLY :   gdept_n    =>  gdept_0_crs       !: depth of t-points (m) 
     155   USE crs , ONLY :   fse3t_b    =>  e3t_0_crs         !: vertical scale factors at t- 
     156   USE crs , ONLY :   fse3t_n    =>  e3t_0_crs         !: vertical scale factors at t- 
     157   USE crs , ONLY :   fse3t_a    =>  e3t_0_crs         !: vertical scale factors at t- 
     158   USE crs , ONLY :   fsdept_n   =>  gdept_0_crs       !: depth of t-points (m) 
     159   USE crs , ONLY :   e3t_max_crs => e3t_max_0_crs 
     160   USE crs , ONLY :   e3u_max_crs => e3u_max_0_crs 
     161   USE crs , ONLY :   e3v_max_crs => e3v_max_0_crs 
     162   USE crs , ONLY :   e3w_max_crs => e3w_max_0_crs 
     163#endif 
     164   USE crs , ONLY :   e3t_0        =>  e3t_0_crs         !: vertical scale factors at t- 
     165   USE crs , ONLY :   e3u_0        =>  e3u_0_crs         !: vertical scale factors at t- 
     166   USE crs , ONLY :   e3v_0        =>  e3v_0_crs         !: vertical scale factors at t- 
     167   USE crs , ONLY :   e3w_0        =>  e3w_0_crs         !: vertical scale factors at t- 
     168 
    117169   USE crs , ONLY :   ff         =>  ff_crs         !: f-points (m) 
    118  
    119    USE crs , ONLY :   gdept_0    =>  gdept_crs       !: depth of t-points (m) 
     170   USE crs , ONLY :   gdept_0    =>  gdept_0_crs       !: depth of t-points (m) 
    120171   USE dom_oce , ONLY :   gdept_1d   =>  gdept_1d      !: depth of t-points (m) 
    121172#if defined key_zco 
    122    USE crs , ONLY :   gdept      =>  gdept_crs       !: depth of t-points (m) 
     173   USE crs , ONLY :   gdept      =>  gdept_0_crs       !: depth of t-points (m) 
    123174   USE crs , ONLY :   gdepw      =>  gdepw_crs       !: depth of t-points (m) 
    124175#endif 
     
    140191   USE crs , ONLY :   wn      =>    wn_crs      !: vertical velocity (m s-1)   
    141192   USE crs , ONLY :   tsn     =>    tsn_crs     !: 4D array contaning ( tn, sn ) 
    142    USE oce , ONLY :   tsb     =>    tsb     !: 4D array contaning ( tb, sb ) 
    143    USE oce , ONLY :   tsa     =>    tsa     !: 4D array contaning ( ta, sa ) 
    144    USE oce , ONLY :   rhop    =>    rhop    !: potential volumic mass (kg m-3)  
     193   USE crs , ONLY :   tsb     =>    tsb_crs     !: 4D array contaning ( tb, sb ) 
     194   USE crs , ONLY :   tsa     =>    tsa_crs     !: 4D array contaning ( ta, sa ) 
     195   USE crs , ONLY :   rhop    =>    rhop_crs    !: potential volumic mass (kg m-3)  
    145196   USE crs , ONLY :   rhd     =>    rhd_crs    !: in situ density anomalie rhd=(rho-rau0)/rau0 (no units) 
    146197   USE crs , ONLY :   rn2b    =>    rb2_crs     !: in situ density anomalie rhd=(rho-rau0)/rau0 (no units) 
     
    160211   USE crs , ONLY :   emp_b      =>    emp_b_crs      !: freshwater budget: volume flux               [Kg/m2/s] 
    161212   USE crs , ONLY :   sfx        =>    sfx_crs        !: freshwater budget: concentration/dillution   [Kg/m2/s] 
     213   USE crs , ONLY :   sbc_trc_b  =>    sbc_trc_b_crs      !: freshwater budget: volume flux               [Kg/m2/s] 
     214   USE crs , ONLY :   sbc_trc    =>    sbc_trc_crs      !: freshwater budget: volume flux               [Kg/m2/s] 
    162215   USE crs , ONLY :   fmmflx     =>    fmmflx_crs     !: freshwater budget: volume flux               [Kg/m2/s] 
    163216   USE crs , ONLY :   rnf        =>    rnf_crs        !: river runoff   [Kg/m2/s] 
     
    169222   USE crs , ONLY :  ahtt     =>   ahtt_crs        !: lateral diffusivity coef. at t-points 
    170223   USE ldftra_oce , ONLY :  rldf     =>   rldf 
    171  
     224   USE crs , ONLY :  trc_i => trc_i_crs 
     225   USE crs , ONLY :  trc_o => trc_o_crs 
    172226   USE crs , ONLY :   avt        =>   avt_crs         !: vert. diffusivity coef. at w-point for temp   
    173227#if defined key_zdfddm 
     
    262316   USE dom_oce , ONLY :   e3t        =>  e3t_0         !: vertical scale factors at t- 
    263317   USE dom_oce , ONLY :   e3t_0      =>  e3t_0         !: vertical scale factors at t- 
     318#if defined key_vvl  
     319   USE dom_oce , ONLY :   fse3t_b    =>  e3t_b 
     320   USE dom_oce , ONLY :   fse3t_n    =>  e3t_n 
     321   USE dom_oce , ONLY :   fse3t      =>  e3t_n 
     322   USE dom_oce , ONLY :   fse3u      =>  e3u_n 
     323   USE dom_oce , ONLY :   fse3v      =>  e3v_n 
     324   USE dom_oce , ONLY :   fse3w      =>  e3w_n 
     325   USE dom_oce , ONLY :   fse3t_a    =>  e3t_a 
     326   USE dom_oce , ONLY :     e3t_b    =>  e3t_b 
     327   USE dom_oce , ONLY :     e3t_n    =>  e3t_n 
     328   USE dom_oce , ONLY :     e3t_a    =>  e3t_a 
     329   USE dom_oce , ONLY :     e3u_n    =>  e3u_n 
     330   USE dom_oce , ONLY :     e3v_n    =>  e3v_n 
     331   USE dom_oce , ONLY :   e3u        =>  e3u_n         !: vertical scale factors at u- 
     332   USE dom_oce , ONLY :   e3u_0      =>  e3u_0         !: vertical scale factors at u- 
     333   USE dom_oce , ONLY :   e3v        =>  e3v_n         !: vertical scale factors v- 
     334   USE dom_oce , ONLY :   e3v_0      =>  e3v_0         !: vertical scale factors v- 
     335   USE dom_oce , ONLY :   e3w_n      =>  e3w_n         !: w-points (m) 
     336   USE dom_oce , ONLY :   e3w        =>  e3w_n         !: w-points (m) 
     337   USE dom_oce , ONLY :   e3w_0      =>  e3w_0         !: w-points (m) 
     338   USE dom_oce , ONLY :   e3f        =>  e3f_n         !: f-points (m) 
     339   USE dom_oce , ONLY :   gdept_n    =>  gdept_n         !: f-points (m) 
     340   USE dom_oce , ONLY :  fsdept_n    =>  gdept_n         !: f-points (m) 
     341#else 
     342   USE dom_oce , ONLY :   fse3t_n    =>  e3t_0 
    264343   USE dom_oce , ONLY :   fse3t      =>  e3t_0 
    265    USE dom_oce , ONLY :   fse3t_b      =>  e3t_0 
    266    USE dom_oce , ONLY :   fse3t_a      =>  e3t_0 
     344   USE dom_oce , ONLY :   fse3u      =>  e3u_0 
     345   USE dom_oce , ONLY :   fse3v      =>  e3v_0 
    267346   USE dom_oce , ONLY :   fse3w      =>  e3w_0 
     347   USE dom_oce , ONLY :   fse3t_b    =>  e3t_0 
     348   USE dom_oce , ONLY :   fse3t_a    =>  e3t_0 
     349   USE dom_oce , ONLY :     e3t_a    =>  e3t_0 
    268350   USE dom_oce , ONLY :   e3u        =>  e3u_0         !: vertical scale factors at u- 
    269351   USE dom_oce , ONLY :   e3u_0      =>  e3u_0         !: vertical scale factors at u- 
     
    273355   USE dom_oce , ONLY :   e3w_0      =>  e3w_0         !: w-points (m) 
    274356   USE dom_oce , ONLY :   e3f        =>  e3f_0         !: f-points (m) 
     357   USE dom_oce , ONLY :   gdept_n    =>  gdept_0         !: f-points (m) 
     358   USE dom_oce , ONLY :  fsdept_n    =>  gdept_0         !: f-points (m) 
     359#endif 
    275360   USE dom_oce , ONLY :   ff         =>  ff         !: f-points (m) 
    276361   USE dom_oce , ONLY :   gdept_0    =>  gdept_0         !: f-points (m) 
     
    349434   USE sbc_oce , ONLY :   rnf        =>    rnf        !: river runoff   [Kg/m2/s] 
    350435   USE sbc_oce , ONLY :   ln_dm2dc   =>    ln_dm2dc   !: Diurnal Cycle  
    351    USE sbc_oce , ONLY :   ncpl_qsr_freq   =>   ncpl_qsr_freq   !: qsr coupling frequency per days from atmospher 
    352    USE sbc_oce , ONLY :   ln_rnf     =>    ln_rnf     !: runoffs / runoff mouths 
    353436   USE sbc_oce , ONLY :   fr_i       =>    fr_i       !: ice fraction (between 0 to 1) 
    354    USE sbc_oce , ONLY :   nn_ice_embd => nn_ice_embd  !: flag for  levitating/embedding sea-ice in the ocean 
    355437   USE traqsr  , ONLY :   rn_abs     =>    rn_abs     !: fraction absorbed in the very near surface 
    356438   USE traqsr  , ONLY :   rn_si0     =>    rn_si0     !: very near surface depth of extinction 
     
    360442   USE sbcrnf  , ONLY :   h_rnf      =>    h_rnf      !: river runoff   [Kg/m2/s] 
    361443   USE sbcrnf  , ONLY :   nk_rnf     =>    nk_rnf     !: depth of runoff in model level 
     444   USE trc     , ONLY :   sbc_trc_b  =>    sbc_trc_b  !: freshwater budget: volume flux               [Kg/m2/s] 
     445   USE trc     , ONLY :   sbc_trc    =>    sbc_trc    !: freshwater budget: volume flux               [Kg/m2/s] 
     446   USE trc , ONLY :  trc_i => trc_i 
     447   USE trc , ONLY :  trc_o => trc_o 
    362448 
    363449   USE trc_oce 
     
    407493   USE sbc_oce , ONLY : nn_ice_embd 
    408494   USE sbc_oce , ONLY : ln_cpl 
     495   USE sbc_oce , ONLY : ln_rnf 
    409496   USE sbc_oce , ONLY : ncpl_qsr_freq 
    410497 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcdta.F90

    r6101 r6772  
    3737!$AGRIF_END_DO_NOT_TREAT 
    3838   !! * Substitutions 
    39 #  include "domzgr_substitute.h90" 
     39!cbr #  include "domzgr_substitute.h90" 
    4040   !!---------------------------------------------------------------------- 
    4141   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcice.F90

    r5602 r6772  
    1414 
    1515   USE oce_trc         ! shared variables between ocean and passive tracers 
    16    USE trc             ! passive tracers common variables 
     16   USE trc, ONLY : nn_ice_tr,lk_pisces,lk_cfc,lk_c14b,lk_my_trc             ! passive tracers common variables 
    1717   USE trcice_cfc      ! CFC      initialisation 
    1818   USE trcice_pisces   ! PISCES   initialisation 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcstp.F90

    r6101 r6772  
    7777      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt ) 
    7878      !     
    79       IF( nn_dttrc /= 1 )   CALL trc_sub_stp( kt )  ! averaging physical variables for sub-stepping 
     79!cbr      IF( nn_dttrc /= 1 )   CALL trc_sub_stp( kt )  ! averaging physical variables for sub-stepping 
    8080      !     
    8181      IF( MOD( kt , nn_dttrc ) == 0 ) THEN      ! only every nn_dttrc time step 
     
    102102         IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt )       ! trends: Mixed-layer 
    103103         ! 
    104          IF( nn_dttrc /= 1   )     CALL trc_sub_reset( kt )       ! resetting physical variables when sub-stepping 
     104!cbr         IF( nn_dttrc /= 1   )     CALL trc_sub_reset( kt )       ! resetting physical variables when sub-stepping 
    105105         ! 
    106106      ENDIF 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcsub.F90

    r5602 r6772  
    4545 
    4646   !!* Substitution 
    47 #  include "top_substitute.h90" 
     47!!#  include "top_substitute.h90" 
    4848   !!---------------------------------------------------------------------- 
    4949   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     
    111111          ! 
    112112          sshn_tm  (:,:)         = sshn_tm  (:,:)         + sshn  (:,:)  
    113           rnf_tm   (:,:)         = rnf_tm   (:,:)         + rnf   (:,:)  
    114 !cbr          h_rnf_tm (:,:)         = h_rnf_tm (:,:)         + h_rnf (:,:)  
     113          IF( ln_rnf )THEN 
     114             rnf_tm   (:,:)         = rnf_tm   (:,:)         + rnf   (:,:)  
     115             h_rnf_tm (:,:)         = h_rnf_tm (:,:)         + h_rnf (:,:)  
     116          ENDIF 
    115117          hmld_tm  (:,:)         = hmld_tm  (:,:)         + hmld  (:,:) 
    116118          fr_i_tm  (:,:)         = fr_i_tm  (:,:)         + fr_i  (:,:) 
     
    151153         ssha_temp  (:,:)        = ssha  (:,:) 
    152154         rnf_temp   (:,:)        = rnf   (:,:) 
    153 !cbr         h_rnf_temp (:,:)        = h_rnf (:,:) 
    154          hmld_temp  (:,:)        = hmld  (:,:) 
     155         IF( ln_rnf )THEN 
     156            h_rnf_temp (:,:)        = h_rnf (:,:) 
     157            hmld_temp  (:,:)        = hmld  (:,:) 
     158         ENDIF 
    155159         fr_i_temp  (:,:)        = fr_i  (:,:) 
    156160         emp_temp   (:,:)        = emp   (:,:) 
     
    196200# endif 
    197201         sshn_tm  (:,:)          = sshn_tm    (:,:)       + sshn  (:,:)  
    198          rnf_tm   (:,:)          = rnf_tm     (:,:)       + rnf   (:,:)  
    199 !cbr         h_rnf_tm (:,:)          = h_rnf_tm   (:,:)       + h_rnf (:,:)  
     202         IF( ln_rnf )THEN 
     203            rnf_tm   (:,:)          = rnf_tm     (:,:)       + rnf   (:,:)  
     204            h_rnf_tm (:,:)          = h_rnf_tm   (:,:)       + h_rnf (:,:)  
     205         ENDIF 
    200206         hmld_tm  (:,:)          = hmld_tm    (:,:)       + hmld  (:,:) 
    201207         fr_i_tm  (:,:)          = fr_i_tm    (:,:)       + fr_i  (:,:) 
     
    207213         sshn     (:,:)          = sshn_tm    (:,:) * r1_ndttrcp1  
    208214         sshb     (:,:)          = sshb_hold  (:,:) 
    209          rnf      (:,:)          = rnf_tm     (:,:) * r1_ndttrcp1  
    210 !cbr         h_rnf    (:,:)          = h_rnf_tm   (:,:) * r1_ndttrcp1  
     215         IF( ln_rnf )THEN 
     216            rnf      (:,:)          = rnf_tm     (:,:) * r1_ndttrcp1  
     217            h_rnf    (:,:)          = h_rnf_tm   (:,:) * r1_ndttrcp1  
     218         ENDIF 
    211219         hmld     (:,:)          = hmld_tm    (:,:) * r1_ndttrcp1  
    212220         !  variables that are initialized after averages 
     
    319327#endif 
    320328      sshn_tm  (:,:) = sshn  (:,:)  
    321       rnf_tm   (:,:) = rnf   (:,:)  
    322 !cbr      h_rnf_tm (:,:) = h_rnf (:,:)  
     329      IF( ln_rnf )THEN 
     330         rnf_tm   (:,:) = rnf   (:,:)  
     331         h_rnf_tm (:,:) = h_rnf (:,:)  
     332      ENDIF 
    323333      hmld_tm  (:,:) = hmld  (:,:) 
    324334 
     
    378388      sshb  (:,:)     =  sshb_temp  (:,:) 
    379389      ssha  (:,:)     =  ssha_temp  (:,:) 
    380       rnf   (:,:)     =  rnf_temp   (:,:) 
    381 !cbr      h_rnf (:,:)     =  h_rnf_temp (:,:) 
     390      IF( ln_rnf )THEN 
     391         rnf   (:,:)     =  rnf_temp   (:,:) 
     392         h_rnf (:,:)     =  h_rnf_temp (:,:) 
     393      ENDIF 
    382394      ! 
    383395      hmld  (:,:)     =  hmld_temp  (:,:) 
     
    427439      emp_b_hold (:,:) = emp   (:,:) 
    428440      sshn_tm    (:,:) = sshn  (:,:)  
    429       rnf_tm     (:,:) = rnf   (:,:)  
    430 !cbr      h_rnf_tm   (:,:) = h_rnf (:,:)  
     441      IF( ln_rnf )THEN 
     442         rnf_tm     (:,:) = rnf   (:,:)  
     443         h_rnf_tm   (:,:) = h_rnf (:,:)  
     444      ENDIF 
    431445      hmld_tm    (:,:) = hmld  (:,:) 
    432446      fr_i_tm    (:,:) = fr_i  (:,:) 
Note: See TracChangeset for help on using the changeset viewer.