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 900 for trunk/NEMO/C1D_SRC/step_c1d.F90 – NEMO

Ignore:
Timestamp:
2008-04-22T20:13:41+02:00 (16 years ago)
Author:
rblod
Message:

Update 1D configuration according to SBC and LIM3, see ticket #117

File:
1 edited

Legend:

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

    r899 r900  
    1 MODULE step1d 
     1MODULE step_c1d 
    22   !!====================================================================== 
    3    !!                       ***  MODULE step1D  *** 
    4    !! Time-stepping    : manager of the ocean, tracer and ice time stepping 
     3   !!                       ***  MODULE step_c1d  *** 
     4   !! Time-stepping    : manager of the ocean, tracer and ice time stepping - c1d case 
    55   !!====================================================================== 
     6   !! History :   2.0  !  2004-04  (C. Ethe)  adapted from step.F90 for C1D 
     7   !!             3.0  !  2008-04  (G. Madec)  redo the adaptation to include SBC 
     8   !!---------------------------------------------------------------------- 
    69#if defined key_cfg_1d 
    710   !!---------------------------------------------------------------------- 
    8    !!   'key_cfg_1d'               1D Configuration 
     11   !!   'key_cfg_1d'                                       1D Configuration 
    912   !!----------------------------------------------------------------------   
    10    !!---------------------------------------------------------------------- 
    11    !!   stp_1d           : OPA system time-stepping on 1 direction 
    12    !!---------------------------------------------------------------------- 
    13    !! * Modules used 
     13   !!   stp_c1d        : NEMO system time-stepping in c1d case 
     14   !!---------------------------------------------------------------------- 
    1415   USE oce             ! ocean dynamics and tracers variables 
    1516   USE dom_oce         ! ocean space and time domain variables  
    1617   USE zdf_oce         ! ocean vertical physics variables 
    17    USE sbc_oce         ! surface boundary condition: ocean 
    18    USE ldftra_oce 
    19    USE ldfdyn_oce 
    2018   USE in_out_manager  ! I/O manager 
     19   USE iom             ! 
    2120   USE lbclnk 
    2221 
     
    2524   USE dtatem          ! ocean temperature data           (dta_tem routine) 
    2625   USE dtasal          ! ocean salinity    data           (dta_sal routine) 
     26   USE sbcmod          ! surface boundary condition       (sbc     routine) 
     27   USE sbcrnf          ! surface boundary condition: runoff variables 
    2728   USE ocfzpt          ! surface ocean freezing point    (oc_fz_pt routine) 
    2829 
    29    USE trcstp          ! passive tracer time-stepping     (trc_stp routine) 
    30  
     30   USE trcstp          ! passive tracer time-stepping      (trc_stp routine) 
     31 
     32   USE traqsr          ! solar radiation penetration      (tra_qsr routine) 
     33   USE trasbc          ! surface boundary condition       (tra_sbc routine) 
     34   !   zdfkpp          ! KPP non-local tracer fluxes      (tra_kpp routine) 
     35   USE trazdf          ! vertical mixing                  (tra_zdf routine) 
     36   USE tranxt          ! time-stepping                    (tra_nxt routine) 
     37   USE tranpc          ! non-penetrative convection       (tra_npc routine) 
     38 
     39   USE eosbn2          ! equation of state                (eos_bn2 routine) 
     40 
     41   USE dyncor1d        ! Coriolis term (c1d case)         (dyn_cor_1d     ) 
    3142   USE dynzdf          ! vertical diffusion               (dyn_zdf routine) 
    32  
    33    USE traqsr          ! solar radiation penetration      (tra_qsr routine) 
    34    USE tranxt          ! time-stepping                    (tra_nxt routine) 
    35    USE trazdf          ! vertical diffusion               (tra_zdf routine) 
    36    USE trasbc          ! surface boundary condition       (tra_sbc routine) 
    37  
    38    USE eosbn2 
     43   USE dynnxt1d        ! time-stepping                    (dyn_nxt routine) 
    3944 
    4045   USE zdfbfr          ! bottom friction                  (zdf_bfr routine) 
     
    4651   USE zdfmxl          ! Mixed-layer depth                (zdf_mxl routine) 
    4752 
    48    USE dyncor1d 
    49    USE dynnxt1d 
    50    USE diawri1d        ! Standard run outputs             (dia_wri_1d routine) 
    51  
    5253   USE ice_oce         ! sea-ice variable 
    53    USE icestp1d        ! sea-ice time-stepping             (ice_stp routine) 
    54  
    55    USE diawri          ! Standard run outputs             (dia_wri_state routine) 
    56  
     54 
     55   USE diawri          ! Standard run outputs             (dia_wri routine) 
    5756 
    5857   USE stpctl          ! time stepping control            (stp_ctl routine) 
    5958   USE restart         ! ocean restart                    (rst_wri routine) 
    6059   USE prtctl          ! Print control                    (prt_ctl routine) 
     60 
    6161   IMPLICIT NONE 
    6262   PRIVATE 
    6363 
    64    !! * Routine accessibility 
    65    PUBLIC stp_1d            ! called by opa.F90 
     64   PUBLIC stp_c1d      ! called by opa.F90 
    6665 
    6766   !! * Substitutions 
     
    6968#  include "zdfddm_substitute.h90" 
    7069   !!---------------------------------------------------------------------- 
    71    !!   OPA 9.0 , LOCEAN-IPSL (2005)  
    72    !! $Id$ 
    73    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     70   !! NEMO 3.0 , LOCEAN-IPSL (2008)  
     71   !! $Id:$ 
     72   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)  
    7473   !!---------------------------------------------------------------------- 
    7574 
    7675CONTAINS 
    7776 
    78    SUBROUTINE stp_1d( kstp ) 
     77   SUBROUTINE stp_c1d( kstp ) 
    7978      !!---------------------------------------------------------------------- 
    80       !!                     ***  ROUTINE stp1D  *** 
     79      !!                     ***  ROUTINE stp_c1d  *** 
    8180      !!                       
    82       !! ** Purpose : - Time stepping of OPA (momentum and active tracer eqs.) 
    83       !!              - Time stepping of LIM (dynamic and thermodynamic eqs.) 
     81      !! ** Purpose :  - Time stepping of SBC including LIM (dynamic and thermodynamic eqs.) 
     82      !!               - Time stepping of OPA (momentum and active tracer eqs.) 
     83      !!               - Time stepping of TOP (passive tracer eqs.) 
    8484      !!  
    8585      !! ** Method  : -1- Update forcings and data   
    86       !!              -2- Update ocean physics  
     86      !!              -2- Update vertical ocean physics  
    8787      !!              -3- Compute the t and s trends  
    8888      !!              -4- Update t and s  
     
    9191      !!              -7- Compute the diagnostics variables (rd,N2, div,cur,w) 
    9292      !!              -8- Outputs and diagnostics 
    93       !! 
    94       !! History : 
    95       !!        !  91-03  ()  Original code 
    96       !!        !  91-11  (G. Madec) 
    97       !!        !  92-06  (M. Imbard)  add a first output record 
    98       !!        !  96-04  (G. Madec)  introduction of dynspg 
    99       !!        !  96-04  (M.A. Foujols)  introduction of passive tracer 
    100       !!   8.0  !  97-06  (G. Madec)  new architecture of call 
    101       !!   8.2  !  97-06  (G. Madec, M. Imbard, G. Roullet)  free surface 
    102       !!   8.2  !  99-02  (G. Madec, N. Grima)  hpg implicit 
    103       !!   8.2  !  00-07  (J-M Molines, M. Imbard)  Open Bondary Conditions 
    104       !!   9.0  !  02-06  (G. Madec)  free form, suppress macro-tasking 
    105       !!        !  04-10  (C. Ethe) 1D configuration 
    10693      !!---------------------------------------------------------------------- 
    107       !! * Arguments 
    108       INTEGER, INTENT( in ) ::   kstp   ! ocean time-step index 
    109  
    110       !! * local declarations 
     94      INTEGER, INTENT(in) ::   kstp   ! ocean time-step index 
     95      INTEGER ::   jk       ! dummy loop indice 
    11196      INTEGER ::   indic    ! error indicator if < 0 
    112 !!      INTEGER ::   ii0, ii1, ij0, ij1   ! temporary integers 
    11397      !! --------------------------------------------------------------------- 
    11498 
    11599      indic = 1                    ! reset to no error condition 
    116       adatrj = adatrj + rdt/86400._wp 
    117100 
    118101      CALL day( kstp )             ! Calendar 
    119102 
    120       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    121       ! Update data, open boundaries and Forcings 
     103      CALL rst_opn( kstp )         ! Open the restart file 
     104 
     105      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     106      ! Update data, open boundaries, surface boundary condition (including sea-ice) 
    122107      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    123108 
    124109      IF( lk_dtatem  )   CALL dta_tem( kstp )         ! update 3D temperature data 
    125  
    126       IF( lk_dtasal  )   CALL dta_sal( kstp )         ! Salinity data 
    127  
    128       IF( lk_dtasst  )   CALL dta_sst( kstp )         ! Sea Surface Temperature data 
    129  
    130                          CALL tau( kstp )             ! wind stress 
    131  
    132                          CALL flx_rnf( kstp )         ! runoff data 
    133  
    134                          CALL flx( kstp )             ! heat and freshwater fluxes 
    135  
    136       IF( lk_ice_lim )  THEN  
    137                         CALL ice_stp_1d( kstp )      ! sea-ice model (Update stress & fluxes) 
    138       ELSE 
    139                         CALL oce_sbc( kstp )         ! ocean surface boudaries 
     110      IF( lk_dtasal  )   CALL dta_sal( kstp )         ! update 3D salinity data 
     111 
     112                         CALL sbc    ( kstp )         ! Sea Boundary Condition (including sea-ice) 
     113 
     114      IF( ninist == 1 ) THEN                          ! Output the initial state and forcings 
     115                        CALL dia_wri_state( 'output.init' )   ;   ninist = 0 
    140116      ENDIF 
    141117 
    142       IF( ln_fwb     )   CALL flx_fwb( kstp )         ! freshwater budget 
    143  
    144  
    145       IF( kstp == nit000 ) THEN  
    146          IF( ninist == 1 ) THEN                       ! Output the initial state and forcings 
    147             CALL dia_wri_state( 'output.init' ) 
    148          ENDIF 
    149       ENDIF 
    150  
    151       IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    152          CALL prt_ctl(tab2d_1=emp    , clinfo1=' emp  -   : ', mask1=tmask, ovlap=1) 
    153          CALL prt_ctl(tab2d_1=emps   , clinfo1=' emps -   : ', mask1=tmask, ovlap=1) 
    154          CALL prt_ctl(tab2d_1=qns    , clinfo1=' qns  -   : ', mask1=tmask, ovlap=1) 
    155          CALL prt_ctl(tab2d_1=qsr    , clinfo1=' qsr  -   : ', mask1=tmask, ovlap=1) 
    156          CALL prt_ctl(tab3d_1=tmask  , clinfo1=' tmask    : ', mask1=tmask, ovlap=1, kdim=jpk) 
    157          CALL prt_ctl(tab3d_1=tn     , clinfo1=' sst  -   : ', mask1=tmask, ovlap=1, kdim=1) 
    158          CALL prt_ctl(tab3d_1=sn     , clinfo1=' sss  -   : ', mask1=tmask, ovlap=1, kdim=1) 
    159          CALL prt_ctl(tab2d_1=utau   , clinfo1=' tau  - u : ', mask1=umask, & 
    160             &         tab2d_2=vtau   , clinfo2='      - v : ', mask2=vmask, ovlap=1) 
    161       ENDIF 
    162  
    163  
    164118 
    165119      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    172126      !----------------------------------------------------------------------- 
    173127 
    174                        CALL bn2( tb, sb, rn2 )              ! before Brunt-Vaisala frequency 
     128                        CALL bn2( tb, sb, rn2 )             ! before Brunt-Vaisala frequency 
    175129       
    176130      !                                                     ! Vertical eddy viscosity and diffusivity coefficients 
    177       IF( lk_zdfric )   CALL zdf_ric( kstp )                       ! Richardson number dependent Kz 
    178       IF( lk_zdftke )   CALL zdf_tke( kstp )                       ! TKE closure scheme for Kz 
    179       IF( lk_zdfkpp )   CALL zdf_kpp( kstp )                       ! KPP scheme for Kz 
    180       IF( lk_zdfcst )   avt (:,:,:) = avt0 * tmask(:,:,:)          ! Constant Kz (reset avt to the background value) 
    181  
    182  
     131      IF( lk_zdfric )   CALL zdf_ric( kstp )                     ! Richardson number dependent Kz 
     132      IF( lk_zdftke )   CALL zdf_tke( kstp )                     ! TKE closure scheme for Kz 
     133      IF( lk_zdfkpp )   CALL zdf_kpp( kstp )                     ! KPP closure scheme for Kz 
     134      IF( lk_zdfcst )   THEN                                     ! Constant Kz (reset avt, avm to the background value) 
     135         avt (:,:,:) = avt0 * tmask(:,:,:) 
     136         avmu(:,:,:) = avm0 * umask(:,:,:) 
     137         avmv(:,:,:) = avm0 * vmask(:,:,:) 
     138      ENDIF 
     139      IF( nn_runoff /=0 ) THEN                              ! increase diffusivity at rivers mouths 
     140         DO jk = 2, nkrnf   ;   avt(:,:,jk) = avt(:,:,jk) + rn_avt_rnf * rnfmsk(:,:)   ;   END DO 
     141      ENDIF 
    183142      IF( ln_zdfevd )   CALL zdf_evd( kstp )                 ! enhanced vertical eddy diffusivity 
    184  
    185       IF( lk_zdfddm .AND. .NOT. lk_zdfkpp)   & 
     143      IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   & 
    186144         &              CALL zdf_ddm( kstp )                 ! double diffusive mixing 
    187  
    188145                        CALL zdf_bfr( kstp )                 ! bottom friction 
    189  
    190146                        CALL zdf_mxl( kstp )                 ! mixed layer depth 
    191147 
    192  
    193148#if defined key_passivetrc 
    194149      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    197152      ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
    198153      !----------------------------------------------------------------------- 
    199  
    200                                CALL trc_stp( kstp, indic )            ! time-stepping 
    201  
     154                             CALL trc_stp( kstp, indic )            ! time-stepping 
    202155#endif 
    203156 
    204  
    205157      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    206158      ! Active tracers 
     
    208160      ! N.B. ua, va arrays are used as workspace in this section 
    209161      !----------------------------------------------------------------------- 
    210  
    211                                ta(:,:,:) = 0.e0               ! set tracer trends to zero 
    212                                sa(:,:,:) = 0.e0 
    213  
    214                                CALL tra_sbc( kstp )           ! surface boundary condition 
    215  
    216       IF( ln_traqsr        )   CALL tra_qsr( kstp )           ! penetrative solar radiation qsr 
    217  
    218       IF( lk_zdfkpp        )   CALL tra_kpp( kstp )           ! KPP non-local tracer fluxes 
    219  
    220                                CALL tra_zdf( kstp )           ! vertical mixing 
    221  
    222                                CALL tra_nxt( kstp )           ! tracer fields at next time step 
    223  
    224                                CALL eos( tb, sb, rhd, rhop )       ! now (swap=before) in situ density for dynhpg module 
     162                             ta(:,:,:) = 0.e0                ! set tracer trends to zero 
     163                             sa(:,:,:) = 0.e0 
     164 
     165                             CALL tra_sbc    ( kstp )        ! surface boundary condition 
     166      IF( ln_traqsr      )   CALL tra_qsr    ( kstp )        ! penetrative solar radiation qsr 
     167                             CALL tra_adv    ( kstp )        ! horizontal & vertical advection 
     168      IF( lk_zdfkpp )        CALL tra_kpp    ( kstp )        ! KPP non-local tracer fluxes 
     169                             CALL tra_zdf    ( kstp )        ! vertical mixing 
     170                             CALL tra_nxt( kstp )            ! tracer fields at next time step 
     171      IF( ln_zdfnpc      )   CALL tra_npc( kstp )            ! applied non penetrative convective adjustment on (t,s) 
     172                             CALL eos( tb, sb, rhd, rhop )   ! now (swap=before) in situ density for dynhpg module 
    225173 
    226174      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    229177      ! N.B. ta, sa arrays are used as workspace in this section  
    230178      !----------------------------------------------------------------------- 
    231  
    232179                               ua(:,:,:) = 0.e0               ! set dynamics trends to zero 
    233180                               va(:,:,:) = 0.e0 
    234    
    235                                CALL dyn_cor_1d     ( kstp ) 
    236       !                                                       ! vertical diffusion 
    237                                CALL dyn_zdf( kstp )       
    238  
    239 !i bug lbc sur emp 
    240       CALL lbc_lnk( emp, 'T', 1. ) 
    241 !i 
    242   
    243                                 CALL dyn_nxt_1d( kstp )          ! lateral velocity at next time step  
    244  
     181 
     182                               CALL dyn_vor_c1d( kstp )       ! vorticity term including Coriolis 
     183                               CALL dyn_zdf    ( kstp )       ! vertical diffusion 
     184                               CALL dyn_nxt_c1d( kstp )       ! lateral velocity at next time step 
    245185 
    246186      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    249189      ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
    250190      !----------------------------------------------------------------------- 
    251  
    252                                CALL oc_fz_pt                    ! ocean surface freezing temperature 
    253  
    254  
    255       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    256       ! Control, diagnostics and outputs 
    257       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    258       ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
    259       !----------------------------------------------------------------------- 
    260  
    261       !                                            ! Time loop: control and print 
    262                        CALL stp_ctl( kstp, indic ) 
    263                        IF ( indic < 0 ) CALL ctl_stop( 'step1d: indic < 0' ) 
    264  
    265       IF ( nstop == 0 ) THEN 
    266          !                                         ! Diagnostics: 
    267          !                                         ! save and outputs 
    268                            CALL rst_write  ( kstp )              ! ocean model: restart file output 
    269                            CALL dia_wri_1d ( kstp, indic )       ! ocean model: outputs 
    270  
    271       ENDIF 
    272  
    273  
    274    END SUBROUTINE stp_1d 
     191                       CALL oc_fz_pt                        ! ocean surface freezing temperature 
     192 
     193      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     194      ! Control and restarts 
     195      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     196                                 CALL stp_ctl( kstp, indic ) 
     197      IF( kstp == nit000     )   CALL iom_close( numror )             ! close input  ocean restart file 
     198      IF( lrst_oce           )   CALL rst_write  ( kstp )             ! write output ocean restart file 
     199 
     200      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     201      ! diagnostics and outputs 
     202      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     203      ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
     204      !----------------------------------------------------------------------- 
     205 
     206      IF( nstop == 0 )           CALL dia_wri_c1d( kstp, indic )       ! ocean model: outputs 
     207      ! 
     208   END SUBROUTINE stp_c1d 
     209 
    275210#else 
    276211   !!---------------------------------------------------------------------- 
    277    !!   Default key                                     NO 1D Config 
     212   !!   Default key                                            NO 1D Config 
    278213   !!---------------------------------------------------------------------- 
    279214CONTAINS 
    280    SUBROUTINE stp_1d ( kt ) 
    281       WRITE(*,*) 'stp_1d: You should not have seen this print! error?', kt 
    282    END SUBROUTINE stp_1d 
     215   SUBROUTINE stp_c1d ( kt )      ! dummy routine 
     216      WRITE(*,*) 'stp_c1d: You should not have seen this print! error?', kt 
     217   END SUBROUTINE stp_c1d 
    283218#endif 
     219 
    284220   !!====================================================================== 
    285 END MODULE step1d 
     221END MODULE step_c1d 
Note: See TracChangeset for help on using the changeset viewer.