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

Changeset 2027


Ignore:
Timestamp:
2010-07-29T13:33:05+02:00 (14 years ago)
Author:
cetlod
Message:

Reorganisation of the initialisation phase, see ticket:695

Location:
branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC
Files:
1 added
19 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/DIA/diaar5.F90

    r2004 r2027  
    2323   PRIVATE 
    2424 
    25    PUBLIC   dia_ar5   ! routine called in step.F90 module 
     25   PUBLIC   dia_ar5        ! routine called in step.F90 module 
     26   PUBLIC   dia_ar5_init   ! routine called in opa.F90 module 
    2627 
    2728   LOGICAL, PUBLIC, PARAMETER :: lk_diaar5 = .TRUE.   ! coupled flag 
     
    6768      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zrhd, zrhop 
    6869      !!-------------------------------------------------------------------- 
    69  
    70       IF( kt == nit000  )   CALL dia_ar5_init   ! Initialization (first time-step only) 
    7170 
    7271      CALL iom_put( 'cellthc', fse3t(:,:,:) ) 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/DYN/dynadv.F90

    r1601 r2027  
    2222   PRIVATE 
    2323 
    24    PUBLIC dyn_adv     ! routine called by step module 
     24   PUBLIC dyn_adv       ! routine called by step module 
     25   PUBLIC dyn_adv_init  ! routine called by opa module 
    2526  
    2627   LOGICAL, PUBLIC ::   ln_dynadv_vec  = .TRUE.    ! vector form flag 
     
    5657      !!---------------------------------------------------------------------- 
    5758      ! 
    58       IF( kt == nit000 )   CALL dyn_adv_ctl          ! initialisation & control of options 
    59  
    6059      SELECT CASE ( nadv )                     ! compute advection trend and add it to general trend 
    6160      CASE ( 0 )      
     
    7776 
    7877    
    79    SUBROUTINE dyn_adv_ctl 
     78   SUBROUTINE dyn_adv_init 
    8079      !!--------------------------------------------------------------------- 
    81       !!                  ***  ROUTINE dyn_adv_ctl  *** 
     80      !!                  ***  ROUTINE dyn_adv_init  *** 
    8281      !!                 
    8382      !! ** Purpose :   Control the consistency between namelist options for  
     
    9493      IF(lwp) THEN                    ! Namelist print 
    9594         WRITE(numout,*) 
    96          WRITE(numout,*) 'dyn_adv_ctl : choice/control of the momentum advection scheme' 
     95         WRITE(numout,*) 'dyn_adv_init : choice/control of the momentum advection scheme' 
    9796         WRITE(numout,*) '~~~~~~~~~~~' 
    9897         WRITE(numout,*) '       Namelist namdyn_adv : chose a advection formulation & scheme for momentum' 
     
    124123      ENDIF 
    125124      ! 
    126    END SUBROUTINE dyn_adv_ctl 
     125   END SUBROUTINE dyn_adv_init 
    127126 
    128127  !!====================================================================== 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/DYN/dynhpg.F90

    r1601 r2027  
    1818   !!   dyn_hpg      : update the momentum trend with the now horizontal 
    1919   !!                  gradient of the hydrostatic pressure 
    20    !!       hpg_ctl : initialisation and control of options 
     20   !!       hpg_init : initialisation and control of options 
    2121   !!       hpg_zco  : z-coordinate scheme 
    2222   !!       hpg_zps  : z-coordinate plus partial steps (interpolation) 
     
    3939   PRIVATE 
    4040 
    41    PUBLIC   dyn_hpg    ! routine called by step module 
     41   PUBLIC   dyn_hpg        ! routine called by step module 
     42   PUBLIC       hpg_init   ! routine called by opa module 
    4243 
    4344   !                                              !!* Namelist namdyn_hpg : hydrostatic pressure gradient  
     
    8182      !!---------------------------------------------------------------------- 
    8283    
    83       IF( kt == nit000 )   CALL hpg_ctl      ! initialisation & control of options 
    84  
    8584      IF( l_trddyn ) THEN                    ! Temporary saving of ua and va trends (l_trddyn) 
    8685         ztrdu(:,:,:) = ua(:,:,:)   
     
    110109 
    111110 
    112    SUBROUTINE hpg_ctl 
    113       !!---------------------------------------------------------------------- 
    114       !!                 ***  ROUTINE hpg_ctl  *** 
     111   SUBROUTINE hpg_init 
     112      !!---------------------------------------------------------------------- 
     113      !!                 ***  ROUTINE hpg_init  *** 
    115114      !! 
    116115      !! ** Purpose :   initializations for the hydrostatic pressure gradient 
     
    174173 
    175174      ! 
    176    END SUBROUTINE hpg_ctl 
     175   END SUBROUTINE hpg_init 
    177176 
    178177 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/DYN/dynldf.F90

    r1954 r2027  
    3030   PRIVATE 
    3131 
    32    PUBLIC   dyn_ldf   ! called by step module  
     32   PUBLIC   dyn_ldf       ! called by step module  
     33   PUBLIC   dyn_ldf_init  ! called by opa module  
    3334 
    3435   INTEGER ::   nldf = 0   ! type of lateral diffusion used defined from ln_dynldf_... namlist logicals) 
     
    5657      !!---------------------------------------------------------------------- 
    5758 
    58       IF( kt == nit000 )   CALL dyn_ldf_ctl      ! initialisation & control of options 
    59  
    6059      IF( l_trddyn )   THEN                      ! temporary save of ta and sa trends 
    6160         ztrdu(:,:,:) = ua(:,:,:)  
     
    6968      CASE ( 2 )    ;   CALL dyn_ldf_bilap  ( kt )      ! iso-level bilaplacian 
    7069      CASE ( 3 )    ;   CALL dyn_ldf_bilapg ( kt )      ! s-coord. horizontal bilaplacian 
    71       CASE ( 4 )                                        ! iso-level laplacian + bilaplacian 
    72          CALL dyn_ldf_lap    ( kt ) 
    73          CALL dyn_ldf_bilap  ( kt ) 
    74       CASE ( 5 )                                        ! rotated laplacian + bilaplacian (s-coord) 
    75          CALL dyn_ldf_iso    ( kt ) 
    76          CALL dyn_ldf_bilapg ( kt ) 
    7770      ! 
    7871      CASE ( -1 )                                       ! esopa: test all possibility with control print 
     
    8982                        CALL prt_ctl( tab3d_1=ua, clinfo1=' ldf3 - Ua: ', mask1=umask,   & 
    9083            &                         tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    91       ! 
    92       CASE ( -2 )                                       ! neither laplacian nor bilaplacian schemes used 
    93          IF( kt == nit000 ) THEN 
    94             IF(lwp) WRITE(numout,*) 
    95             IF(lwp) WRITE(numout,*) 'dyn_ldf : no lateral diffusion on momentum setup' 
    96             IF(lwp) WRITE(numout,*) '~~~~~~~ ' 
    97          ENDIF 
    9884      END SELECT 
    9985 
     
    11096 
    11197 
    112    SUBROUTINE dyn_ldf_ctl 
     98   SUBROUTINE dyn_ldf_init 
    11399      !!---------------------------------------------------------------------- 
    114       !!                  ***  ROUTINE dyn_ldf_ctl  *** 
     100      !!                  ***  ROUTINE dyn_ldf_init  *** 
    115101      !!  
    116102      !! ** Purpose :   initializations of the horizontal ocean dynamics physics 
     
    123109      IF(lwp) THEN                        ! Namelist print 
    124110         WRITE(numout,*) 
    125          WRITE(numout,*) 'dyn_ldf_ctl : Choice of the lateral diffusive operator on dynamics' 
     111         WRITE(numout,*) 'dyn_ldf_init : Choice of the lateral diffusive operator on dynamics' 
    126112         WRITE(numout,*) '~~~~~~~~~~~' 
    127113         WRITE(numout,*) '       Namelist nam_dynldf : set lateral mixing parameters (type, direction, coefficients)' 
     
    137123      IF( ln_dynldf_lap   )   ioptio = ioptio + 1 
    138124      IF( ln_dynldf_bilap )   ioptio = ioptio + 1 
    139       IF( ioptio <  1 ) CALL ctl_warn( '          neither laplacian nor bilaplacian operator set for dynamics' ) 
     125      IF( ioptio /= 1 ) CALL ctl_stop( '          use ONE of the 2 lap/bilap operator type on dynamics' ) 
    140126      ioptio = 0 
    141127      IF( ln_dynldf_level )   ioptio = ioptio + 1 
     
    157143            IF ( ln_dynldf_iso   )   nldf = 1      ! isoneutral (   rotation) 
    158144         ENDIF 
    159          IF ( ln_sco ) THEN             ! s-coordinate 
     145         IF ( ln_sco ) THEN             ! z-coordinate 
    160146            IF ( ln_dynldf_level )   nldf = 0      ! iso-level  (no rotation) 
    161147            IF ( ln_dynldf_hor   )   nldf = 1      ! horizontal (   rotation) 
     
    175161            IF ( ln_dynldf_iso   )   ierr = 2      ! isoneutral (   rotation) 
    176162         ENDIF 
    177          IF ( ln_sco ) THEN             ! s-coordinate 
     163         IF ( ln_sco ) THEN             ! z-coordinate 
    178164            IF ( ln_dynldf_level )   nldf = 2      ! iso-level  (no rotation) 
    179165            IF ( ln_dynldf_hor   )   nldf = 3      ! horizontal (   rotation) 
     
    182168      ENDIF 
    183169       
    184       IF( ln_dynldf_lap .AND. ln_dynldf_bilap ) THEN  ! mixed laplacian and bilaplacian operators 
    185          IF ( ln_zco ) THEN                ! z-coordinate 
    186             IF ( ln_dynldf_level )   nldf = 4      ! iso-level  (no rotation) 
    187             IF ( ln_dynldf_hor   )   nldf = 4      ! horizontal (no rotation) 
    188             IF ( ln_dynldf_iso   )   ierr = 2      ! isoneutral (   rotation) 
    189          ENDIF 
    190          IF ( ln_zps ) THEN             ! z-coordinate 
    191             IF ( ln_dynldf_level )   ierr = 1      ! iso-level not allowed  
    192             IF ( ln_dynldf_hor   )   nldf = 4      ! horizontal (no rotation) 
    193             IF ( ln_dynldf_iso   )   ierr = 2      ! isoneutral (   rotation) 
    194          ENDIF 
    195          IF ( ln_sco ) THEN             ! s-coordinate 
    196             IF ( ln_dynldf_level )   nldf = 4      ! iso-level  (no rotation) 
    197             IF ( ln_dynldf_hor   )   nldf = 5      ! horizontal (   rotation) 
    198             IF ( ln_dynldf_iso   )   ierr = 2      ! isoneutral (   rotation) 
    199          ENDIF 
    200       ENDIF 
    201  
    202170      IF( lk_esopa )                 nldf = -1     ! esopa test 
    203171 
     
    210178      IF(lwp) THEN 
    211179         WRITE(numout,*) 
    212          IF( nldf == -2 )   WRITE(numout,*) '              neither laplacian nor bilaplacian schemes used' 
    213180         IF( nldf == -1 )   WRITE(numout,*) '              ESOPA test All scheme used' 
    214181         IF( nldf ==  0 )   WRITE(numout,*) '              laplacian operator' 
    215          IF( nldf ==  1 )   WRITE(numout,*) '              rotated laplacian operator' 
     182         IF( nldf ==  1 )   WRITE(numout,*) '              Rotated laplacian operator' 
    216183         IF( nldf ==  2 )   WRITE(numout,*) '              bilaplacian operator' 
    217          IF( nldf ==  3 )   WRITE(numout,*) '              rotated bilaplacian' 
    218          IF( nldf ==  4 )   WRITE(numout,*) '              laplacian and bilaplacian operators' 
    219          IF( nldf ==  5 )   WRITE(numout,*) '              rotated laplacian and bilaplacian operators' 
     184         IF( nldf ==  3 )   WRITE(numout,*) '              Rotated bilaplacian' 
    220185      ENDIF 
    221186      ! 
    222    END SUBROUTINE dyn_ldf_ctl 
     187   END SUBROUTINE dyn_ldf_init 
    223188 
    224189   !!====================================================================== 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/DYN/dynspg.F90

    r1566 r2027  
    2727   PRIVATE 
    2828 
    29    PUBLIC   dyn_spg   ! routine called by step module 
     29   PUBLIC   dyn_spg        ! routine called by step module 
     30   PUBLIC   dyn_spg_init   ! routine called by opa module 
    3031 
    3132   INTEGER ::   nspg = 0   ! type of surface pressure gradient scheme defined from lk_dynspg_...  
     
    7475 
    7576 
    76       IF( kt == nit000 )   CALL dyn_spg_ctl      ! initialisation & control of options 
    77  
    7877      IF( l_trddyn )   THEN                      ! temporary save of ta and sa trends 
    7978         ztrdu(:,:,:) = ua(:,:,:) 
     
    119118 
    120119 
    121    SUBROUTINE dyn_spg_ctl 
     120   SUBROUTINE dyn_spg_init 
    122121      !!--------------------------------------------------------------------- 
    123       !!                  ***  ROUTINE dyn_spg_ctl  *** 
     122      !!                  ***  ROUTINE dyn_spg_init  *** 
    124123      !!                 
    125124      !! ** Purpose :   Control the consistency between cpp options for  
     
    131130      IF(lwp) THEN             ! Control print 
    132131         WRITE(numout,*) 
    133          WRITE(numout,*) 'dyn_spg_ctl : choice of the surface pressure gradient scheme' 
     132         WRITE(numout,*) 'dyn_spg_init : choice of the surface pressure gradient scheme' 
    134133         WRITE(numout,*) '~~~~~~~~~~~' 
    135134         WRITE(numout,*) '     Explicit free surface                  lk_dynspg_exp = ', lk_dynspg_exp 
     
    178177#endif 
    179178      ! 
    180    END SUBROUTINE dyn_spg_ctl 
     179   END SUBROUTINE dyn_spg_init 
    181180 
    182181  !!====================================================================== 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/DYN/dynvor.F90

    r1694 r2027  
    3636   PRIVATE 
    3737 
    38    PUBLIC   dyn_vor   ! routine called by step.F90 
     38   PUBLIC   dyn_vor        ! routine called by step.F90 
     39   PUBLIC       vor_init   ! routine called by opa.F90 
    3940 
    4041   !                                             !!* Namelist namdyn_vor: vorticity term 
     
    7475      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    7576      !!---------------------------------------------------------------------- 
    76  
    77       IF( kt == nit000 )   CALL vor_ctl          ! initialisation & control of options 
    7877 
    7978      !                                          ! vorticity term  
     
    637636 
    638637 
    639    SUBROUTINE vor_ctl 
     638   SUBROUTINE vor_init 
    640639      !!--------------------------------------------------------------------- 
    641       !!                  ***  ROUTINE vor_ctl  *** 
     640      !!                  ***  ROUTINE vor_init  *** 
    642641      !! 
    643642      !! ** Purpose :   Control the consistency between cpp options for 
     
    653652      IF(lwp) THEN                    ! Namelist print 
    654653         WRITE(numout,*) 
    655          WRITE(numout,*) 'dyn:vor_ctl : vorticity term : read namelist and control the consistency' 
     654         WRITE(numout,*) 'dyn:vor_init : vorticity term : read namelist and control the consistency' 
    656655         WRITE(numout,*) '~~~~~~~~~~~' 
    657656         WRITE(numout,*) '        Namelist namdyn_vor : oice of the vorticity term scheme' 
     
    700699      ENDIF 
    701700      ! 
    702    END SUBROUTINE vor_ctl 
     701   END SUBROUTINE vor_init 
    703702 
    704703   !!============================================================================== 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/DYN/dynzdf.F90

    r1533 r2027  
    2727   PRIVATE 
    2828 
    29    PUBLIC   dyn_zdf    !  routine called by step.F90 
     29   PUBLIC   dyn_zdf       !  routine called by step.F90 
     30   PUBLIC   dyn_zdf_init  !  routine called by opa.F90 
    3031 
    3132   INTEGER  ::   nzdf = 0              ! type vertical diffusion algorithm used  
     
    5758      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrdu, ztrdv   ! 3D workspace 
    5859      !!--------------------------------------------------------------------- 
    59  
    60       IF( kt == nit000 )   CALL zdf_ctl          ! initialisation & control of options 
    6160 
    6261      !                                          ! set time step 
     
    9695 
    9796 
    98    SUBROUTINE zdf_ctl 
     97   SUBROUTINE dyn_zdf_init 
    9998      !!---------------------------------------------------------------------- 
    100       !!                 ***  ROUTINE zdf_ctl  *** 
     99      !!                 ***  ROUTINE dyn_zdf_init  *** 
    101100      !! 
    102101      !! ** Purpose :   initializations of the vertical diffusion scheme 
     
    124123      IF(lwp) THEN                                  ! Print the choice 
    125124         WRITE(numout,*) 
    126          WRITE(numout,*) 'dyn:zdf_ctl : vertical dynamics physics scheme' 
     125         WRITE(numout,*) 'dyn_zdf_init : vertical dynamics physics scheme' 
    127126         WRITE(numout,*) '~~~~~~~~~~~' 
    128127         IF( nzdf == -1 )   WRITE(numout,*) '              ESOPA test All scheme used' 
     
    131130      ENDIF 
    132131      ! 
    133    END SUBROUTINE zdf_ctl 
     132   END SUBROUTINE dyn_zdf_init 
    134133 
    135134   !!============================================================================== 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/FLO/floats.F90

    r1601 r2027  
    2525 
    2626   PUBLIC   flo_stp    ! routine called by step.F90 
     27   PUBLIC   flo_init   ! routine called by opa.F90 
    2728 
    2829   !!---------------------------------------------------------------------- 
     
    5253         IF(lwp) WRITE(numout,*) 'flo_stp : call floats routine ' 
    5354         IF(lwp) WRITE(numout,*) '~~~~~~~' 
    54  
    55          CALL flo_init           ! read the namelist of floats              
    5655 
    5756         CALL flo_dom            ! compute/read initial position of floats 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/LDF/ldfslp.F90

    r1515 r2027  
    3131   PRIVATE 
    3232 
    33    PUBLIC   ldf_slp    ! routine called by step.F90 
     33   PUBLIC   ldf_slp         ! routine called by step.F90 
     34   PUBLIC   ldf_slp_init    ! routine called by opa.F90 
    3435 
    3536   LOGICAL , PUBLIC, PARAMETER              ::   lk_ldfslp = .TRUE.   !: slopes flag 
     
    9798      !!---------------------------------------------------------------------- 
    9899       
    99       IF( kt == nit000 )   CALL ldf_slp_init      ! initialization (first time-step only) 
    100  
    101100      zeps  =  1.e-20                             ! Local constant initialization 
    102101      zmg   = -1.0 / grav 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/ZDF/zdfbfr.F90

    r1708 r2027  
    2626   PRIVATE 
    2727 
    28    PUBLIC   zdf_bfr    ! called by step.F90 
     28   PUBLIC   zdf_bfr         ! called by step.F90 
     29   PUBLIC   zdf_bfr_init    ! called by opa.F90 
    2930    
    3031   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   bfrua , bfrva   !: Bottom friction coefficients set in zdfbfr 
     
    7374      REAL(wp) ::   zvu, zuv, zecu, zecv   ! temporary scalars 
    7475      !!---------------------------------------------------------------------- 
    75  
    76  
    77       IF( kt == nit000 )   CALL zdf_bfr_init   ! initialisation 
    7876 
    7977      IF( nn_bfr == 2 ) THEN                 ! quadratic botton friction 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/ZDF/zdfddm.F90

    r1601 r2027  
    2424   PRIVATE 
    2525 
    26    PUBLIC   zdf_ddm    ! called by step.F90 
     26   PUBLIC   zdf_ddm       ! called by step.F90 
     27   PUBLIC   zdf_ddm_init  ! called by opa.F90 
    2728 
    2829   LOGICAL , PUBLIC, PARAMETER ::   lk_zdfddm = .TRUE.  !: double diffusive mixing flag 
     
    8586      REAL(wp), DIMENSION(jpi,jpj) ::   zmsks, zmskf, zmskd1, zmskd2, zmskd3   ! 2D workspace  
    8687      !!---------------------------------------------------------------------- 
    87  
    88       IF ( kt == nit000 )   CALL zdf_ddm_init          ! Initialization (first time-step only) 
    8988 
    9089      !                                                ! =============== 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/ZDF/zdfkpp.F90

    r2000 r2027  
    2828   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2929   USE prtctl          ! Print control 
    30    USE trdmod          ! momentum/tracers trends  
     30   USE trdmod_oce      ! ocean trends definition 
     31   USE trdtra          ! tracers trends 
    3132 
    3233   IMPLICIT NONE 
    3334   PRIVATE 
    3435 
    35    PUBLIC   zdf_kpp   ! routine called by step.F90 
    36    PUBLIC   tra_kpp   ! routine called by step.F90 
     36   PUBLIC   zdf_kpp       ! routine called by step.F90 
     37   PUBLIC   zdf_kpp_init  ! routine called by opa.F90 
     38   PUBLIC   tra_kpp       ! routine called by step.F90 
     39#if defined key_top 
     40   PUBLIC   trc_kpp       ! routine called by trcstp.F90 
     41#endif 
    3742 
    3843   LOGICAL , PUBLIC, PARAMETER ::   lk_zdfkpp = .TRUE.    !: KPP vertical mixing flag 
     
    12371242      !! 
    12381243      !! ** Purpose :   compute and add to the tracer trend the non-local 
    1239       !!      tracer flux 
     1244      !!                tracer flux 
    12401245      !! 
    12411246      !! ** Method  :   ??? 
    12421247      !! 
    12431248      !! history : 
    1244       !!     9.0  ! 05-11 (G. Madec)  Original code 
     1249      !!     1.0  ! 2005-11 (G. Madec)  Original code 
     1250      !!     3.3  ! 2010-06 (C. Ethe)  Merge TRA-TRC 
    12451251      !!---------------------------------------------------------------------- 
    12461252      !! * Modules used 
    1247       USE oce, ONLY :    ztrdt => ua,       & ! use ua as 3D workspace 
    1248                          ztrds => va          ! use va as 3D workspace 
     1253      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrdt, ztrds   ! 3D workspace 
    12491254      !!---------------------------------------------------------------------- 
    12501255      INTEGER, INTENT(in) :: kt 
     
    12521257 
    12531258      IF( kt == nit000 ) THEN 
    1254          IF(lwp) WRITE(numout,*) 
     1259         IF(lwp) WRITE(numout,*)  
    12551260         IF(lwp) WRITE(numout,*) 'tra_kpp : KPP non-local tracer fluxes' 
    12561261         IF(lwp) WRITE(numout,*) '~~~~~~~   ' 
    12571262      ENDIF 
    12581263 
    1259  
    1260       ! Save ta and sa trends 
    1261       IF( l_trdtra )   THEN 
    1262          ztrdt(:,:,:) = ta(:,:,:) 
    1263          ztrds(:,:,:) = sa(:,:,:) 
     1264      IF( l_trdtra )   THEN                    !* Save ta and sa trends 
     1265         ALLOCATE( ztrdt(jpi,jpj,jpk) )   ;    ztrdt(:,:,:) = tsa(:,:,:,jp_tem) 
     1266         ALLOCATE( ztrds(jpi,jpj,jpk) )   ;    ztrds(:,:,:) = tsa(:,:,:,jp_sal) 
    12641267      ENDIF 
    12651268 
    12661269      ! add non-local temperature and salinity flux ( in convective case only) 
    12671270      DO jk = 1, jpkm1 
    1268          DO jj = 2, jpjm1 
     1271         DO jj = 2, jpjm1  
    12691272            DO ji = fs_2, fs_jpim1 
    1270                ta(ji,jj,jk) =  ta(ji,jj,jk)                           & 
    1271                   &         - ( ghats(ji,jj,jk  ) * avt(ji,jj,jk  )   & 
    1272                   &           - ghats(ji,jj,jk+1) * avt(ji,jj,jk+1) ) * wt0(ji,jj) / fse3t(ji,jj,jk) 
    1273                sa(ji,jj,jk) = sa(ji,jj,jk)                              & 
    1274                   &         - ( ghats(ji,jj,jk  ) * fsavs(ji,jj,jk  )   & 
    1275                   &           - ghats(ji,jj,jk+1) * fsavs(ji,jj,jk+1) ) * ws0(ji,jj) / fse3t(ji,jj,jk) 
     1273               tsa(ji,jj,jk,jp_tem) =  tsa(ji,jj,jk,jp_tem)                      & 
     1274                  &                 - (  ghats(ji,jj,jk  ) * avt  (ji,jj,jk  )   &  
     1275                  &                    - ghats(ji,jj,jk+1) * avt  (ji,jj,jk+1) ) * wt0(ji,jj) / fse3t(ji,jj,jk) 
     1276               tsa(ji,jj,jk,jp_sal) =  tsa(ji,jj,jk,jp_sal)                      & 
     1277                  &                 - (  ghats(ji,jj,jk  ) * fsavs(ji,jj,jk  )   &  
     1278                  &                    - ghats(ji,jj,jk+1) * fsavs(ji,jj,jk+1) ) * ws0(ji,jj) / fse3t(ji,jj,jk) 
    12761279            END DO 
    12771280         END DO 
     
    12801283      ! save the non-local tracer flux trends for diagnostic 
    12811284      IF( l_trdtra )   THEN 
    1282          ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:) 
    1283          ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:) 
     1285         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:) 
     1286         ztrds(:,:,:) = tsa(:,:,:,jp_sal) - ztrds(:,:,:) 
    12841287!!bug gm jpttdzdf ==> jpttkpp 
    1285          CALL trd_mod(ztrdt, ztrds, jptra_trd_zdf, 'TRA', kt) 
     1288         CALL trd_tra( kt, 'TRA', jp_tem, jptra_trd_zdf, ztrdt ) 
     1289         CALL trd_tra( kt, 'TRA', jp_sal, jptra_trd_zdf, ztrds ) 
     1290         DEALLOCATE( ztrdt )      ;     DEALLOCATE( ztrds ) 
    12861291      ENDIF 
    12871292 
    1288       IF(ln_ctl) THEN   
    1289          CALL prt_ctl( tab3d_1=ta, clinfo1=' kpp  - Ta: ', mask1=tmask,   & 
    1290          &             tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     1293      IF(ln_ctl) THEN 
     1294         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' kpp  - Ta: ', mask1=tmask,   & 
     1295         &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    12911296      ENDIF 
    12921297 
    12931298   END SUBROUTINE tra_kpp 
    12941299 
     1300#if defined key_top 
     1301   !!---------------------------------------------------------------------- 
     1302   !!   'key_top'                                                TOP models 
     1303   !!---------------------------------------------------------------------- 
     1304   SUBROUTINE trc_kpp( kt ) 
     1305      !!---------------------------------------------------------------------- 
     1306      !!                  ***  ROUTINE trc_kpp  *** 
     1307      !! 
     1308      !! ** Purpose :   compute and add to the tracer trend the non-local 
     1309      !!                tracer flux 
     1310      !! 
     1311      !! ** Method  :   ??? 
     1312      !! 
     1313      !! history : 
     1314      !!            9.0  ! 2005-11 (G. Madec)  Original code 
     1315      !!       NEMO 3.3  ! 2010-06 (C. Ethe )  Adapted to passive tracers 
     1316      !!---------------------------------------------------------------------- 
     1317      USE trc 
     1318      USE prtctl_trc          ! Print control 
     1319      !! * Arguments 
     1320      INTEGER ,                         INTENT( in    )  :: kt     ! ocean time-step index 
     1321      !! * Local declarations 
     1322      INTEGER  ::   ji, jj, jk, jn      ! Dummy loop indices 
     1323      REAL(wp) ::   ztra, zflx 
     1324      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrtrd 
     1325      !!---------------------------------------------------------------------- 
     1326 
     1327      IF( kt == nit000 ) THEN 
     1328         IF(lwp) WRITE(numout,*)  
     1329         IF(lwp) WRITE(numout,*) 'trc_kpp : KPP non-local tracer fluxes' 
     1330         IF(lwp) WRITE(numout,*) '~~~~~~~   ' 
     1331      ENDIF 
     1332 
     1333      IF( l_trdtrc )  ALLOCATE( ztrtrd(jpi,jpj,jpk) ) 
     1334      ! 
     1335      DO jn = 1, jptra 
     1336         ! 
     1337         IF( l_trdtrc )  ztrtrd(:,:,:)  = tra(:,:,:,jn) 
     1338         ! add non-local on passive tracer flux ( in convective case only) 
     1339         DO jk = 1, jpkm1 
     1340            DO jj = 2, jpjm1  
     1341               DO ji = fs_2, fs_jpim1 
     1342                  ! Surface tracer flux for non-local term  
     1343                  zflx = - ( emps(ji,jj) * tra(ji,jj,1,jn) * rcs ) * tmask(ji,jj,1) 
     1344                  ! compute the trend 
     1345                  ztra = - ( ghats(ji,jj,jk  ) * fsavs(ji,jj,jk  )   & 
     1346                  &        - ghats(ji,jj,jk+1) * fsavs(ji,jj,jk+1) ) * zflx / fse3t(ji,jj,jk) 
     1347                  ! add the trend to the general trend 
     1348                  tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn)  + ztra 
     1349               END DO 
     1350            END DO 
     1351         END DO 
     1352         ! save the non-local tracer flux trends for diagnostic 
     1353         IF( l_trdtrc )  ztrtrd(:,:,:)  = tra(:,:,:,jn) - ztrtrd(:,:,:) 
     1354         CALL trd_tra( kt, 'TRC', jn, jptra_trd_zdf, ztrtrd(:,:,:,jn) ) 
     1355         ! 
     1356      END DO 
     1357      IF( l_trdtrc )  DEALLOCATE( ztrtrd ) 
     1358      IF( ln_ctl )   THEN 
     1359         WRITE(charout, FMT="(' kpp')")  ;  CALL prt_ctl_trc_info(charout) 
     1360         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=clname, clinfo2='trd' ) 
     1361      ENDIF 
     1362      ! 
     1363   END SUBROUTINE trc_kpp 
     1364#endif 
    12951365 
    12961366   SUBROUTINE zdf_kpp_init 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/ZDF/zdfric.F90

    r1601 r2027  
    2828   PRIVATE 
    2929 
    30    PUBLIC   zdf_ric    ! called by step.F90 
     30   PUBLIC   zdf_ric         ! called by step.F90 
     31   PUBLIC   zdf_ric_init    ! called by opa.F90 
    3132 
    3233   LOGICAL, PUBLIC, PARAMETER ::   lk_zdfric = .TRUE.   !: Richardson vertical mixing flag 
     
    8283      !!---------------------------------------------------------------------- 
    8384 
    84       IF( kt == nit000  ) CALL zdf_ric_init            ! Initialization (first time-step only) 
    85  
    8685      !                                                ! =============== 
    8786      DO jk = 2, jpkm1                                 ! Horizontal slab 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/ZDF/zdftke.F90

    r1756 r2027  
    5454 
    5555   PUBLIC   zdf_tke    ! routine called in step module 
     56   PUBLIC   tke_init   ! routine called in opa module 
    5657   PUBLIC   tke_rst    ! routine called in step module 
    5758 
     
    149150      !!---------------------------------------------------------------------- 
    150151      ! 
    151       IF( kt == nit000 )   CALL tke_init     ! initialisation  
    152                            ! 
    153152                           CALL tke_tke      ! now tke (en) 
    154153                           ! 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/ZDF/zdftke_old.F90

    r1617 r2027  
    4949 
    5050   PUBLIC   zdf_tke_old   ! routine called in step module 
     51   PUBLIC   zdf_tke_init  ! routine called in opa module 
    5152 
    5253   LOGICAL , PUBLIC, PARAMETER              ::   lk_zdftke_old = .TRUE.  !: TKE vertical mixing flag 
     
    182183      !!-------------------------------------------------------------------- 
    183184 
    184       IF( kt == nit000  )   CALL zdf_tke_init      ! Initialization (first time-step only) 
    185  
    186185      !                                            ! Local constant initialization 
    187186      zbbrau =  .5 * rn_ebb / rau0 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/ZDF/zdftmx.F90

    r1601 r2027  
    2727   PRIVATE 
    2828 
    29    PUBLIC   zdf_tmx    ! called in step module  
     29   PUBLIC   zdf_tmx         ! called in step module  
     30   PUBLIC   zdf_tmx_init    ! called in opa module  
    3031 
    3132   LOGICAL, PUBLIC, PARAMETER ::   lk_zdftmx = .TRUE.    !: tidal mixing flag 
     
    9697      REAL(wp), DIMENSION(jpi,jpj) ::   zkz   ! temporary 2D workspace 
    9798      !!---------------------------------------------------------------------- 
    98  
    99       !                         
    100       IF( kt == nit000  )   CALL zdf_tmx_init      ! Initialization (first time-step only) 
    10199 
    102100      !                          ! ----------------------- ! 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/cla.F90

    r2000 r2027  
    2929   !! * Routine accessibility 
    3030   PUBLIC tra_cla        ! routine called by step.F90 
     31   PUBLIC tra_cla_init   ! routine called by opa.F90 
    3132 
    3233   !! * Modules variables    
     
    7677      !!---------------------------------------------------------------------- 
    7778  
    78       ! cross land advection for straits 
    79  
    80       ! Initialization 
    81       IF( kt == nit000 )   CALL tra_cla_init 
    82  
    83  
    8479      ! Bab el Mandeb strait horizontal advection 
    8580 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/opa.F90

    r1976 r2027  
    2525   !!             -   ! 2007-07  (J. Chanut, A. Sellar) Unstructured open boundaries (BDY) 
    2626   !!            3.2  ! 2009-08  (S. Masson)  open/write in the listing file in mpp 
     27   !!            3.3  ! 2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase 
    2728   !!---------------------------------------------------------------------- 
    2829 
     
    3334   !!   opa_closefile  : close remaining files 
    3435   !!---------------------------------------------------------------------- 
    35    USE oce             ! dynamics and tracers variables 
    36    USE dom_oce         ! ocean space domain variables 
     36 
     37   USE step_oce        ! Time stepping module definition 
    3738   USE sbc_oce         ! surface boundary condition: ocean 
    3839   USE trdmod_oce      ! ocean variables trends 
     
    4041   USE mppini          ! shared/distributed memory setting (mpp_init routine) 
    4142   USE domain          ! domain initialization             (dom_init routine) 
    42    USE obc_par         ! open boundary cond. parameters 
    4343   USE obcini          ! open boundary cond. initialization (obc_ini routine) 
    44    USE bdy_par         ! unstructured open boundary cond. parameters 
    4544   USE bdyini          ! unstructured open boundary cond. initialization (bdy_init routine) 
    4645   USE istate          ! initial state setting          (istate_init routine) 
    47    USE sbcmod          ! surface boundary condition  
    48    USE eosbn2          ! equation of state                 (eos_init routine) 
    49    USE dynhpg          ! hydrostatic pressure gradient 
    5046   USE ldfdyn          ! lateral viscosity setting      (ldfdyn_init routine) 
    5147   USE ldftra          ! lateral diffusivity setting    (ldftra_init routine) 
     
    5349   USE phycst          ! physical constant                  (par_cst routine) 
    5450   USE trdmod          ! momentum/tracers trends       (trd_mod_init routine) 
    55    USE diaptr          ! poleward transports           (dia_ptr_init routine) 
    5651   USE step            ! OPA time-stepping                  (stp     routine) 
    5752#if defined key_oasis3 
     
    6055   USE cpl_oasis4      ! OASIS4 coupling (not working) 
    6156#endif 
    62    USE dynspg_oce      ! Control choice of surface pressure gradient schemes 
    63    USE prtctl          ! Print control                 (prt_ctl_init routine) 
    6457   USE c1d             ! 1D configuration 
    65    USE dyncor_c1d      ! Coriolis factor at T-point 
    6658   USE step_c1d        ! Time stepping loop for the 1D configuration 
    6759#if defined key_top 
    6860   USE trcini          ! passive tracer initialisation 
    6961#endif 
    70     
    71    USE iom 
    72    USE in_out_manager  ! I/O manager 
     62 
    7363   USE lib_mpp         ! distributed memory computing 
    7464#if defined key_iomput 
     
    7666#endif 
    7767 
    78    IMPLICIT NONE 
    7968   PRIVATE 
    8069 
     
    237226      ELSE                            ;   CALL mpp_init2     ! eliminate land processors 
    238227      ENDIF 
    239        
    240       CALL phy_cst                          ! Physical constants 
    241       CALL eos_init                         ! Equation of state 
    242       CALL dom_cfg                          ! Domain configuration 
    243       CALL dom_init                         ! Domain 
    244 !!gm c1d case can be moved in dom_init routine 
    245       IF( lk_c1d ) THEN                          ! 1D configuration  
    246          CALL cor_c1d                            ! Coriolis defined at T-point 
    247          umask(:,:,:) = tmask(:,:,:)             ! U, V and T-points are the same 
    248          vmask(:,:,:) = tmask(:,:,:)             !  
    249       ENDIF 
    250 !!gm c1d end 
    251  
    252       IF( ln_ctl )   CALL prt_ctl_init      ! Print control 
    253  
    254       IF( lk_obc )   CALL obc_init          ! Open boundaries  
    255       IF( lk_bdy )   CALL bdy_init          ! Unstructured open boundaries 
    256  
    257       CALL istate_init                      ! ocean initial state (Dynamics and tracers) 
     228  
     229 
     230 
     231      
     232 
     233                            CALL     phy_cst    ! Physical constants 
     234                            CALL     eos_init   ! Equation of state 
     235                            CALL     dom_cfg    ! Domain configuration 
     236                            CALL     dom_init   ! Domain 
     237 
     238      IF( ln_ctl        )   CALL prt_ctl_init   ! Print control 
     239 
     240      IF( lk_obc        )   CALL     obc_init   ! Open boundaries  
     241      IF( lk_bdy        )   CALL     bdy_init   ! Unstructured open boundaries 
     242 
     243      IF( ln_zps        )   CALL zps_hde_init   ! Partial steps:  horizontal derivative 
     244                            CALL  istate_init   ! ocean initial state (Dynamics and tracers) 
    258245 
    259246      !                                     ! Ocean physics 
    260       CALL sbc_init                             ! Read namsbc namelist : surface module (needed for iom_init) 
    261       CALL ldf_tra_init                         ! Lateral ocean tracer physics 
    262       CALL ldf_dyn_init                         ! Lateral ocean momentum physics 
    263       CALL zdf_init                             ! Vertical ocean physics 
    264  
     247                            CALL     sbc_init   ! Read namsbc namelist : surface module (needed for iom_init) 
     248 
     249      !                                     ! Vertical physics 
     250                            CALL     zdf_init   ! namelist read 
     251                            CALL zdf_bfr_init   ! bottom friction 
     252      IF( lk_zdfric     )   CALL zdf_ric_init   ! Richardson number dependent Kz 
     253      IF( lk_zdftke_old )   CALL zdf_tke_init   ! TKE closure scheme for Kz (old scheme) 
     254      IF( lk_zdftke     )   CALL     tke_init   ! TKE closure scheme for Kz 
     255      IF( lk_zdfkpp     )   CALL zdf_kpp_init   ! KPP closure scheme for Kz 
     256      IF( lk_zdftmx     )   CALL zdf_tmx_init   ! tidal vertical mixing 
     257      IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   &  
     258         &                  CALL zdf_ddm_init   ! double diffusive mixing 
     259      !                                     ! Lateral physics 
     260                            CALL ldf_tra_init   ! Lateral ocean tracer physics 
     261                            CALL ldf_dyn_init   ! Lateral ocean momentum physics 
     262      IF( lk_ldfslp )       CALL ldf_slp_init   ! slope of lateral mixing 
     263#if defined key_traldf_c2d 
     264      IF( lk_traldf_eiv )   CALL ldf_eiv( kstp )      ! eddy induced velocity coefficient 
     265#  endif 
     266      !                                     ! Active tracers 
     267                            CALL tra_qsr_init   ! penetrative solar radiation qsr 
     268      IF( lk_trabbc     )   CALL tra_bbc_init   ! bottom heat flux 
     269      IF( lk_trabbl     )   CALL tra_bbl_init   ! advective (and/or diffusive) bottom boundary layer scheme 
     270      IF( lk_tradmp     )   CALL tra_dmp_init   ! internal damping trends 
     271                            CALL tra_adv_init   ! horizontal & vertical advection 
     272      IF( n_cla == 1    )   CALL tra_cla_init   ! Cross Land Advection (Update Hor. advection) 
     273                            CALL tra_ldf_init   ! lateral mixing 
     274                            CALL tra_zdf_init   ! vertical mixing and after tracer fields 
     275 
     276      !                                     ! Dynamics 
     277                            CALL dyn_adv_init   ! advection (vector or flux form) 
     278                            CALL     vor_init   ! vorticity term including Coriolis 
     279                            CALL dyn_ldf_init   ! lateral mixing 
     280                            CALL     hpg_init   ! horizontal gradient of Hydrostatic pressure 
     281                            CALL dyn_zdf_init   ! vertical diffusion 
     282                            CALL dyn_spg_init   ! surface pressure gradient 
    265283#if defined key_top 
    266       CALL trc_ini                          ! Passive tracers 
     284      !                                     ! Passive tracers 
     285                            CALL     trc_ini 
    267286#endif 
    268287 
    269288      !                                     ! diagnostics 
    270       CALL iom_init                             ! iom_put initialization 
    271       CALL dia_ptr_init                         ! Poleward TRansports initialization 
    272       CALL trd_mod_init                         ! Mixed-layer/Vorticity/Integral constraints trends 
     289                            CALL     iom_init   ! iom_put initialization 
     290      IF( lk_floats    )    CALL     flo_init   ! drifting Floats 
     291      IF( lk_diaar5    )    CALL dia_ar5_init   ! ar5 diag 
     292                            CALL dia_ptr_init   ! Poleward TRansports initialization 
     293                            CALL trd_mod_init   ! Mixed-layer/Vorticity/Integral constraints trends 
    273294      ! 
    274295   END SUBROUTINE opa_init 
  • branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/step.F90

    r1953 r2027  
    2626   !!   stp            : OPA system time-stepping 
    2727   !!---------------------------------------------------------------------- 
    28    USE oce             ! ocean dynamics and tracers variables 
    29    USE dom_oce         ! ocean space and time domain variables  
    30    USE zdf_oce         ! ocean vertical physics variables 
    31    USE ldftra_oce      ! ocean tracer   - trends 
    32    USE ldfdyn_oce      ! ocean dynamics - trends 
    33    USE in_out_manager  ! I/O manager 
    34    USE iom             ! 
    35    USE lbclnk 
    36  
    37    USE daymod          ! calendar                         (day     routine) 
    38  
    39    USE dtatem          ! ocean temperature data           (dta_tem routine) 
    40    USE dtasal          ! ocean salinity    data           (dta_sal routine) 
    41    USE sbcmod          ! surface boundary condition       (sbc     routine) 
    42    USE sbcrnf          ! surface boundary condition: runoff variables 
    43    USE sbccpl          ! surface boundary condition: coupled formulation (call send at end of step) 
    44    USE cpl_oasis3, ONLY : lk_cpl 
    45  
    46 #if defined key_top 
    47    USE trcstp          ! passive tracer time-stepping      (trc_stp routine) 
    48 #endif 
    49  
    50    USE traqsr          ! solar radiation penetration      (tra_qsr routine) 
    51    USE trasbc          ! surface boundary condition       (tra_sbc routine) 
    52    USE trabbc          ! bottom boundary condition        (tra_bbc routine) 
    53    USE trabbl          ! bottom boundary layer            (tra_bbl routine) 
    54    USE tradmp          ! internal damping                 (tra_dmp routine) 
    55    USE traadv          ! advection scheme control     (tra_adv_ctl routine) 
    56    USE traldf          ! lateral mixing                   (tra_ldf routine) 
    57    USE cla             ! cross land advection             (tra_cla routine) 
    58    !   zdfkpp          ! KPP non-local tracer fluxes      (tra_kpp routine) 
    59    USE trazdf          ! vertical mixing                  (tra_zdf routine) 
    60    USE tranxt          ! time-stepping                    (tra_nxt routine) 
    61    USE tranpc          ! non-penetrative convection       (tra_npc routine) 
    62  
    63    USE eosbn2          ! equation of state                (eos_bn2 routine) 
    64  
    65    USE dynadv          ! advection                        (dyn_adv routine) 
    66    USE dynbfr          ! Bottom friction terms            (dyn_bfr routine) 
    67    USE dynvor          ! vorticity term                   (dyn_vor routine) 
    68    USE dynhpg          ! hydrostatic pressure grad.       (dyn_hpg routine) 
    69    USE dynldf          ! lateral momentum diffusion       (dyn_ldf routine) 
    70    USE dynzdf          ! vertical diffusion               (dyn_zdf routine) 
    71    USE dynspg_oce      ! surface pressure gradient        (dyn_spg routine) 
    72    USE dynspg          ! surface pressure gradient        (dyn_spg routine) 
    73    USE dynnxt          ! time-stepping                    (dyn_nxt routine) 
    74  
    75    USE obc_par         ! open boundary condition variables 
    76    USE obcdta          ! open boundary condition data     (obc_dta routine) 
    77    USE obcrst          ! open boundary cond. restart      (obc_rst routine) 
    78    USE obcrad          ! open boundary cond. radiation    (obc_rad routine) 
    79  
    80    USE bdy_par         ! unstructured open boundary data variables 
    81    USE bdydta          ! unstructured open boundary data  (bdy_dta routine) 
    82  
    83    USE sshwzv          ! vertical velocity and ssh        (ssh_wzv routine) 
    84  
    85    USE ldfslp          ! iso-neutral slopes               (ldf_slp routine) 
    86    USE ldfeiv          ! eddy induced velocity coef.      (ldf_eiv routine) 
    87  
    88    USE zdftmx          ! tide-induced vertical mixing     (zdf_tmx routine) 
    89    USE zdfbfr          ! bottom friction                  (zdf_bfr routine) 
    90    USE zdftke_old      ! old TKE vertical mixing      (zdf_tke_old routine) 
    91    USE zdftke          ! TKE vertical mixing              (zdf_tke routine) 
    92    USE zdfkpp          ! KPP vertical mixing              (zdf_kpp routine) 
    93    USE zdfddm          ! double diffusion mixing          (zdf_ddm routine) 
    94    USE zdfevd          ! enhanced vertical diffusion      (zdf_evd routine) 
    95    USE zdfric          ! Richardson vertical mixing       (zdf_ric routine) 
    96    USE zdfmxl          ! Mixed-layer depth                (zdf_mxl routine) 
    97  
    98    USE zpshde          ! partial step: hor. derivative     (zps_hde routine) 
    99  
    100    USE diawri          ! Standard run outputs             (dia_wri routine) 
    101    USE trdicp          ! Ocean momentum/tracers trends    (trd_wri routine) 
    102    USE trdmld          ! mixed-layer trends               (trd_mld routine) 
    103    USE trdmld_rst      ! restart for mixed-layer trends 
    104    USE trdmod_oce      ! ocean momentum/tracers trends 
    105    USE trdvor          ! vorticity budget                 (trd_vor routine) 
    106    USE diagap          ! hor. mean model-data gap         (dia_gap routine) 
    107    USE diahdy          ! dynamic height                   (dia_hdy routine) 
    108    USE diaptr          ! poleward transports              (dia_ptr routine) 
    109    USE diaar5          ! AR5 diagnosics                   (dia_ar5 routine) 
    110    USE diahth          ! thermocline depth                (dia_hth routine) 
    111    USE diafwb          ! freshwater budget                (dia_fwb routine) 
    112    USE flo_oce         ! floats variables 
    113    USE floats          ! floats computation               (flo_stp routine) 
    114  
    115    USE stpctl          ! time stepping control            (stp_ctl routine) 
    116    USE restart         ! ocean restart                    (rst_wri routine) 
    117    USE prtctl          ! Print control                    (prt_ctl routine) 
    118  
    119 #if defined key_agrif 
    120    USE agrif_opa_sponge ! Momemtum and tracers sponges 
    121 #endif 
     28   USE step_oce         ! time stepping definition modules  
    12229 
    12330   IMPLICIT NONE 
     
    265172                             sa(:,:,:) = 0.e0 
    266173 
     174                             CALL tra_swap 
    267175                             CALL tra_sbc    ( kstp )       ! surface boundary condition 
    268176      IF( ln_traqsr      )   CALL tra_qsr    ( kstp )       ! penetrative solar radiation qsr 
    269177      IF( lk_trabbc      )   CALL tra_bbc    ( kstp )       ! bottom heat flux 
    270       IF( lk_trabbl_dif  )   CALL tra_bbl_dif( kstp )       ! diffusive bottom boundary layer scheme 
    271       IF( lk_trabbl_adv  )   CALL tra_bbl_adv( kstp )       ! advective (and/or diffusive) bottom boundary layer scheme 
     178      IF( lk_trabbl      )   CALL tra_bbl    ( kstp )       ! advective (and/or diffusive) bottom boundary layer scheme 
    272179      IF( lk_tradmp      )   CALL tra_dmp    ( kstp )       ! internal damping trends 
    273180                             CALL tra_adv    ( kstp )       ! horizontal & vertical advection 
     
    276183                             CALL tra_ldf    ( kstp )       ! lateral mixing 
    277184#if defined key_agrif 
     185                             CALL tra_unswap 
    278186      IF(.NOT. Agrif_Root()) CALL Agrif_Sponge_tra          ! tracers sponge 
     187                             CALL tra_swap 
    279188#endif 
    280189                             CALL tra_zdf    ( kstp )       ! vertical mixing and after tracer fields 
     
    283192         IF( ln_zdfnpc   )   CALL tra_npc    ( kstp )            ! update after fields by non-penetrative convection 
    284193                             CALL tra_nxt    ( kstp )            ! tracer fields at next time step 
     194                             CALL tra_unswap 
    285195                             CALL eos( ta, sa, rhd, rhop )       ! Time-filtered in situ density for hpg computation 
    286196         IF( ln_zps      )   CALL zps_hde( kstp, ta, sa, rhd,   &   ! Partial steps: time filtered hor. derivative 
     
    289199          
    290200      ELSE                                                  ! centered hpg  (eos then time stepping) 
     201                             CALL tra_unswap 
    291202                             CALL eos( tn, sn, rhd, rhop )       ! now in situ density for hpg computation 
    292203         IF( ln_zps      )   CALL zps_hde( kstp, tn, sn, rhd,   &   ! Partial steps: now horizontal derivative 
    293204            &                                   gtu, gsu, gru,  &   ! of t, s, rd at the bottom ocean level 
    294205            &                                   gtv, gsv, grv ) 
     206                             CALL tra_swap 
    295207         IF( ln_zdfnpc   )   CALL tra_npc    ( kstp )       ! update after fields by non-penetrative convection 
    296208                             CALL tra_nxt    ( kstp )       ! tracer fields at next time step 
     209                             CALL tra_unswap 
    297210      ENDIF  
    298211 
Note: See TracChangeset for help on using the changeset viewer.