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

Ignore:
Timestamp:
2015-02-24T15:46:25+01:00 (9 years ago)
Author:
cbricaud
Message:

bug correction

Location:
branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC
Files:
5 added
9 edited

Legend:

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

    r4996 r5105  
    1313   !!---------------------------------------------------------------------- 
    1414   USE trc         ! passive tracers common variables  
    15    USE iom         ! I/O manager 
     15   USE oce_trc 
     16   USE crs, ONLY : ln_crs 
    1617 
    1718   IMPLICIT NONE 
     
    3233      INTEGER              :: jn 
    3334      !!--------------------------------------------------------------------- 
     35      IF( ln_crs ) CALL iom_swap( "nemo_crs" ) 
    3436  
    3537      ! write the tracer concentrations in the file 
     
    3739      DO jn = jp_myt0, jp_myt1 
    3840         cltra = TRIM( ctrcnm(jn) )                  ! short title for tracer 
    39          CALL iom_put( cltra, trn(:,:,:,jn) ) 
     41         IF( lk_vvl ) THEN 
     42            CALL iom_put( cltra, trn(:,:,:,jn) * fse3t_n(:,:,:) ) 
     43         ELSE 
     44            CALL iom_put( TRIM(cltra), trn(:,:,:,jn) ) 
     45         ENDIF 
    4046      END DO 
     47      ! 
     48      IF( ln_crs ) CALL iom_swap( "nemo" ) 
    4149      ! 
    4250   END SUBROUTINE trc_wri_my_trc 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp.F90

    r4990 r5105  
    1717   USE trcnam_trp      ! passive tracers transport namelist variables 
    1818   USE trabbl          ! bottom boundary layer               (trc_bbl routine) 
     19   USE trabbl_crs      ! bottom boundary layer               (trc_bbl routine) 
    1920   USE trcbbl          ! bottom boundary layer               (trc_bbl routine) 
     21   USE trcbbl_crs      ! bottom boundary layer               (trc_bbl routine) 
    2022   USE zdfkpp          ! KPP non-local tracer fluxes         (trc_kpp routine) 
    2123   USE trcdmp          ! internal damping                    (trc_dmp routine) 
    2224   USE trcldf          ! lateral mixing                      (trc_ldf routine) 
     25   USE trcldf_crs      ! lateral mixing                      (trc_ldf routine) 
    2326   USE trcadv          ! advection                           (trc_adv routine) 
     27   USE trcadv_crs      ! advection                           (trc_adv routine) 
    2428   USE trczdf          ! vertical diffusion                  (trc_zdf routine) 
     29   USE trczdf_crs      ! vertical diffusion                  (trc_zdf routine 
    2530   USE trcnxt          ! time-stepping                       (trc_nxt routine) 
    2631   USE trcrad          ! positivity                          (trc_rad routine) 
    2732   USE trcsbc          ! surface boundary condition          (trc_sbc routine) 
     33   USE trcsbc_crs      ! surface boundary condition          (trc_sbc routine) 
    2834   USE zpshde          ! partial step: hor. derivative       (zps_hde routine) 
     35   USE zpshde_crs      ! partial step: hor. derivative       (zps_hde routine) 
     36   USE dom_oce , ONLY : ln_crs 
     37   USe crs, ONLY : jpi_crs,jpj_crs,wn_crs !cbr 
    2938 
    3039#if defined key_agrif 
     
    5867      !!---------------------------------------------------------------------- 
    5968      INTEGER, INTENT( in ) ::  kstp  ! ocean time-step index 
     69      REAL(wp) :: zmin,zmax 
     70      INTEGER :: ji,jj,jk 
    6071      !! --------------------------------------------------------------------- 
    6172      ! 
     
    6475      IF( .NOT. lk_c1d ) THEN 
    6576         ! 
    66                                 CALL trc_sbc( kstp )            ! surface boundary condition 
    67          IF( lk_trabbl )        CALL trc_bbl( kstp )            ! advective (and/or diffusive) bottom boundary layer scheme 
     77!         CALL test(kstp,1) 
     78!         IF( ln_crs ) THEN ;    CALL trc_sbc_crs( kstp ) 
     79!         ELSE              ;    CALL trc_sbc( kstp ) 
     80!         ENDIF 
     81!         CALL test(kstp,2) 
     82         IF( ln_crs ) THEN ;    CALL trc_bbl_crs( kstp ) 
     83         ELSE              ;    CALL trc_bbl( kstp ) 
     84         ENDIF 
    6885         IF( ln_trcdmp )        CALL trc_dmp( kstp )            ! internal damping trends 
     86!         CALL test(kstp,3) 
     87 
     88         IF( ln_crs ) THEN ;    CALL trc_adv_crs( kstp ) 
     89         ELSE              ;    CALL trc_adv( kstp ) 
     90         ENDIF 
     91!         CALL test(kstp,4) 
     92 
    6993         IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kstp )        ! internal damping trends on closed seas only 
    70                                 CALL trc_adv( kstp )            ! horizontal & vertical advection  
    71                                 CALL trc_ldf( kstp )            ! lateral mixing 
     94         IF( ln_crs ) THEN ;    CALL trc_ldf_crs( kstp ) 
     95         ELSE              ;    CALL trc_ldf( kstp ) 
     96         ENDIF 
     97!         CALL test(kstp,5) 
    7298         IF( .NOT. lk_offline .AND. lk_zdfkpp )    & 
    7399            &                   CALL trc_kpp( kstp )            ! KPP non-local tracer fluxes 
     
    75101         IF(.NOT. Agrif_Root()) CALL Agrif_Sponge_trc           ! tracers sponge 
    76102#endif 
    77                                 CALL trc_zdf( kstp )            ! vertical mixing and after tracer fields 
     103         IF( ln_crs ) THEN ;    CALL trc_zdf_crs( kstp ) 
     104         ELSE              ;    CALL trc_zdf( kstp ) 
     105         ENDIF 
     106!         CALL test(kstp,6) 
    78107                                CALL trc_nxt( kstp )            ! tracer fields at next time step      
     108!         CALL test(kstp,7) 
    79109         IF( ln_trcrad )        CALL trc_rad( kstp )            ! Correct artificial negative concentrations 
    80110 
     
    82112      IF( .NOT. Agrif_Root())   CALL Agrif_Update_Trc( kstp )   ! Update tracer at AGRIF zoom boundaries : children only 
    83113#endif 
    84          IF( ln_zps    )        CALL zps_hde( kstp, jptra, trn, pgtu=gtru, pgtv=gtrv, sgtu=gtrui, sgtv=gtrvi )  ! Partial steps: now horizontal gradient of passive 
     114         IF( ln_zps    )        CALL zps_hde( kstp, jptra, trn, gtru, gtrv )  ! Partial steps: now horizontal gradient of passive 
     115         IF( ln_zps    )THEN 
     116         IF( ln_crs ) THEN ;    CALL zps_hde_crs( kstp, jptra, trn, gtru, gtrv ) 
     117         ELSE              ;    CALL zps_hde( kstp, jptra, trn, gtru, gtrv ) 
     118         ENDIF 
     119         ENDIF 
    85120                                                                ! tracers at the bottom ocean level 
    86121         ! 
     
    98133      ! 
    99134   END SUBROUTINE trc_trp 
     135   SUBROUTINE test(kt,i) 
     136   INTEGER,INTENT(IN) :: kt,i 
     137   REAL(wp)::zmin,zmax 
     138   INTEGER :: ji,jj,jk 
     139   zmin=MINVAL( trb(2:jpi-1,2:jpj-1,:,1),mask=(tmask(2:jpi-1,2:jpj-1,:)==1)) ; CALL mpp_min(zmin) 
     140   zmax=MAXVAL( trb(2:jpi-1,2:jpj-1,:,1),mask=(tmask(2:jpi-1,2:jpj-1,:)==1)) ; CALL mpp_max(zmax) 
     141   IF(lwp)WRITE(numout,*)"trctrp b ",kt,i,zmin,zmax    
     142   zmin=MINVAL( trn(2:jpi-1,2:jpj-1,:,1),mask=(tmask(2:jpi-1,2:jpj-1,:)==1)) ; CALL mpp_min(zmin) 
     143   zmax=MAXVAL( trn(2:jpi-1,2:jpj-1,:,1),mask=(tmask(2:jpi-1,2:jpj-1,:)==1)) ; CALL mpp_max(zmax) 
     144   IF(lwp)WRITE(numout,*)"trctrp n ",kt,i,zmin,zmax    
     145   zmin=MINVAL( tra(2:jpi-1,2:jpj-1,:,1),mask=(tmask(2:jpi-1,2:jpj-1,:)==1)) ; CALL mpp_min(zmin) 
     146   zmax=MAXVAL( tra(2:jpi-1,2:jpj-1,:,1),mask=(tmask(2:jpi-1,2:jpj-1,:)==1)) ; CALL mpp_max(zmax) 
     147   IF(lwp)WRITE(numout,*)"trctrp a ",kt,i,zmin,zmax    
     148   zmin=MINVAL( trn(2:jpi-1,2:jpj-1,1:jpk-1,1),mask=(tmask(2:jpi-1,2:jpj-1,1:jpk-1)==1)) ; CALL mpp_min(zmin) 
     149   zmax=MAXVAL( trn(2:jpi-1,2:jpj-1,1:jpk-1,1),mask=(tmask(2:jpi-1,2:jpj-1,1:jpk-1)==1)) ; CALL mpp_max(zmax) 
     150   IF(lwp)WRITE(numout,*)"trctrp n ",kt,i,zmin,zmax    
     151   zmin=MINVAL( tra(2:jpi-1,2:jpj-1,1:jpk-1,1),mask=(tmask(2:jpi-1,2:jpj-1,1:jpk-1)==1)) ; CALL mpp_min(zmin) 
     152   zmax=MAXVAL( tra(2:jpi-1,2:jpj-1,1:jpk-1,1),mask=(tmask(2:jpi-1,2:jpj-1,1:jpk-1)==1)) ; CALL mpp_max(zmax) 
     153   IF(lwp)WRITE(numout,*)"trctrp a ",kt,i,zmin,zmax    
    100154 
     155   IF(narea==267)WRITE(narea+5000,*)"tra(17,5,74,1) = ",kt,i,tra(17,5,74,1) 
     156 
     157   DO ji=1,jpi 
     158   DO jj=1,jpj 
     159   DO jk=1,jpk 
     160      IF( tra(ji,jj,jk,1) .NE.  tra(ji,jj,jk,1) )WRITE(narea+200,*)"BUG7 ",ji,jj,jk, tra(ji,jj,jk,1); CALL FLUSH(narea+200) 
     161   ENDDO 
     162   ENDDO 
     163   ENDDO 
     164    
     165   END SUBROUTINE test 
    101166#else 
    102167   !!---------------------------------------------------------------------- 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/oce_trc.F90

    r4990 r5105  
    88   !!---------------------------------------------------------------------- 
    99#if defined key_top 
     10 
     11#if defined key_crs 
     12 
     13  !* Domain size * 
     14   USE par_oce , ONLY :   jpi      =>   jpi        !: first  dimension of grid --> i  
     15   USE par_oce , ONLY :   jpj      =>   jpj        !: second dimension of grid --> j   
     16   USE par_oce , ONLY :   jpk      =>   jpk        !: number of levels   
     17   USE par_oce , ONLY :   jpim1    =>   jpim1      !: jpi - 1 
     18   USE par_oce , ONLY :   jpjm1    =>   jpjm1      !: jpj - 1  
     19   USE par_oce , ONLY :   jpkm1    =>   jpkm1      !: jpk - 1   
     20   USE par_oce , ONLY :   jpij     =>   jpij       !: jpi x jpj 
     21   USE par_oce , ONLY :   lk_esopa =>   lk_esopa   !: flag to activate the all option 
     22   USE par_oce , ONLY :   jp_tem   =>   jp_tem     !: indice for temperature 
     23   USE par_oce , ONLY :   jp_sal   =>   jp_sal     !: indice for salinity 
     24 
     25   !* IO manager * 
     26   USE in_out_manager 
     27 
     28   !* Memory Allocation * 
     29   USE wrk_nemo 
     30 
     31   !* Timing * 
     32   USE timing, ONLY : timing_start , timing_stop 
     33 
     34   !* MPP library                          
     35   USE lib_mpp 
     36 
     37   !* Fortran utilities                          
     38   USE lib_fortran 
     39 
     40   !* Lateral boundary conditions                          
     41   USE lbclnk 
     42 
     43   !* physical constants * 
     44   USE phycst 
     45 
     46   !* 1D configuration 
     47   USE c1d 
     48 
     49   !* model domain * 
     50   USE dom_oce , ONLY : narea => narea 
     51   USE dom_oce , ONLY : nproc => nproc 
     52   USE dom_oce , ONLY : nimpp => nimpp 
     53   USE dom_oce , ONLY : njmpp => njmpp 
     54   USE dom_oce , ONLY : nreci => nreci 
     55   USE dom_oce , ONLY : nrecj => nrecj 
     56   USE dom_oce , ONLY : nlci  => nlci 
     57   USE dom_oce , ONLY : nldi  => nldi 
     58   USE dom_oce , ONLY : nlei  => nlei 
     59   USE dom_oce , ONLY : nlcj  => nlcj 
     60   USE dom_oce , ONLY : nldj  => nldj 
     61   USE dom_oce , ONLY : nlej  => nlej 
     62   USE dom_oce , ONLY : nlcit  => nlcit 
     63   USE dom_oce , ONLY : nldit  => nldit 
     64   USE dom_oce , ONLY : nleit  => nleit 
     65   USE dom_oce , ONLY : nlcjt  => nlcjt 
     66   USE dom_oce , ONLY : nldjt  => nldjt 
     67   USE dom_oce , ONLY : nlejt  => nlejt 
     68   USE dom_oce , ONLY : nimppt => nimppt 
     69   USE dom_oce , ONLY : njmppt => njmppt 
     70   USE dom_oce , ONLY : ibonit => ibonit 
     71   USE dom_oce , ONLY : ibonjt => ibonjt 
     72   USE dom_oce , ONLY : lk_vvl => lk_vvl 
     73   USE dom_oce , ONLY : rdt => rdt 
     74   USE dom_oce , ONLY : ln_zco => ln_zco 
     75   USE dom_oce , ONLY : ln_zps => ln_zps 
     76   USE dom_oce , ONLY : ln_sco => ln_sco 
     77   USE dom_oce , ONLY : neuler => neuler 
     78 
     79   USE crs,  ONLY : mi0 => mi0  
     80   USE crs,  ONLY : mi1 => mi1  
     81   USE crs,  ONLY : mj0 => mj0  
     82   USE crs,  ONLY : mj1 => mj1  
     83 
     84   USE dom_oce , ONLY :  lzoom => lzoom  
     85   !USE dom_oce , ONLY :  =>  
     86 
     87   !* horizontal mesh * 
     88   USE crs , ONLY :   glamt      =>   glamt_crs      !: longitude of t-point (degre)   
     89   USE crs , ONLY :   glamu      =>   glamu_crs      !: longitude of t-point (degre)   
     90   USE crs , ONLY :   glamv      =>   glamv_crs      !: longitude of t-point (degre)   
     91   USE crs , ONLY :   glamf      =>   glamf_crs      !: longitude of t-point (degre)   
     92   USE crs , ONLY :   gphit      =>   gphit_crs      !: latitude  of t-point (degre)    
     93   USE crs , ONLY :   gphiu      =>   gphiu_crs      !: latitude  of t-point (degre)    
     94   USE crs , ONLY :   gphiv      =>   gphiv_crs      !: latitude  of t-point (degre)    
     95   USE crs , ONLY :   gphif      =>   gphif_crs      !: latitude  of t-point (degre)    
     96   USE crs , ONLY :   e1t        =>   e1t_crs        !: horizontal scale factors at t-point (m)   
     97   USE crs , ONLY :   e2t        =>   e2t_crs        !: horizontal scale factors at t-point (m)    
     98   USE crs , ONLY :   e1e2t      =>   e1e2t_crs      !: cell surface at t-point (m2) 
     99   USE crs , ONLY :   e1u        =>   e1u_crs        !: horizontal scale factors at u-point (m) 
     100   USE crs , ONLY :   e2u        =>   e2u_crs        !: horizontal scale factors at u-point (m) 
     101   USE crs , ONLY :   e1v        =>   e1v_crs        !: horizontal scale factors at v-point (m) 
     102   USE crs , ONLY :   e2v        =>   e2v_crs        !: horizontal scale factors at v-point (m)   
     103   USE crs , ONLY :   e3t        =>  e3t_crs         !: vertical scale factors at t- 
     104   USE crs , ONLY :   e3t_0      =>  e3t_crs         !: vertical scale factors at t- 
     105   USE crs , ONLY :   fse3t      =>  e3t_crs 
     106   USE crs , ONLY :   fse3t_b      =>  e3t_crs 
     107   USE crs , ONLY :   fse3t_a      =>  e3t_crs 
     108   USE crs , ONLY :   fse3w      =>  e3w_crs 
     109   USE crs , ONLY :   e3u        =>  e3u_crs         !: vertical scale factors at u- 
     110   USE crs , ONLY :   e3u_0      =>  e3u_crs         !: vertical scale factors at u- 
     111   USE crs , ONLY :   e3v        =>  e3v_crs         !: vertical scale factors v- 
     112   USE crs , ONLY :   e3v_0      =>  e3v_crs         !: vertical scale factors v- 
     113   USE crs , ONLY :   e3w        =>  e3w_crs         !: w-points (m) 
     114   USE crs , ONLY :   e3w_0      =>  e3w_crs         !: w-points (m) 
     115   USE crs , ONLY :   e3f        =>  e3f_crs         !: f-points (m) 
     116   USE crs , ONLY :   ff         =>  ff_crs         !: f-points (m) 
     117 
     118   USE crs , ONLY :   gdept_0    =>  gdept_crs       !: depth of t-points (m) 
     119   USE dom_oce , ONLY :   gdept_1d   =>  gdept_1d      !: depth of t-points (m) 
     120#if defined key_zco 
     121   USE crs , ONLY :   gdept      =>  gdept_crs       !: depth of t-points (m) 
     122   USE crs , ONLY :   gdepw      =>  gdepw_crs       !: depth of t-points (m) 
     123#endif 
     124  !* masks, bathymetry * 
     125   USE crs , ONLY :   mbkt       =>   mbkt_crs       !: vertical index of the bottom last T- ocean level 
     126   USE crs , ONLY :   mbku       =>   mbku_crs       !: vertical index of the bottom last U- ocean level 
     127   USE crs , ONLY :   mbkv       =>   mbkv_crs       !: vertical index of the bottom last V- ocean level 
     128   USE crs , ONLY :   tmask_i    =>   tmask_i_crs    !: Interior mask at t-points 
     129   USE crs , ONLY :   tmask      =>   tmask_crs      !: land/ocean mask at t-points 
     130   USE crs , ONLY :   umask      =>   umask_crs      !: land/ocean mask at u-points    
     131   USE crs , ONLY :   vmask      =>   vmask_crs      !: land/ocean mask at v-points  
     132   USE crs , ONLY :   fmask      =>   fmask_crs      !: land/ocean mask at f-points  
     133 
     134 !* ocean fields: here now and after fields * 
     135!cbr?   USE crs , ONLY :   ua      =>    ua_crs      !: i-horizontal velocity (m s-1)  
     136!cbr?   USE crs , ONLY :   va      =>    va_crs      !: j-horizontal velocity (m s-1) 
     137   USE crs , ONLY :   un      =>    un_crs      !: i-horizontal velocity (m s-1)  
     138   USE crs , ONLY :   vn      =>    vn_crs      !: j-horizontal velocity (m s-1) 
     139   USE crs , ONLY :   wn      =>    wn_crs      !: vertical velocity (m s-1)   
     140   USE crs , ONLY :   tsn     =>    tsn_crs     !: 4D array contaning ( tn, sn ) 
     141   USE oce , ONLY :   tsb     =>    tsb     !: 4D array contaning ( tb, sb ) 
     142   USE oce , ONLY :   tsa     =>    tsa     !: 4D array contaning ( ta, sa ) 
     143   USE oce , ONLY :   rhop    =>    rhop    !: potential volumic mass (kg m-3)  
     144   USE oce , ONLY :   rhd     =>    rhd     !: in situ density anomalie rhd=(rho-rau0)/rau0 (no units) 
     145   USE crs , ONLY :   hdivn   =>    hdivn_crs   !: horizontal divergence (1/s) 
     146   USE crs , ONLY :   hdivb   =>    hdivb_crs   !: horizontal divergence (1/s) 
     147   USE crs , ONLY :   sshb    =>    sshb_crs    !: sea surface height at t-point [m]    
     148   USE crs , ONLY :   sshn    =>    sshn_crs    !: sea surface height at t-point [m]    
     149   USE crs , ONLY :   ssha    =>    ssha_crs    !: sea surface height at t-point [m]    
     150 
     151   !* surface fluxes * 
     152   USE crs , ONLY :   utau       =>    utau_crs       !: i-surface stress component 
     153   USE crs , ONLY :   vtau       =>    vtau_crs       !: j-surface stress component 
     154   USE crs , ONLY :   wndm       =>    wndm_crs       !: 10m wind speed  
     155   USE crs , ONLY :   qsr        =>    qsr_crs        !: penetrative solar radiation (w m-2)   
     156   USE crs , ONLY :   emp        =>    emp_crs        !: freshwater budget: volume flux               [Kg/m2/s] 
     157   USE crs , ONLY :   emp_b      =>    emp_b_crs      !: freshwater budget: volume flux               [Kg/m2/s] 
     158   USE crs , ONLY :   sfx        =>    sfx_crs        !: freshwater budget: concentration/dillution   [Kg/m2/s] 
     159   USE crs , ONLY :   fmmflx     =>    fmmflx_crs     !: freshwater budget: volume flux               [Kg/m2/s] 
     160   USE crs , ONLY :   rnf        =>    rnf_crs        !: river runoff   [Kg/m2/s] 
     161   USE crs , ONLY :   fr_i       =>    fr_i_crs       !: ice fraction (between 0 to 1) 
     162 
     163   USE crs , ONLY :   avt        =>   avt_crs         !: vert. diffusivity coef. at w-point for temp   
     164#if defined key_zdfddm 
     165   USE crs , ONLY :   avs        =>   avs_crs         !: salinity vertical diffusivity coeff. at w-point 
     166#endif 
     167 
     168!cbr   USE trc_oce 
     169   USE trc_oce, ONLY : lk_offline 
     170   USE trc_oce, ONLY : nn_dttrc 
     171 
     172   USE crs , ONLY :   nmln        =>   nmln_crs        !: number of level in the mixed layer 
     173   USE crs , ONLY :   hmld        =>   hmld_crs        !: mixing layer depth (turbocline) 
     174   USE crs , ONLY :   hmlp        =>   hmlp_crs        !: mixed layer depth  (rho=rho0+zdcrit) (m) 
     175   USE crs , ONLY :   hmlpt       =>   hmlpt_crs       !: mixed layer depth at t-points (m) 
     176 
     177  !* direction of lateral diffusion * 
     178#if   defined key_ldfslp 
     179   USE ldfslp_crs , ONLY :   uslp       =>   uslp_crs         !: i-direction slope at u-, w-points 
     180   USE ldfslp_crs , ONLY :   vslp       =>   vslp_crs         !: j-direction slope at v-, w-points 
     181   USE ldfslp_crs , ONLY :   wslpi      =>   wslpi_crs        !: i-direction slope at u-, w-points 
     182   USE ldfslp_crs , ONLY :   wslpj      =>   wslpj_crs        !: j-direction slope at v-, w-points 
     183#endif 
     184 
     185#else 
     186 
    10187   !!---------------------------------------------------------------------- 
    11188   !!   'key_top'                                                TOP models 
     
    24201   USE par_oce , ONLY :   jp_sal   =>   jp_sal     !: indice for salinity 
    25202 
     203  !* model domain * 
     204   USE dom_oce , ONLY : narea => narea 
     205   USE dom_oce , ONLY : nproc => nproc 
     206   USE dom_oce , ONLY : nimpp => nimpp 
     207   USE dom_oce , ONLY : njmpp => njmpp 
     208   USE dom_oce , ONLY : nreci => nreci 
     209   USE dom_oce , ONLY : nrecj => nrecj 
     210   USE dom_oce , ONLY : nlci  => nlci 
     211   USE dom_oce , ONLY : nldi  => nldi 
     212   USE dom_oce , ONLY : nlei  => nlei 
     213   USE dom_oce , ONLY : nlcj  => nlcj 
     214   USE dom_oce , ONLY : nldj  => nldj 
     215   USE dom_oce , ONLY : nlej  => nlej 
     216   USE dom_oce , ONLY : nlcit  => nlcit 
     217   USE dom_oce , ONLY : nldit  => nldit 
     218   USE dom_oce , ONLY : nleit  => nleit 
     219   USE dom_oce , ONLY : nlcjt  => nlcjt 
     220   USE dom_oce , ONLY : nldjt  => nldjt 
     221   USE dom_oce , ONLY : nlejt  => nlejt 
     222   USE dom_oce , ONLY : nimppt => nimppt 
     223   USE dom_oce , ONLY : njmppt => njmppt 
     224   USE dom_oce , ONLY : ibonit => ibonit 
     225   USE dom_oce , ONLY : ibonjt => ibonjt 
     226   USE dom_oce , ONLY : lk_vvl => lk_vvl 
     227   USE dom_oce , ONLY : rdt => rdt 
     228   USE dom_oce , ONLY : ln_zco => ln_zco 
     229   USE dom_oce , ONLY : ln_zps => ln_zps 
     230   USE dom_oce , ONLY : ln_sco => ln_sco 
     231   USE dom_oce , ONLY : neuler => neuler 
     232 
     233   USE dom_oce,  ONLY : mi0 => mi0 
     234   USE dom_oce,  ONLY : mi1 => mi1 
     235   USE dom_oce,  ONLY : mj0 => mj0 
     236   USE dom_oce,  ONLY : mj1 => mj1 
     237 
     238   USE dom_oce , ONLY :   glamt      =>   glamt      !: longitude of t-point (degre)   
     239   USE dom_oce , ONLY :   glamu      =>   glamu      !: longitude of t-point (degre)   
     240   USE dom_oce , ONLY :   glamv      =>   glamv      !: longitude of t-point (degre)   
     241   USE dom_oce , ONLY :   glamf      =>   glamf      !: longitude of t-point (degre)   
     242   USE dom_oce , ONLY :   gphit      =>   gphit      !: latitude  of t-point (degre)    
     243   USE dom_oce , ONLY :   gphiu      =>   gphiu      !: latitude  of t-point (degre)    
     244   USE dom_oce , ONLY :   gphiv      =>   gphiv      !: latitude  of t-point (degre)    
     245   USE dom_oce , ONLY :   gphif      =>   gphif     !: latitude  of t-point (degre)    
     246   USE dom_oce , ONLY :   e1t        =>   e1t        !: horizontal scale factors at t-point (m)   
     247   USE dom_oce , ONLY :   e2t        =>   e2t        !: horizontal scale factors at t-point (m)    
     248   USE dom_oce , ONLY :   e1e2t      =>   e1e2t      !: cell surface at t-point (m2) 
     249   USE dom_oce , ONLY :   e1u        =>   e1u        !: horizontal scale factors at u-point (m) 
     250   USE dom_oce , ONLY :   e2u        =>   e2u        !: horizontal scale factors at u-point (m) 
     251   USE dom_oce , ONLY :   e1v        =>   e1v        !: horizontal scale factors at v-point (m) 
     252   USE dom_oce , ONLY :   e2v        =>   e2v        !: horizontal scale factors at v-point (m)   
     253   USE dom_oce , ONLY :   e3t        =>  e3t_0         !: vertical scale factors at t- 
     254   USE dom_oce , ONLY :   e3t_0      =>  e3t_0         !: vertical scale factors at t- 
     255   USE dom_oce , ONLY :   fse3t      =>  e3t_0 
     256   USE dom_oce , ONLY :   fse3t_b      =>  e3t_0 
     257   USE dom_oce , ONLY :   fse3t_a      =>  e3t_0 
     258   USE dom_oce , ONLY :   fse3w      =>  e3w_0 
     259   USE dom_oce , ONLY :   e3u        =>  e3u_0         !: vertical scale factors at u- 
     260   USE dom_oce , ONLY :   e3u_0      =>  e3u_0         !: vertical scale factors at u- 
     261   USE dom_oce , ONLY :   e3v        =>  e3v_0         !: vertical scale factors v- 
     262   USE dom_oce , ONLY :   e3v_0      =>  e3v_0         !: vertical scale factors v- 
     263   USE dom_oce , ONLY :   e3w        =>  e3w_0         !: w-points (m) 
     264   USE dom_oce , ONLY :   e3w_0      =>  e3w_0         !: w-points (m) 
     265   USE dom_oce , ONLY :   e3f        =>  e3f_0         !: f-points (m) 
     266   USE dom_oce , ONLY :   ff         =>  ff         !: f-points (m) 
     267   USE dom_oce , ONLY :   gdept_0    =>  gdept_0         !: f-points (m) 
     268   USE dom_oce , ONLY :   gdept_1d   => gdept_1d          !: f-points (m) 
     269   USE dom_oce , ONLY :   tmask      => tmask          !: f-points (m) 
     270   USE dom_oce , ONLY :   umask      => umask          !: f-points (m) 
     271   USE dom_oce , ONLY :   vmask      => vmask          !: f-points (m) 
     272   USE dom_oce , ONLY :   tmask_i      => tmask_i          !: f-points (m) 
     273   USE dom_oce , ONLY :   mbkt      => mbkt          !: f-points (m) 
     274   USE dom_oce , ONLY :   mbku      => mbku          !: f-points (m) 
     275   USE dom_oce , ONLY :   mbkv      => mbkv          !: f-points (m) 
     276 
    26277   !* IO manager * 
    27278   USE in_out_manager     
     
    49300 
    50301   !* model domain * 
    51    USE dom_oce  
     302   !cbr USE dom_oce , ONLY : e3w_0 
     303   USE dom_oce , ONLY :  lzoom => lzoom  
    52304 
    53305   USE domvvl, ONLY : un_td, vn_td          !: thickness diffusion transport 
     
    66318   USE oce , ONLY :   rhop    =>    rhop    !: potential volumic mass (kg m-3)  
    67319   USE oce , ONLY :   rhd     =>    rhd     !: in situ density anomalie rhd=(rho-rau0)/rau0 (no units) 
    68 #if defined key_offline 
    69    USE oce , ONLY :   rab_n   =>    rab_n   !: local thermal/haline expension ratio at T-points 
    70 #endif 
    71320   USE oce , ONLY :   hdivn   =>    hdivn   !: horizontal divergence (1/s) 
    72321   USE oce , ONLY :   rotn    =>    rotn    !: relative vorticity    [s-1] 
     
    135384# endif 
    136385 
     386#endif 
    137387#else 
    138388   !!---------------------------------------------------------------------- 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcdia.F90

    r4292 r5105  
    2020   !! trcdib_wr   : outputs of biological fields 
    2121   !!---------------------------------------------------------------------- 
    22    USE dom_oce         ! ocean space and time domain variables  
    23    USE oce_trc 
     22   USE trc_oce, ONLY : lk_offline ! offline flag 
    2423   USE trc 
    2524   USE par_trc 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcdta.F90

    r4624 r5105  
    1919   USE oce_trc       !  shared variables between ocean and passive tracers 
    2020   USE trc           !  passive tracers common variables 
    21    USE iom           !  I/O manager 
    2221   USE lib_mpp       !  MPP library 
    2322   USE fldread       !  read input fields 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r4990 r5105  
    2525   USE trcini_my_trc   ! MY_TRC   initialisation 
    2626   USE trcdta          ! initialisation from files 
    27    USE daymod          ! calendar manager 
    28    USE zpshde          ! partial step: hor. derivative   (zps_hde routine) 
     27   USE zpshde,ONLY: zps_hde    ! partial step: hor. derivative   (zps_hde routine) 
     28   USE zpshde_crs      ! partial step: hor. derivative   (zps_hde routine) 
    2929   USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine) 
    3030   USE trcsub          ! variables to substep passive tracers 
    3131   USE lib_mpp         ! distribued memory computing library 
    32    USE sbc_oce 
     32   USE sbc_oce, ONLY : ltrcdm2dc 
     33   USE crs    , ONLY : ln_crs 
     34   USE dom_oce, ONLY : nn_cla 
    3335  
    3436   IMPLICIT NONE 
     
    143145  
    144146      tra(:,:,:,:) = 0._wp 
    145       IF( ln_zps .AND. .NOT. lk_c1d )   &              ! Partial steps: before horizontal gradient of passive 
    146         &    CALL zps_hde( nit000, jptra, trn, pgtu=gtru, pgtv=gtrv, sgtu=gtrui, sgtv=gtrvi )       ! tracers at the bottom ocean level 
    147  
     147      IF( ln_zps .AND. .NOT. lk_c1d )THEN              ! Partial steps: before horizontal gradient of passive 
     148         IF( ln_crs )  THEN 
     149            CALL zps_hde_crs( nit000, jptra, trn, gtru, gtrv ) 
     150         ELSE 
     151            CALL zps_hde( nit000, jptra, trn, pgtu=gtru, pgtv=gtrv, sgtu=gtrui, sgtv=gtrvi )! tracers at the bottom ocean level 
     152         ENDIF 
     153      ENDIF 
    148154      ! 
    149155      IF( nn_dttrc /= 1 )        CALL trc_sub_ini      ! Initialize variables for substepping passive tracers 
     
    188194      !!---------------------------------------------------------------------- 
    189195      USE trcadv        , ONLY:   trc_adv_alloc          ! TOP-related alloc routines... 
     196      USE trcadv_crs    , ONLY:   trc_adv_alloc_crs      ! TOP-related alloc routines.. 
    190197      USE trc           , ONLY:   trc_alloc 
    191198      USE trcnxt        , ONLY:   trc_nxt_alloc 
    192199      USE trczdf        , ONLY:   trc_zdf_alloc 
     200      USE trczdf_crs    , ONLY:   trc_zdf_alloc_crs 
    193201      USE trdtrc_oce    , ONLY:   trd_trc_oce_alloc 
    194202#if defined key_trdmxl_trc  
     
    200208      ! 
    201209      ierr =        trc_adv_alloc()          ! Start of TOP-related alloc routines... 
     210      ierr = ierr + trc_adv_alloc_crs() 
    202211      ierr = ierr + trc_alloc    () 
    203212      ierr = ierr + trc_nxt_alloc() 
    204213      ierr = ierr + trc_zdf_alloc() 
     214      ierr = ierr + trc_zdf_alloc_crs() 
    205215      ierr = ierr + trd_trc_oce_alloc() 
    206216#if defined key_trdmxl_trc  
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcrst.F90

    r4990 r5105  
    2323   !!   trc_rst_wri    : write restart file 
    2424   !!---------------------------------------------------------------------- 
    25    USE oce_trc 
     25   USE oce_trc ! ,ONLY: jprstlib 
    2626   USE trc 
    2727   USE trcnam_trp 
    28    USE iom 
    29    USE daymod 
     28   USE iom_def , ONLY : jprstlib , jprstdimg , jpnf90 , jpdom_autoglo  
     29   USE iom , ONLY : iom_open , iom_get , iom_varid , iom_rstput , iom_close 
     30   USE dom_oce, ONLY: ndastp ,adatrj  , rdttra 
     31   USE daymod , ONLY : day_init 
     32 
    3033   IMPLICIT NONE 
    3134   PRIVATE 
     
    137140          CALL trc_rst_stat            ! statistics 
    138141          CALL iom_close( numrtw )     ! close the restart file (only at last time step) 
    139 #if ! defined key_trdmxl_trc 
     142#if ! defined key_trdmld_trc 
    140143          lrst_trc = .FALSE. 
    141144#endif 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcstp.F90

    r4990 r5105  
    1111   !!---------------------------------------------------------------------- 
    1212   USE oce_trc          ! ocean dynamics and active tracers variables 
    13    USE sbc_oce 
     13   USE sbc_oce , ONLY : ltrcdm2dc,qsr_mean 
    1414   USE trc 
    1515   USE trctrp           ! passive tracers transport 
     
    1717   USE prtctl_trc       ! Print control for debbuging 
    1818   USE trcdia 
    19    USE trcwri 
     19   USE trcwri , ONLY : trc_wri 
    2020   USE trcrst 
    2121   USE trdtrc_oce 
    2222   USE trdmxl_trc 
    23    USE iom 
     23   USE iom, ONLY : lk_iomput , iom_close 
    2424   USE in_out_manager 
    2525   USE trcsub 
     26   USE dom_oce, ONLY : nday, nmonth, nyear 
    2627 
    2728   IMPLICIT NONE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcsub.F90

    r4611 r5105  
    1313   USE trc 
    1414   USE prtctl_trc       ! Print control for debbuging 
    15    USE iom 
    16    USE in_out_manager 
     15   USE iom, ONLY : jpnf90 
     16   USE in_out_manager, ONLY : jprstlib 
    1717   USE lbclnk 
    18 #if defined key_zdftke 
    19    USE zdftke          ! twice TKE (en) 
    20 #endif 
     18!#if defined key_zdftke 
     19!   USE zdftke          ! twice TKE (en) 
     20!#endif 
    2121#if defined key_zdfgls 
    2222   USE zdfgls, ONLY: en 
    2323#endif 
    24    USE trabbl 
    25    USE zdf_oce 
    26    USE domvvl 
    27    USE divcur          ! hor. divergence and curl      (div & cur routines) 
     24!   USE trabbl 
     25!   USE zdf_oce 
     26!   USE domvvl 
     27   USE divcur, ONLY : div_cur           ! hor. divergence and curl      (div & cur routines) 
    2828   USE sbcrnf, ONLY: h_rnf, nk_rnf   ! River runoff  
    2929   USE bdy_oce 
     
    160160         wndm_temp  (:,:)        = wndm  (:,:) 
    161161         !                                    !  Variables reset in trc_sub_ssh 
     162#if ! defined key_crs 
    162163         rotn_temp  (:,:,:)      = rotn  (:,:,:) 
     164# endif 
    163165         hdivn_temp (:,:,:)      = hdivn (:,:,:) 
     166#if ! defined key_crs 
    164167         rotb_temp  (:,:,:)      = rotb  (:,:,:) 
     168# endif 
    165169         hdivb_temp (:,:,:)      = hdivb (:,:,:) 
    166170         ! 
     
    396400      ! 
    397401      hdivn (:,:,:)   =  hdivn_temp (:,:,:) 
     402      hdivb (:,:,:)   =  hdivb_temp (:,:,:) 
     403#if ! defined key_crs 
    398404      rotn  (:,:,:)   =  rotn_temp  (:,:,:) 
    399       hdivb (:,:,:)   =  hdivb_temp (:,:,:) 
    400405      rotb  (:,:,:)   =  rotb_temp  (:,:,:) 
     406#endif 
    401407      !                                       
    402408 
Note: See TracChangeset for help on using the changeset viewer.