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 439 – NEMO

Changeset 439


Ignore:
Timestamp:
2006-04-11T15:52:28+02:00 (18 years ago)
Author:
opalod
Message:

nemo_v1_update_045 : CT : modifications to be able to run 1D on-line & off-line passive tracers configurations

Location:
trunk/NEMO
Files:
1 deleted
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/C1D_SRC/step1d.F90

    r321 r439  
    3232   USE ocfzpt          ! surface ocean freezing point    (oc_fz_pt routine) 
    3333 
     34   USE trcstp          ! passive tracer time-stepping     (trc_stp routine) 
    3435 
    3536   USE dynzdf_imp      ! vertical diffusion: implicit     (dyn_zdf routine) 
     
    202203 
    203204 
     205#if defined key_passivetrc 
     206      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     207      ! Passive Tracer Model 
     208      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     209      ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
     210      !----------------------------------------------------------------------- 
     211 
     212                               CALL trc_stp( kstp, indic )            ! time-stepping 
     213 
     214#endif 
    204215 
    205216 
  • trunk/NEMO/OFF_SRC/DOM/domrea.F90

    r382 r439  
    9393      REAL(wp) ::   zdate0, zdt 
    9494      REAL(wp), DIMENSION(jpidta,jpjdta) ::   & 
    95          zta       ! dummy array for bathymetry  
     95         zta, zlamt, zphit       ! dummy array for bathymetry  
    9696      REAL(wp) , DIMENSION(jpidta,jpjdta,jpk) :: & 
    9797         zt3a      ! dummy array for bathymetry  
     
    112112 
    113113      llog  = .FALSE. 
     114      zlamt(:,:) = 0.e0 
     115      zphit(:,:) = 0.e0 
    114116 
    115117      CALL ymds2ju( 0, 1, 1, 0.e0, zdate0 )    ! calendar initialization 
     
    127129 
    128130            IF(lwp) WRITE(numout,*) '          one file in "mesh_mask.nc" ' 
    129             CALL restini( clnam0, jpidta   , jpjdta   , glamt, gphit,  &   ! create 'mesh_mask.nc' file 
     131            CALL restini( clnam0, jpidta   , jpjdta   , zlamt, zphit,  &   ! create 'mesh_mask.nc' file 
    130132            &             jpk   , gdept , trim(clnam0)        ,  &   ! in unit inum0 
    131133            &             itime , zdate0, zdt   , inum0, domain_id=nidom ) 
     
    140142 
    141143            IF(lwp) WRITE(numout,*) '          two files in "mesh.nc" and "mask.nc" ' 
    142             CALL restini( clnam1, jpidta   , jpjdta   , glamt, gphit,  &   ! create 'mesh.nc' file  
     144            CALL restini( clnam1, jpidta   , jpjdta   , zlamt, zphit,  &   ! create 'mesh.nc' file  
    143145            &             jpk   , gdept , trim(clnam1)        ,  &   ! in unit inum1  
    144146            &             itime , zdate0, zdt   , inum1, domain_id=nidom ) 
    145             CALL restini( clnam2, jpidta   , jpjdta   , glamt, gphit,  &   ! create 'mask.nc' file  
     147            CALL restini( clnam2, jpidta   , jpjdta   , zlamt, zphit,  &   ! create 'mask.nc' file  
    146148            &             jpk   , gdept , trim(clnam2)        ,  &   ! in unit inum2  
    147149            &             itime , zdate0, zdt   , inum2, domain_id=nidom ) 
     
    156158 
    157159            IF(lwp) WRITE(numout,*) '          three files in "mesh_hgr.nc" , mesh_zgr.nc" and "mask.nc" ' 
    158             CALL restini( clnam3, jpidta   , jpjdta   , glamt, gphit,  &   ! create 'mesh_hgr.nc' file 
     160            CALL restini( clnam3, jpidta   , jpjdta   , zlamt, zphit,  &   ! create 'mesh_hgr.nc' file 
    159161            &             jpk   , gdept , trim(clnam3)        ,  &   ! in unit inum3 
    160162            &             itime , zdate0, zdt   , inum3, domain_id=nidom ) 
    161             CALL restini( clnam4, jpidta   , jpjdta   , glamt, gphit,  &   ! create 'mesh_zgr.nc' file 
     163            CALL restini( clnam4, jpidta   , jpjdta   , zlamt, zphit,  &   ! create 'mesh_zgr.nc' file 
    162164            &             jpk   , gdept , trim(clnam4)        ,  &   ! in unit inum4 
    163165            &             itime , zdate0, zdt   , inum4, domain_id=nidom ) 
    164             CALL restini( clnam2, jpidta   , jpjdta   , glamt, gphit,  &   ! create 'mask.nc' file 
     166            CALL restini( clnam2, jpidta   , jpjdta   , zlamt, zphit,  &   ! create 'mask.nc' file 
    165167            &             jpk   , gdept , trim(clnam2)        ,  &   ! in unit inum2 
    166168            &             itime , zdate0, zdt   , inum2, domain_id=nidom ) 
     
    201203           END DO 
    202204         END DO 
     205 
     206#if defined key_cfg_1d 
     207      IF(lwp) WRITE(numout,*) '**********  1D configuration : set umask and vmask equal tmask ********' 
     208      IF(lwp) WRITE(numout,*) '**********                                                     ********' 
     209      ! set umask and vmask equal tmask in 1D configuration 
     210      umask(:,:,:) = tmask(:,:,:) 
     211      vmask(:,:,:) = tmask(:,:,:) 
     212#endif 
    203213 
    204214#if defined key_off_degrad 
  • trunk/NEMO/TOP_SRC/TRP/trcbbl.F90

    r433 r439  
    55   !!                                  layer scheme 
    66   !!============================================================================== 
    7 #if  defined key_passivetrc && ( defined key_trcbbl_dif   ||   defined key_trcbbl_adv ) 
     7#if  defined key_passivetrc && ( defined key_trcbbl_dif   ||   defined key_trcbbl_adv ) && ! defined key_cfg_1d 
    88   !!---------------------------------------------------------------------- 
    99   !!   'key_trcbbl_dif'   or            diffusive bottom boundary layer 
  • trunk/NEMO/TOP_SRC/TRP/trcstp.F90

    r433 r439  
    1212   USE trc              ! ocean passive tracers variables  
    1313   USE trctrp           ! passive tracers transport 
    14    USE trctrp1d         ! passive tracers transport 1D configuration 
    1514   USE trcsms           ! passive tracers sources and sinks 
    1615   USE prtctl_trc       ! Print control for debbuging 
     
    1817   USE trcdit 
    1918   USE trcrst 
    20    USE ini1d 
    2119 
    2220   IMPLICIT NONE 
     
    7068 
    7169      ! transport of passive tracers 
    72       IF( lk_cfg_1d  )  THEN 
    73          CALL trc_trp_1d( kt )    
    74       ELSE 
    75          CALL trc_trp( kt ) 
    76       ENDIF 
    77  
     70      CALL trc_trp( kt ) 
    7871 
    7972      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
  • trunk/NEMO/TOP_SRC/TRP/trctrp.F90

    r433 r439  
    128128      !                                                       
    129129 
    130        IF( lk_zps           )   CALL zps_hde_trc( kt, trb, gtru, gtrv )  ! Partial steps: now horizontal gradient 
     130      IF( lk_zps .AND. .NOT. lk_trccfg_1d ) & 
     131         &                     CALL zps_hde_trc( kt, trb, gtru, gtrv )  ! Partial steps: now horizontal gradient 
    131132      !                                                                 ! of passive tracers at the bottom ocean level 
    132133 
  • trunk/NEMO/TOP_SRC/TRP/trctrp_ctl.F90

    r349 r439  
    125125         IF(lwp) WRITE(numout,*) '     cross-land advection only with 2nd order advection scheme' 
    126126         nstop = nstop + 1 
     127      ENDIF 
     128 
     129      IF( lk_trccfg_1d ) THEN 
     130         ln_trcadv_cen2   = .FALSE.    ;  ln_trcadv_tvd    = .FALSE. ; ln_trcadv_muscl  = .FALSE. 
     131         ln_trcadv_muscl2 = .FALSE.    ;  ln_trcadv_smolar = .FALSE. 
     132         IF(lwp) WRITE(numout,*) ' *******  1D configuration : No advection on passive tracers *******' 
     133         IF(lwp) WRITE(numout,*) ' *******                                                     *******' 
    127134      ENDIF 
    128135 
     
    236243      ENDIF 
    237244 
    238       IF( .NOT. ln_trcldf_diff ) THEN 
     245      IF( .NOT. ln_trcldf_diff .OR. lk_trccfg_1d ) THEN 
    239246         l_trcldf_lap = .FALSE.   ;   l_trcldf_bilap   = .FALSE.   ;   l_trcldf_bilapg  = .FALSE. 
    240247         l_trcldf_iso = .FALSE.   ;   l_trcldf_iso_zps = .FALSE. 
    241248         l_trczdf_iso = .FALSE.   ;   l_trczdf_iso_vo  = .FALSE. 
    242          IF(lwp ) WRITE(numout,*) '          No lateral physics on passive tracers' 
     249         IF(lwp ) WRITE(numout,*) '************* No lateral physics on passive tracers *****************' 
     250         IF(lwp ) WRITE(numout,*) '*************                                       *****************' 
    243251      ELSE 
    244252         ! ... Space variation of eddy coefficients 
  • trunk/NEMO/TOP_SRC/trc.F90

    r433 r439  
    198198#endif 
    199199 
     200  !!  1D configuration 
     201  !! -------------------------------------------------- 
     202#if defined key_cfg_1d 
     203      LOGICAL, PARAMETER ::   lk_trccfg_1d   = .TRUE.   !: 1D pass. tracer configuration flag 
     204#else    
     205      LOGICAL, PARAMETER ::   lk_trccfg_1d   = .FALSE.  !: 1D pass. tracer configuration flag 
     206#endif 
     207 
     208 
    200209#else 
    201210   !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.