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

Changeset 2517


Ignore:
Timestamp:
2010-12-23T17:34:46+01:00 (13 years ago)
Author:
cetlod
Message:

v3.3beta:Ensure restartability of ORCA2_OFF_PISCES & define lk_offline flag for OFFLINE mode

Location:
branches/nemo_v3_3_beta/NEMOGCM/NEMO
Files:
20 edited

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OFF_SRC/dtadyn.F90

    r2445 r2517  
    3636   USE iom             ! I/O library 
    3737   USE lib_mpp         ! distributed memory computing library 
     38   USE prtctl          !  print control 
    3839 
    3940   IMPLICIT NONE 
     
    6263   INTEGER ::   numfl_t, numfl_u, numfl_v, numfl_w 
    6364 
    64    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   tdta       ! temperature at two consecutive times 
    65    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   sdta       ! salinity at two consecutive times 
    66    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   udta       ! zonal velocity at two consecutive times 
    67    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   vdta       ! meridional velocity at two consecutive times 
    68    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   wdta       ! vertical velocity at two consecutive times 
    69    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   avtdta     ! vertical diffusivity coefficient 
    70  
    71    REAL(wp), DIMENSION(jpi,jpj    ,2) ::   hmlddta    ! mixed layer depth at two consecutive times 
    72    REAL(wp), DIMENSION(jpi,jpj    ,2) ::   wspddta    ! wind speed at two consecutive times 
    73    REAL(wp), DIMENSION(jpi,jpj    ,2) ::   frlddta    ! sea-ice fraction at two consecutive times 
    74    REAL(wp), DIMENSION(jpi,jpj    ,2) ::   empdta     ! E-P at two consecutive times 
    75    REAL(wp), DIMENSION(jpi,jpj    ,2) ::   qsrdta     ! short wave heat flux at two consecutive times 
     65   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: tdta       ! temperature at two consecutive times 
     66   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: sdta       ! salinity at two consecutive times 
     67   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: udta       ! zonal velocity at two consecutive times 
     68   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: vdta       ! meridional velocity at two consecutive times 
     69   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: wdta       ! vertical velocity at two consecutive times 
     70   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: avtdta     ! vertical diffusivity coefficient 
     71 
     72   REAL(wp), DIMENSION(jpi,jpj    ,2) :: hmlddta    ! mixed layer depth at two consecutive times 
     73   REAL(wp), DIMENSION(jpi,jpj    ,2) :: wspddta    ! wind speed at two consecutive times 
     74   REAL(wp), DIMENSION(jpi,jpj    ,2) :: frlddta    ! sea-ice fraction at two consecutive times 
     75   REAL(wp), DIMENSION(jpi,jpj    ,2) :: empdta     ! E-P at two consecutive times 
     76   REAL(wp), DIMENSION(jpi,jpj    ,2) :: qsrdta     ! short wave heat flux at two consecutive times 
     77   REAL(wp), DIMENSION(jpi,jpj    ,2) :: bblxdta    ! frequency of bbl in the x direction at 2 consecutive times  
     78   REAL(wp), DIMENSION(jpi,jpj    ,2) :: bblydta    ! frequency of bbl in the y direction at 2 consecutive times  
     79   LOGICAL :: l_offbbl 
    7680#if defined key_ldfslp 
    77    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   uslpdta    ! zonal isopycnal slopes 
    78    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   vslpdta    ! meridional isopycnal slopes 
    79    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   wslpidta   ! zonal diapycnal slopes 
    80    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   wslpjdta   ! meridional diapycnal slopes 
     81   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: uslpdta    ! zonal isopycnal slopes 
     82   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: vslpdta    ! meridional isopycnal slopes 
     83   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: wslpidta   ! zonal diapycnal slopes 
     84   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: wslpjdta   ! meridional diapycnal slopes 
    8185#endif 
    8286#if ! defined key_degrad &&  defined key_traldf_c2d && defined key_traldf_eiv  
    83    REAL(wp), DIMENSION(jpi,jpj    ,2) ::   aeiwdta    ! G&M coefficient 
     87   REAL(wp), DIMENSION(jpi,jpj    ,2) :: aeiwdta    ! G&M coefficient 
    8488#endif 
    8589#if defined key_degrad 
    86    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   ahtudta, ahtvdta, ahtwdta   ! Lateral diffusivity 
     90   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: ahtudta, ahtvdta, ahtwdta   ! Lateral diffusivity 
    8791# if defined key_traldf_eiv 
    88    REAL(wp), DIMENSION(jpi,jpj,jpk,2) ::   aeiudta, aeivdta, aeiwdta   ! G&M coefficient 
     92   REAL(wp), DIMENSION(jpi,jpj,jpk,2) :: aeiudta, aeivdta, aeiwdta   ! G&M coefficient 
    8993# endif 
    9094#endif 
     
    272276#endif 
    273277      ! 
    274       IF( lk_trabbl .AND. .NOT. lk_c1d ) THEN       ! Compute bbl coefficients if needed 
     278      IF( .NOT. l_offbbl ) THEN       ! Compute bbl coefficients if needed 
    275279         tsb(:,:,:,:) = tsn(:,:,:,:) 
    276280         CALL bbl( kt, 'TRC') 
    277281      END IF 
     282      IF(ln_ctl) THEN 
     283         CALL prt_ctl(tab3d_1=tsn(:,:,:,jp_tem), clinfo1=' tn      - : ', mask1=tmask, ovlap=1, kdim=jpk   ) 
     284         CALL prt_ctl(tab3d_1=tsn(:,:,:,jp_sal), clinfo1=' sn      - : ', mask1=tmask, ovlap=1, kdim=jpk   ) 
     285         CALL prt_ctl(tab3d_1=un               , clinfo1=' un      - : ', mask1=tmask, ovlap=1, kdim=jpk   ) 
     286         CALL prt_ctl(tab3d_1=vn               , clinfo1=' vn      - : ', mask1=tmask, ovlap=1, kdim=jpk   ) 
     287         CALL prt_ctl(tab3d_1=wn               , clinfo1=' wn      - : ', mask1=tmask, ovlap=1, kdim=jpk   ) 
     288         CALL prt_ctl(tab3d_1=avt              , clinfo1=' kz      - : ', mask1=tmask, ovlap=1, kdim=jpk   ) 
     289         CALL prt_ctl(tab2d_1=fr_i             , clinfo1=' fr_i    - : ', mask1=tmask, ovlap=1 ) 
     290         CALL prt_ctl(tab2d_1=hmld             , clinfo1=' hmld    - : ', mask1=tmask, ovlap=1 ) 
     291         CALL prt_ctl(tab2d_1=emps             , clinfo1=' emps    - : ', mask1=tmask, ovlap=1 ) 
     292         CALL prt_ctl(tab2d_1=wndm             , clinfo1=' wspd    - : ', mask1=tmask, ovlap=1 ) 
     293         CALL prt_ctl(tab2d_1=qsr              , clinfo1=' qsr     - : ', mask1=tmask, ovlap=1 ) 
     294      ENDIF 
    278295      ! 
    279296   END SUBROUTINE dta_dyn 
     
    291308      !! 
    292309      INTEGER ::  jkenr 
    293       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zu, zv, zw, zt, zs, zavt , zhdiv              ! 3D workspace 
    294       REAL(wp), DIMENSION(jpi,jpj)     ::   zemp, zqsr, zmld, zice, zwspd, ztaux, ztauy   ! 2D workspace 
     310      REAL(wp), DIMENSION(jpi,jpj,jpk) ::  zu, zv, zw, zt, zs, zavt , zhdiv              ! 3D workspace 
     311      REAL(wp), DIMENSION(jpi,jpj)     ::  zemp, zqsr, zmld, zice, zwspd, ztaux, ztauy   ! 2D workspace 
     312      REAL(wp), DIMENSION(jpi,jpj)     ::  zbblx, zbbly 
     313 
    295314#if ! defined key_degrad && defined key_traldf_c2d && defined key_traldf_eiv 
    296315      REAL(wp), DIMENSION(jpi,jpj) :: zaeiw  
     
    348367      CALL iom_get( numfl_u, jpdom_data, 'vozocrtx', zu   (:,:,:), jkenr ) 
    349368      CALL iom_get( numfl_v, jpdom_data, 'vomecrty', zv   (:,:,:), jkenr ) 
     369      IF( lk_trabbl .AND. .NOT. lk_c1d .AND. nn_bbl_ldf == 1 ) THEN 
     370         IF( iom_varid( numfl_u, 'sobblcox', ldstop = .FALSE. ) > 0  .AND. & 
     371         &   iom_varid( numfl_v, 'sobblcoy', ldstop = .FALSE. ) > 0 ) THEN 
     372             CALL iom_get( numfl_u, jpdom_data, 'sobblcox', zbblx(:,:), jkenr ) 
     373             CALL iom_get( numfl_v, jpdom_data, 'sobblcoy', zbbly(:,:), jkenr ) 
     374             l_offbbl = .TRUE. 
     375         ENDIF 
     376      ENDIF 
    350377 
    351378      ! file grid-W 
     
    405432      qsrdta (:,:,2)  = zqsr(:,:) * tmask(:,:,1) 
    406433      hmlddta(:,:,2)  = zmld(:,:) * tmask(:,:,1) 
     434 
     435      IF( l_offbbl ) THEN  
     436         bblxdta(:,:,2) = MAX( 0., zbblx(:,:) ) 
     437         bblydta(:,:,2) = MAX( 0., zbbly(:,:) ) 
     438         WHERE( bblxdta(:,:,2) > 2. ) bblxdta(:,:,2) = 0. 
     439         WHERE( bblydta(:,:,2) > 2. ) bblydta(:,:,2) = 0. 
     440      ENDIF 
    407441       
    408442      IF( kt == nitend ) THEN 
     
    589623      vdta   (:,:,:,1) = vdta   (:,:,:,2) 
    590624      wdta   (:,:,:,1) = wdta   (:,:,:,2) 
    591  
    592625#if defined key_ldfslp && ! defined key_c1d 
    593626      uslpdta (:,:,:,1) = uslpdta (:,:,:,2) 
     
    601634      empdta (:,:,1) = empdta (:,:,2)  
    602635      qsrdta (:,:,1) = qsrdta (:,:,2)  
     636      IF( l_offbbl ) THEN 
     637         bblxdta(:,:,1) = bblxdta(:,:,2) 
     638         bblydta(:,:,1) = bblydta(:,:,2)  
     639      ENDIF 
    603640 
    604641#if ! defined key_degrad && defined key_traldf_c2d && defined key_traldf_eiv 
     
    650687      emps(:,:) = emp(:,:)  
    651688      qsr (:,:) = qsrdta (:,:,2)  
    652  
     689      IF( l_offbbl ) THEN 
     690         ahu_bbl(:,:) = bblxdta(:,:,2) 
     691         ahv_bbl(:,:) = bblydta(:,:,2)  
     692      ENDIF 
    653693#if ! defined key_degrad && defined key_traldf_c2d && defined key_traldf_eiv 
    654694      aeiw(:,:) = aeiwdta(:,:,2) 
     
    703743      emps(:,:) = emp(:,:)  
    704744      qsr (:,:) = zweighm1 * qsrdta (:,:,1) + pweigh  * qsrdta (:,:,2)  
     745      IF( l_offbbl ) THEN 
     746         ahu_bbl(:,:) = zweighm1 * bblxdta(:,:,1) +  pweigh  * bblxdta(:,:,2) 
     747         ahv_bbl(:,:) = zweighm1 * bblydta(:,:,1) +  pweigh  * bblydta(:,:,2) 
     748      ENDIF 
    705749 
    706750#if ! defined key_degrad && defined key_traldf_c2d && defined key_traldf_eiv  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r2353 r2517  
    3333   USE prtctl          ! Print control 
    3434   USE restart         !  
     35   USE trc_oce, ONLY : lk_offline ! offline flag 
    3536 
    3637   IMPLICIT NONE 
     
    8081      ndt05   = NINT(0.5 * rdttra(1)) 
    8182 
    82       CALL day_rst( nit000, 'READ' )  
     83      IF( .NOT. lk_offline ) CALL day_rst( nit000, 'READ' )  
    8384 
    8485      ! set the calandar from ndastp (read in restart file and namelist) 
     
    254255      ENDIF 
    255256 
    256 #if ! defined key_offline 
    257       CALL rst_opn( kt )                                ! Open the restart file if needed and control lrst_oce 
    258 #endif 
    259       IF( lrst_oce )   CALL day_rst( kt, 'WRITE' )      ! write day restart information 
     257      IF( .NOT. lk_offline ) CALL rst_opn( kt )               ! Open the restart file if needed and control lrst_oce 
     258      IF( lrst_oce         ) CALL day_rst( kt, 'WRITE' )      ! write day restart information 
    260259      ! 
    261260   END SUBROUTINE day 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRA/trabbl.F90

    r2443 r2517  
    4343   PUBLIC   bbl           !  routine called by trcbbl.F90 and dtadyn.F90 
    4444 
    45 # if defined key_trabbl 
    4645   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbl = .TRUE.    !: bottom boundary layer flag 
    47 # else 
    48    LOGICAL, PUBLIC, PARAMETER ::   lk_trabbl = .FALSE.   !: bottom boundary layer flag 
    49 # endif 
    5046 
    5147   !                                           !!* Namelist nambbl *  
     
    5854 
    5955   REAL(wp), DIMENSION(jpi,jpj), PUBLIC ::   utr_bbl  , vtr_bbl   ! u- (v-) transport in the bottom boundary layer 
     56   REAL(wp), DIMENSION(jpi,jpj), PUBLIC ::   ahu_bbl  , ahv_bbl   ! masked diffusive bbl coefficients at u and v-points 
    6057 
    6158   INTEGER , DIMENSION(jpi,jpj) ::   mbku_d   , mbkv_d      ! vertical index of the "lower" bottom ocean U/V-level 
    6259   INTEGER , DIMENSION(jpi,jpj) ::   mgrhu    , mgrhv       ! = +/-1, sign of grad(H) in u-(v-)direction 
    6360   REAL(wp), DIMENSION(jpi,jpj) ::   ahu_bbl_0, ahv_bbl_0   ! diffusive bbl flux coefficients at u and v-points 
    64    REAL(wp), DIMENSION(jpi,jpj) ::   ahu_bbl  , ahv_bbl     ! masked diffusive bbl coefficients at u and v-points 
    6561   REAL(wp), DIMENSION(jpi,jpj) ::   e3u_bbl_0, e3v_bbl_0   ! thichness of the bbl (e3) at u and v-points 
    6662   REAL(wp), DIMENSION(jpi,jpj) ::   e1e2t_r   ! thichness of the bbl (e3) at u and v-points 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/trc_oce.F90

    r2326 r2517  
    3434   !!---------------------------------------------------------------------- 
    3535   LOGICAL, PUBLIC, PARAMETER ::   lk_qsr_bio = .FALSE.   !: bio-model light absorption flag 
     36#endif 
     37 
     38#if defined key_offline 
     39   !!---------------------------------------------------------------------- 
     40   !!   'key_offline'                                     OFFLINE mode           
     41   !!---------------------------------------------------------------------- 
     42   LOGICAL, PUBLIC, PARAMETER ::   lk_offline = .TRUE.   !: offline flag 
     43#else 
     44   !!---------------------------------------------------------------------- 
     45   !!   Default option                                   NO  OFFLINE mode           
     46   !!---------------------------------------------------------------------- 
     47   LOGICAL, PUBLIC, PARAMETER ::   lk_offline = .FALSE.   !: offline flag 
    3648#endif 
    3749 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zint.F90

    r2287 r2517  
    6969      END DO 
    7070 
    71       IF( nday_year == 365 ) THEN 
     71      IF( nday_year == REAL(nyear_len(1), wp) ) THEN 
    7272         xksi    = xksimax 
    7373         xksimax = 0.e0 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zprod.F90

    r2457 r2517  
    4343     grosip    = 0.151_wp 
    4444 
    45    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk)  ::        & 
    46      &                   prmax 
     45   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk)  ::  prmax  
    4746    
    4847   REAL(wp) ::   & 
     48      rday1                      ,  &  !: 0.6 / rday 
    4949      texcret                    ,  &  !: 1 - excret  
    5050      texcret2                   ,  &  !: 1 - excret2         
     
    105105 
    106106# if defined key_degrad 
    107       prmax(:,:,:) = 0.6 / rday * tgfunc(:,:,:) * facvol(:,:,:) 
     107      prmax(:,:,:) = rday1 * tgfunc(:,:,:) * facvol(:,:,:) 
    108108# else 
    109       prmax(:,:,:) = 0.6 / rday * tgfunc(:,:,:) 
     109      prmax(:,:,:) = rday1 * tgfunc(:,:,:) 
    110110# endif 
    111111 
    112112      ! compute the day length depending on latitude and the day 
    113       IF(lwp) write(numout,*) 
    114       IF(lwp) write(numout,*) 'p4zday : - Julian day ', nday_year 
    115       IF(lwp) write(numout,*) '~~~~~~' 
    116  
    117       IF( nleapy == 1 .AND. MOD( nyear, 4 ) == 0 ) THEN 
    118          zrum = FLOAT( nday_year - 80 ) / 366. 
    119       ELSE 
    120          zrum = FLOAT( nday_year - 80 ) / 365. 
    121       ENDIF 
     113      zrum = FLOAT( nday_year - 80 ) / REAL(nyear_len(1), wp) 
    122114      zcodel = ASIN(  SIN( zrum * rpi * 2. ) * SIN( rad * 23.5 )  ) 
    123115 
     
    408400      ENDIF 
    409401 
     402      rday1     = 0.6 / rday  
    410403      texcret   = 1.0 - excret 
    411404      texcret2  = 1.0 - excret2 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/PISCES/trcini_pisces.F90

    r2287 r2517  
    6464 
    6565      !                                            ! Time-step 
    66       rfact   = rdttra(1) * float(nn_dttrc)          ! --------- 
     66      rfact   = rdttrc(1)                          ! --------- 
    6767      rfactr  = 1. / rfact 
    68       rfact2  = rfact / float(nrdttrc) 
     68      rfact2  = rfact / FLOAT( nrdttrc ) 
    6969      rfact2r = 1. / rfact2 
    7070 
    71       IF(lwp) WRITE(numout,*) '    Tracer  time step    rfact  = ', rfact, ' rdt = ', rdt 
    72       IF(lwp) write(numout,*) '    Biology time step    rfact2 = ', rfact2 
     71      IF(lwp) WRITE(numout,*) '    Passive Tracer  time step    rfact  = ', rfact, ' rdt = ', rdttra(1) 
     72      IF(lwp) write(numout,*) '    PISCES  Biology time step    rfact2 = ', rfact2 
    7373 
    7474 
     
    8383 
    8484      CALL p4z_che        ! initialize the chemical constants 
    85  
    86       ndayflxtr = 0      !  Initialize a counter for the computation of chemistry 
    8785 
    8886      ! Initialization of tracer concentration in case of  no restart  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/PISCES/trcsms_pisces.F90

    r2287 r2517  
    3434   USE p4zflx          !  
    3535 
     36   USE prtctl_trc 
     37 
    3638   USE trdmod_oce 
    3739   USE trdmod_trc 
     
    6769      INTEGER ::   jnt, jn 
    6870      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrpis   ! used for pisces sms trends 
     71      CHARACTER (len=25) :: charout 
    6972      !!--------------------------------------------------------------------- 
    7073 
    7174      IF( kt == nit000 )   CALL trc_sms_pisces_init    ! Initialization (first time-step only) 
    7275 
    73       IF( ndayflxtr /= nday ) THEN      ! New days 
     76      IF( ndayflxtr /= nday_year ) THEN      ! New days 
    7477         ! 
    75          ndayflxtr = nday 
     78         ndayflxtr = nday_year 
     79 
     80         IF(lwp) write(numout,*) 
     81         IF(lwp) write(numout,*) ' New chemical constants and various rates for biogeochemistry at new day : ', nday_year 
     82         IF(lwp) write(numout,*) '~~~~~~' 
    7683 
    7784         CALL p4z_che          ! computation of chemical constants 
     
    7986         ! 
    8087      ENDIF 
    81  
    8288 
    8389      DO jnt = 1, nrdttrc          ! Potential time splitting if requested 
     
    98104        CALL lbc_lnk( tra(:,:,:,jn), 'T', 1. ) 
    99105      END DO 
     106 
    100107 
    101108      IF( l_trdtrc ) THEN 
     
    162169      CALL p4z_flx_init       ! gas exchange 
    163170 
     171      ndayflxtr = 0 
     172 
    164173   END SUBROUTINE trc_sms_pisces_init 
    165174 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/TRP/trcadv.F90

    r2402 r2517  
    6969#if ! defined key_pisces 
    7070      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000 
    71          r2dt(:) =  rdttra(:) * FLOAT(nn_dttrc)          ! = rdtra (restarting with Euler time stepping) 
     71         r2dt(:) =  rdttrc(:)           ! = rdttrc (restarting with Euler time stepping) 
    7272      ELSEIF( kt <= nit000 + nn_dttrc ) THEN          ! at nit000 or nit000+1 
    73          r2dt(:) = 2. * rdttra(:) * FLOAT(nn_dttrc)      ! = 2 rdttra (leapfrog) 
     73         r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
    7474      ENDIF 
    7575#else 
    76       r2dt(:) =  rdttra(:) * FLOAT(nn_dttrc)          ! = rdtra (restarting with Euler time stepping) 
     76      r2dt(:) =  rdttrc(:)              ! = rdttrc (for PISCES use Euler time stepping) 
    7777#endif 
    7878 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/TRP/trcbbl.F90

    r2287 r2517  
    5656      !!---------------------------------------------------------------------- 
    5757 
    58 #if ! defined key_offline 
    59       ! Online coupling with dynamics  : Computation of bbl coef and bbl transport 
    60       ! Offline coupling with dynamics : Read bbl coef and bbl transport from input files 
    61       CALL bbl( kt, 'TRC' ) 
    62       l_bbl = .FALSE.  
    63 #endif 
     58      IF( .NOT. lk_offline ) THEN 
     59         CALL bbl( kt, 'TRC' )         ! Online coupling with dynamics  : Computation of bbl coef and bbl transport 
     60         l_bbl = .FALSE.               ! Offline coupling with dynamics : Read bbl coef and bbl transport from input files 
     61      ENDIF 
    6462 
    6563      IF( l_trdtrc )  THEN 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90

    r2287 r2517  
    111111 
    112112      ! set time step size (Euler/Leapfrog) 
    113       IF( neuler == 0 .AND. kt ==  nit000) THEN  ;  r2dt(:) =     rdttra(:) * FLOAT( nn_dttrc )  ! at nit000             (Euler) 
    114       ELSEIF( kt <= nit000 + 1 )           THEN  ;  r2dt(:) = 2.* rdttra(:) * FLOAT( nn_dttrc )  ! at nit000 or nit000+1 (Leapfrog) 
     113      IF( neuler == 0 .AND. kt ==  nit000) THEN  ;  r2dt(:) =     rdttrc(:)   ! at nit000             (Euler) 
     114      ELSEIF( kt <= nit000 + 1 )           THEN  ;  r2dt(:) = 2.* rdttrc(:)   ! at nit000 or nit000+1 (Leapfrog) 
    115115      ENDIF 
    116116 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/TRP/trcsbc.F90

    r2287 r2517  
    8080      IF( l_trdtrc ) ALLOCATE( ztrtrd(jpi,jpj,jpk) ) 
    8181 
    82 #if ! defined key_offline 
    83       ! Concentration dilution effect on tracer due to evaporation, precipitation, and river runoff 
    84       IF( lk_vvl ) THEN                      ! volume variable 
    85          zemps(:,:) = emps(:,:) - emp(:,:)    
     82      IF( lk_offline ) THEN          ! emps in dynamical files contains emps - rnf 
     83         zemps(:,:) = emps(:,:)   
     84      ELSE                           ! Concentration dilution effect on tracer due to evaporation, precipitation, and river runoff 
     85         IF( lk_vvl ) THEN                      ! volume variable 
     86            zemps(:,:) = emps(:,:) - emp(:,:)    
    8687!!ch         zemps(:,:) = 0. 
    87       ELSE                                   ! linear free surface 
    88          IF( ln_rnf ) THEN  ;  zemps(:,:) = emps(:,:) - rnf(:,:)   !  E-P-R 
    89          ELSE               ;  zemps(:,:) = emps(:,:) 
     88         ELSE                                   ! linear free surface 
     89            IF( ln_rnf ) THEN  ;  zemps(:,:) = emps(:,:) - rnf(:,:)   !  E-P-R 
     90            ELSE               ;  zemps(:,:) = emps(:,:) 
     91            ENDIF  
    9092         ENDIF  
    9193      ENDIF  
    92 #else 
    93       ! emps in dynamical files contains emps - rnf 
    94       IF( lk_vvl ) THEN   ;   zemps(:,:) = 0.         ! No concentration/dilution effect  
    95       ELSE                ;   zemps(:,:) = emps(:,:)  ! emps -rnf  
    96       ENDIF 
    97 #endif 
    9894 
    9995      ! 0. initialization 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp.F90

    r2431 r2517  
    1818   USE trabbl          ! bottom boundary layer               (trc_bbl routine) 
    1919   USE trcbbl          ! bottom boundary layer               (trc_bbl routine) 
    20 #if ! defined key_offline 
    2120   USE zdfkpp          ! KPP non-local tracer fluxes         (trc_kpp routine) 
    22 #endif 
    2321   USE trcdmp          ! internal damping                    (trc_dmp routine) 
    2422   USE trcldf          ! lateral mixing                      (trc_ldf routine) 
     
    6765                                CALL trc_adv( kstp )            ! horizontal & vertical advection  
    6866                                CALL trc_ldf( kstp )            ! lateral mixing 
    69 #if ! defined key_offline 
    70          IF( lk_zdfkpp )        CALL trc_kpp( kstp )            ! KPP non-local tracer fluxes 
    71 #endif 
     67         IF( .NOT. lk_offline .AND. lk_zdfkpp )    & 
     68            &                   CALL trc_kpp( kstp )            ! KPP non-local tracer fluxes 
    7269#if defined key_agrif 
    7370         IF(.NOT. Agrif_Root()) CALL Agrif_Sponge_trc           ! tracers sponge 
     
    8178      ELSE                                               ! 1D vertical configuration 
    8279                                CALL trc_sbc( kstp )            ! surface boundary condition 
    83 #if ! defined key_offline 
    84           IF( lk_zdfkpp )       CALL trc_kpp( kstp )            ! KPP non-local tracer fluxes 
    85 #endif 
     80         IF( .NOT. lk_offline .AND. lk_zdfkpp )    & 
     81            &                   CALL trc_kpp( kstp )            ! KPP non-local tracer fluxes 
    8682                                CALL trc_zdf( kstp )            ! vertical mixing and after tracer fields 
    8783                                CALL trc_nxt( kstp )            ! tracer fields at next time step      
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/TRP/trczdf.F90

    r2476 r2517  
    6565#if ! defined key_pisces 
    6666      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000 
    67          r2dt(:) =  rdttra(:) * FLOAT(nn_dttrc)          ! = rdtra (restarting with Euler time stepping) 
     67         r2dt(:) =  rdttrc(:)           ! = rdttrc (restarting with Euler time stepping) 
    6868      ELSEIF( kt <= nit000 + nn_dttrc ) THEN          ! at nit000 or nit000+1 
    69          r2dt(:) = 2. * rdttra(:) * FLOAT(nn_dttrc)      ! = 2 rdttra (leapfrog) 
     69         r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
    7070      ENDIF 
    7171#else 
    72       r2dt(:) =  rdttra(:) * FLOAT(nn_dttrc)          ! = rdtra (restarting with Euler time stepping) 
     72      r2dt(:) =  rdttrc(:)              ! = rdttrc (for PISCES use Euler time stepping) 
    7373#endif 
    7474 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r2287 r2517  
    6161   !! -------------------------------------------------- 
    6262   INTEGER , PUBLIC ::   nn_writetrc   !: time step frequency for concentration outputs (namelist) 
     63   REAL(wp), PUBLIC, DIMENSION(jpk) ::   rdttrc        !: vertical profile of passive tracer time step 
    6364    
    6465# if defined key_diatrc && ! defined key_iomput 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/trcdia.F90

    r2420 r2517  
    101101      LOGICAL ::   ll_print = .FALSE. 
    102102      CHARACTER (len=40) :: clhstnam, clop 
    103 #if defined key_offline 
    104103      INTEGER ::   inum = 11             ! temporary logical unit 
    105 #endif 
    106104      CHARACTER (len=20) :: cltra, cltrau 
    107105      CHARACTER (len=80) :: cltral 
     
    159157            &                    ' limit storage in depth = ', ipk 
    160158 
    161 #if defined key_offline 
    162         ! WRITE root name in date.file for use by postpro 
    163          IF(lwp) THEN 
     159         IF( lk_offline .AND. lwp ) THEN 
    164160            CALL dia_nam( clhstnam, nn_writetrc,' ' ) 
    165161            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', 1, numout, lwp, narea ) 
     
    167163            CLOSE(inum) 
    168164         ENDIF 
    169 #endif 
    170165 
    171166         ! Define the NETCDF files for passive tracer concentration 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r2457 r2517  
    118118      ENDIF 
    119119 
    120       IF( .NOT. ln_rsttr ) THEN  
    121 #if defined key_offline 
    122          CALL day_init      ! calendar 
    123 #endif 
    124 # if defined key_dtatrc 
    125          ! Initialization of tracer from a file that may also be used for damping 
    126          CALL trc_dta( nit000 ) 
    127          DO jn = 1, jptra 
    128             IF( lutini(jn) )   trn(:,:,:,jn) = trdta(:,:,:,jn) * tmask(:,:,:)   ! initialisation from file if required 
    129          END DO 
    130 # endif 
    131          trb(:,:,:,:) = trn(:,:,:,:) 
     120      IF( ln_rsttr ) THEN 
     121        ! 
     122        IF( lk_offline )  neuler = 1   ! Set time-step indicator at nit000 (leap-frog) 
     123        CALL trc_rst_read              ! restart from a file 
     124        ! 
    132125      ELSE 
    133          ! 
    134          CALL trc_rst_read      ! restart from a file 
    135          ! 
     126        IF( lk_offline )  THEN 
     127           neuler = 0                  ! Set time-step indicator at nit000 (euler) 
     128           CALL day_init               ! set calendar 
     129        ENDIF 
     130        IF( lk_dtatrc )  THEN 
     131           CALL trc_dta( nit000 )      ! Initialization of tracer from a file that may also be used for damping 
     132           DO jn = 1, jptra 
     133              IF( lutini(jn) )   trn(:,:,:,jn) = trdta(:,:,:,jn) * tmask(:,:,:)   ! initialisation from file if required 
     134           END DO 
     135        ENDIF  
     136        trb(:,:,:,:) = trn(:,:,:,:) 
     137        !  
    136138      ENDIF 
    137  
     139  
    138140      tra(:,:,:,:) = 0. 
    139141       
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r2287 r2517  
    129129      ENDIF 
    130130 
     131      rdttrc(:) = rdttra(:) * FLOAT( nn_dttrc )   ! vertical profile of passive tracer time-step 
     132   
     133      IF(lwp) WRITE(numout,*)  
     134      IF(lwp) WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc(1) 
     135      IF(lwp) WRITE(numout,*)  
     136 
    131137#if defined key_trdmld_trc || defined key_trdtrc 
    132138      nn_trd_trc  = 20 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/trcrst.F90

    r2457 r2517  
    3434   USE trcrst_c14b     ! C14 bomb restart 
    3535   USE trcrst_my_trc   ! MY_TRC   restart 
    36 #if defined key_offline 
    37     USE daymod 
    38 #endif 
     36   USE daymod 
    3937   IMPLICIT NONE 
    4038   PRIVATE 
     
    6361      !!---------------------------------------------------------------------- 
    6462      ! 
    65 # if ! defined key_offline 
    66       IF( kt == nit000 ) lrst_trc = .FALSE.  
    67 # else 
    68       IF( kt == nit000 ) THEN 
    69         lrst_trc = .FALSE.  
    70         nitrst = nitend   
    71       ENDIF 
    72  
    73       IF( MOD( kt - 1, nstock ) == 0 ) THEN 
    74          ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment 
    75          nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing 
    76          IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run 
    77       ENDIF 
    78 # endif 
    79      ! to get better performances with NetCDF format: 
    80      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1) 
    81      ! except if we write tracer restart files every tracer time step or if a tracer restart file was writen at nitend - 2*nn_dttrc + 1 
    82      IF( kt == nitrst - 2*nn_dttrc + 1 .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc + 1 .AND. .NOT. lrst_trc ) ) THEN 
     63      IF( lk_offline ) THEN 
     64         IF( kt == nit000 ) THEN 
     65            lrst_trc = .FALSE. 
     66            nitrst = nitend 
     67         ENDIF 
     68 
     69         IF( MOD( kt - 1, nstock ) == 0 ) THEN 
     70            ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment 
     71            nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing 
     72            IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run 
     73         ENDIF 
     74      ELSE 
     75         IF( kt == nit000 ) lrst_trc = .FALSE. 
     76      ENDIF 
     77 
     78      ! to get better performances with NetCDF format: 
     79      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1) 
     80      ! except if we write tracer restart files every tracer time step or if a tracer restart file was writen at nitend - 2*nn_dttrc + 1 
     81      IF( kt == nitrst - 2*nn_dttrc + 1 .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc + 1 .AND. .NOT. lrst_trc ) ) THEN 
    8382         ! beware of the format used to write kt (default is i8.8, that should be large enough) 
    8483         IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst 
     
    102101      !!---------------------------------------------------------------------- 
    103102      INTEGER  ::  jn      
    104       INTEGER  ::  iarak0  
    105       REAL(wp) ::  zarak0 
    106103      INTEGER  ::  jlibalt = jprstlib 
    107104      LOGICAL  ::  llok 
     
    126123      CALL trc_rst_cal( nit000, 'READ' )   ! calendar 
    127124 
    128       IF( ln_trcadv_cen2 .OR. ln_trcadv_tvd ) THEN   ;   iarak0 = 1 
    129       ELSE                                           ;   iarak0 = 0 
    130       ENDIF 
    131       CALL iom_get( numrtr, 'arak0', zarak0 ) 
    132  
    133       IF( iarak0 /= NINT( zarak0 ) )   &                           ! Control of the scheme 
    134          & CALL ctl_stop( ' ===>>>> : problem with advection scheme', & 
    135          & ' it must be the same type for both restart and previous run', & 
    136          & ' centered or euler '  ) 
    137       IF(lwp) WRITE(numout,*) 
    138       IF(lwp) WRITE(numout,*) '    arakawa option      : ', NINT( zarak0 ) 
    139  
    140125      ! READ prognostic variables and computes diagnostic variable 
    141126      DO jn = 1, jptra 
     
    171156 
    172157      CALL trc_rst_cal( kt, 'WRITE' )   ! calendar 
    173  
    174       IF( ln_trcadv_cen2 .OR. ln_trcadv_tvd ) THEN   ;   zarak0 = 1. 
    175       ELSE                                           ;   zarak0 = 0. 
    176       ENDIF 
    177       CALL iom_rstput( kt, nitrst, numrtw, 'arak0', zarak0 ) 
    178  
     158      CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc(1) )   ! surface passive tracer time step 
    179159      ! prognostic variables  
    180160      ! --------------------  
     
    232212      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag 
    233213      ! 
    234       REAL(wp) ::  zkt 
    235 #if defined key_offline 
     214      REAL(wp) ::  zkt, zrdttrc1 
    236215      REAL(wp) ::  zndastp 
    237 #endif 
    238216 
    239217      ! Time domain : restart 
     
    257235            &   CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart',                 & 
    258236            &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' ) 
    259 #if defined key_offline 
    260          ! define ndastp and adatrj 
    261          IF ( nn_rsttr == 2 ) THEN 
    262             CALL iom_get( numrtr, 'ndastp', zndastp )  
    263             ndastp = NINT( zndastp ) 
    264             CALL iom_get( numrtr, 'adatrj', adatrj  ) 
    265          ELSE 
    266             ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam 
    267             adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    268             ! note this is wrong if time step has changed during run 
     237         IF( lk_offline ) THEN      ! set the date in offline mode 
     238            ! Check dynamics and tracer time-step consistency and force Euler restart if changed 
     239            IF( iom_varid( numrtr, 'rdttrc1', ldstop = .FALSE. ) > 0 )   THEN 
     240               CALL iom_get( numrtr, 'rdttrc1', zrdttrc1 ) 
     241               IF( zrdttrc1 /= rdttrc(1) )   neuler = 0 
     242            ENDIF 
     243            !                          ! define ndastp and adatrj 
     244            IF ( nn_rsttr == 2 ) THEN 
     245               CALL iom_get( numrtr, 'ndastp', zndastp )  
     246               ndastp = NINT( zndastp ) 
     247               CALL iom_get( numrtr, 'adatrj', adatrj  ) 
     248            ELSE 
     249               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam 
     250               adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
     251               ! note this is wrong if time step has changed during run 
     252            ENDIF 
     253            ! 
     254            IF(lwp) THEN 
     255              WRITE(numout,*) ' *** Info used values : ' 
     256              WRITE(numout,*) '   date ndastp                                      : ', ndastp 
     257              WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
     258              WRITE(numout,*) 
     259            ENDIF 
     260            ! 
     261            CALL day_init          ! compute calendar 
     262            ! 
    269263         ENDIF 
    270264         ! 
    271          IF(lwp) THEN 
    272            WRITE(numout,*) ' *** Info used values : ' 
    273            WRITE(numout,*) '   date ndastp                                      : ', ndastp 
    274            WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
    275            WRITE(numout,*) 
    276          ENDIF 
    277          ! 
    278          CALL day_init          ! compute calendar 
    279          ! 
    280 #endif 
    281  
    282265      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN 
    283266         ! 
     
    287270            IF(lwp) WRITE(numout,*) '~~~~~~~' 
    288271         ENDIF 
    289          ! calendar control 
    290272         CALL iom_rstput( kt, nitrst, numrtw, 'kt'     , REAL( kt    , wp) )   ! time-step 
    291273         CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp) )   ! date 
     
    304286      !!---------------------------------------------------------------------- 
    305287 
    306       INTEGER  :: ji, jj, jk, jn 
     288      INTEGER  :: jn 
    307289      REAL(wp) :: zdiag_var, zdiag_varmin, zdiag_varmax, zdiag_tot 
    308       REAL(wp) :: zder, zvol 
     290      REAL(wp) :: zder 
    309291      !!---------------------------------------------------------------------- 
    310292 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/trcwri.F90

    r2287 r2517  
    1616   USE trc 
    1717   USE iom 
    18 #if defined key_offline 
    19    USE oce_trc 
    2018   USE dianam 
    21 #endif 
    2219 
    2320   IMPLICIT NONE 
     
    5653      INTEGER               :: jn 
    5754      CHARACTER (len=20)    :: cltra 
    58 #if defined key_offline 
    5955      CHARACTER (len=40) :: clhstnam 
    6056      INTEGER ::   inum = 11            ! temporary logical unit 
    61 #endif 
    6257      !!--------------------------------------------------------------------- 
    6358  
    64 #if defined key_offline 
    65       IF( kt == nit000 ) THEN 
    66         ! WRITE root name in date.file for use by postpro 
    67          IF(lwp) THEN 
    68             CALL dia_nam( clhstnam, nn_writetrc,' ' ) 
    69             CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    70             WRITE(inum,*) clhstnam 
    71             CLOSE(inum) 
    72          ENDIF 
     59      IF( lk_offline .AND. kt == nit000 .AND. lwp ) THEN    ! WRITE root name in date.file for use by postpro 
     60         CALL dia_nam( clhstnam, nn_writetrc,' ' ) 
     61         CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
     62         WRITE(inum,*) clhstnam 
     63         CLOSE(inum) 
    7364      ENDIF 
    74 #endif 
    7565      ! write the tracer concentrations in the file 
    7666      ! --------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.