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

Changeset 3720


Ignore:
Timestamp:
2012-12-04T11:10:08+01:00 (11 years ago)
Author:
cbricaud
Message:

correction ticket 955 & 956

Location:
trunk
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • trunk/DOC/TexFiles/Chapters/Chap_CFG.tex

    r3683 r3720  
    3131 
    3232% ================================================================ 
    33 % 1D model functionality 
     33% 1D model configuration 
    3434% ================================================================ 
    3535\section{Water column model: 1D model (C1D) (\key{c1d})} 
     
    4848 
    4949The methodology is based on the use of the zoom functionality over the smallest possible  
    50 domain : a 3 x 3 domain centred on the grid point of interest (see \S\ref{MISC_zoom}),  
     50domain : a 3x3 domain centred on the grid point of interest (see \S\ref{MISC_zoom}),  
    5151with some extra routines. There is no need to define a new mesh, bathymetry,  
    5252initial state or forcing, since the 1D model will use those of the configuration it is a zoom of.  
    53 The chosen grid point is set in par\_oce.F90 module by setting the \jp{jpizoom} and \jp{jpjzoom}  
     53The chosen grid point is set in \mdl{par\_oce} module by setting the \jp{jpizoom} and \jp{jpjzoom}  
    5454parameters to the indices of the location of the chosen grid point. 
    5555 
    56 The 1D model has some specifies. First, all the horizontal derivatives are assumed to be zero.  
    57 Therefore a simplified \rou{step} routine is used (\rou{step\_c1d}) in which both lateral tendancy  
    58 terms and lateral physics are not called, and the vertical velocity is zero (so far, no attempt at 
    59 introducing a Ekman pumping velocity has been made). 
    60 Second, the two components of the velocity are moved on a $T$-point.  
    61 This requires a specific treatment of the Coriolis term (see \rou{dyncor\_c1d}) and of the  
    62 dynamic time stepping (\rou{dynnxt\_c1d}). 
    63 All the relevant modules can be found in the NEMOGCM/NEMO/OPA\_SRC/C1D directory of  
     56The 1D model has some specifies. First, all the horizontal derivatives are assumed to be zero, and 
     57second, the two components of the velocity are moved on a $T$-point.  
     58Therefore, defining \key{c1d} changes five main things in the code behaviour:  
     59\begin{description} 
     60\item[(1)] the lateral boundary condition routine (\rou{lbc\_lnk}) set the value of the central column  
     61of the 3x3 domain is imposed over the whole domain ;  
     62\item[(3)] a call to \rou{lbc\_lnk} is systematically done when reading input data ($i.e.$ in \mdl{iom}) ;  
     63\item[(3)] a simplified \rou{stp} routine is used (\rou{stp\_c1d}, see \mdl{step\_c1d} module) in which  
     64both lateral tendancy terms and lateral physics are not called ;  
     65\item[(4)] the vertical velocity is zero (so far, no attempt at introducing a Ekman pumping velocity  
     66has been made) ;  
     67\item[(5)] a simplified treatment of the Coriolis term is performed as $U$- and $V$-points are the same  
     68(see \mdl{dyncor\_c1d}). 
     69\end{description} 
     70All the relevant \textit{\_c1d} modules can be found in the NEMOGCM/NEMO/OPA\_SRC/C1D directory of  
    6471the \NEMO distribution. 
    6572 
  • trunk/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r3421 r3720  
    6767      !!              - 1D configuration, move Coriolis, u and v at T-point 
    6868      !!---------------------------------------------------------------------- 
    69       INTEGER ::   jk                ! dummy loop argument 
    70       INTEGER ::   iconf = 0         ! temporary integers 
    71       !!---------------------------------------------------------------------- 
    72       ! 
    73       IF( nn_timing == 1 )  CALL timing_start('dom_init') 
     69      INTEGER ::   jk          ! dummy loop argument 
     70      INTEGER ::   iconf = 0   ! local integers 
     71      !!---------------------------------------------------------------------- 
     72      ! 
     73      IF( nn_timing == 1 )   CALL timing_start('dom_init') 
    7474      ! 
    7575      IF(lwp) THEN 
     
    8686      IF( lk_vvl         )   CALL dom_vvl      ! Vertical variable mesh 
    8787      ! 
    88       IF( lk_c1d ) THEN                        ! 1D configuration  
    89          CALL cor_c1d                          ! Coriolis set at T-point 
    90          umask(:,:,:) = tmask(:,:,:)           ! U, V moved at T-point 
    91          vmask(:,:,:) = tmask(:,:,:) 
    92       END IF 
    93       ! 
    94       hu(:,:) = 0.e0                           ! Ocean depth at U- and V-points 
    95       hv(:,:) = 0.e0 
     88      IF( lk_c1d         )   CALL cor_c1d      ! 1D configuration: Coriolis set at T-point 
     89      ! 
     90      hu(:,:) = 0._wp                          ! Ocean depth at U- and V-points 
     91      hv(:,:) = 0._wp 
    9692      DO jk = 1, jpk 
    9793         hu(:,:) = hu(:,:) + fse3u(:,:,jk) * umask(:,:,jk) 
     
    9995      END DO 
    10096      !                                        ! Inverse of the local depth 
    101       hur(:,:) = 1. / ( hu(:,:) + 1.e0 - umask(:,:,1) ) * umask(:,:,1) 
    102       hvr(:,:) = 1. / ( hv(:,:) + 1.e0 - vmask(:,:,1) ) * vmask(:,:,1) 
     97      hur(:,:) = 1._wp / ( hu(:,:) + 1._wp - umask(:,:,1) ) * umask(:,:,1) 
     98      hvr(:,:) = 1._wp / ( hv(:,:) + 1._wp - vmask(:,:,1) ) * vmask(:,:,1) 
    10399 
    104100                             CALL dom_stp      ! time step 
     
    106102      IF( .NOT.ln_rstart )   CALL dom_ctl      ! Domain control 
    107103      ! 
    108       IF( nn_timing == 1 )  CALL timing_stop('dom_init') 
     104      IF( nn_timing == 1 )   CALL timing_stop('dom_init') 
    109105      ! 
    110106   END SUBROUTINE dom_init 
     
    292288         CALL mpp_maxloc( e2t(:,:), tmask(:,:,1), ze2max, iima2,ijma2 ) 
    293289      ELSE 
    294          ze1min = MINVAL( e1t(:,:), mask = tmask(:,:,1) == 1.e0 )     
    295          ze2min = MINVAL( e2t(:,:), mask = tmask(:,:,1) == 1.e0 )     
    296          ze1max = MAXVAL( e1t(:,:), mask = tmask(:,:,1) == 1.e0 )     
    297          ze2max = MAXVAL( e2t(:,:), mask = tmask(:,:,1) == 1.e0 )     
    298  
    299          iloc  = MINLOC( e1t(:,:), mask = tmask(:,:,1) == 1.e0 ) 
     290         ze1min = MINVAL( e1t(:,:), mask = tmask(:,:,1) == 1._wp )     
     291         ze2min = MINVAL( e2t(:,:), mask = tmask(:,:,1) == 1._wp )     
     292         ze1max = MAXVAL( e1t(:,:), mask = tmask(:,:,1) == 1._wp )     
     293         ze2max = MAXVAL( e2t(:,:), mask = tmask(:,:,1) == 1._wp )     
     294 
     295         iloc  = MINLOC( e1t(:,:), mask = tmask(:,:,1) == 1._wp ) 
    300296         iimi1 = iloc(1) + nimpp - 1 
    301297         ijmi1 = iloc(2) + njmpp - 1 
    302          iloc  = MINLOC( e2t(:,:), mask = tmask(:,:,1) == 1.e0 ) 
     298         iloc  = MINLOC( e2t(:,:), mask = tmask(:,:,1) == 1._wp ) 
    303299         iimi2 = iloc(1) + nimpp - 1 
    304300         ijmi2 = iloc(2) + njmpp - 1 
    305          iloc  = MAXLOC( e1t(:,:), mask = tmask(:,:,1) == 1.e0 ) 
     301         iloc  = MAXLOC( e1t(:,:), mask = tmask(:,:,1) == 1._wp ) 
    306302         iima1 = iloc(1) + nimpp - 1 
    307303         ijma1 = iloc(2) + njmpp - 1 
    308          iloc  = MAXLOC( e2t(:,:), mask = tmask(:,:,1) == 1.e0 ) 
     304         iloc  = MAXLOC( e2t(:,:), mask = tmask(:,:,1) == 1._wp ) 
    309305         iima2 = iloc(1) + nimpp - 1 
    310306         ijma2 = iloc(2) + njmpp - 1 
  • trunk/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90

    r3563 r3720  
    1515   !!            3.2  ! 2009-07  (R. Benshila) Suppression of rigid-lid option 
    1616   !!            3.3  ! 2010-11  (G. Madec) add mbk. arrays associated to the deepest ocean level 
    17    !!---------------------------------------------------------------------- 
     17   !!            3.4  ! 2012-12  (R. Bourdalle-Badie and G. Reffray)  modify C1D case   
     18  !!---------------------------------------------------------------------- 
    1819 
    1920   !!---------------------------------------------------------------------- 
     
    3839   USE lbclnk            ! ocean lateral boundary conditions (or mpp link) 
    3940   USE lib_mpp           ! distributed memory computing library 
    40    USE wrk_nemo        ! Memory allocation 
    41    USE timing          ! Timing 
     41   USE wrk_nemo          ! Memory allocation 
     42   USE timing            ! Timing 
    4243 
    4344   IMPLICIT NONE 
     
    7172      !!                ***  ROUTINE dom_zgr  *** 
    7273      !!                    
    73       !! ** Purpose :  set the depth of model levels and the resulting  
    74       !!      vertical scale factors. 
     74      !! ** Purpose :   set the depth of model levels and the resulting  
     75      !!              vertical scale factors. 
    7576      !! 
    7677      !! ** Method  : - reference 1D vertical coordinate (gdep._0, e3._0) 
     
    8485      !! ** Action  :   define gdep., e3., mbathy and bathy 
    8586      !!---------------------------------------------------------------------- 
    86       INTEGER ::   ioptio = 0   ! temporary integer 
     87      INTEGER ::   ioptio, ibat   ! local integer 
    8788      ! 
    8889      NAMELIST/namzgr/ ln_zco, ln_zps, ln_sco 
    8990      !!---------------------------------------------------------------------- 
    9091      ! 
    91       IF( nn_timing == 1 )  CALL timing_start('dom_zgr') 
     92      IF( nn_timing == 1 )   CALL timing_start('dom_zgr') 
    9293      ! 
    9394      REWIND( numnam )                 ! Read Namelist namzgr : vertical coordinate' 
     
    105106 
    106107      ioptio = 0                       ! Check Vertical coordinate options 
    107       IF( ln_zco ) ioptio = ioptio + 1 
    108       IF( ln_zps ) ioptio = ioptio + 1 
    109       IF( ln_sco ) ioptio = ioptio + 1 
     108      IF( ln_zco      )  ioptio = ioptio + 1 
     109      IF( ln_zps      )  ioptio = ioptio + 1 
     110      IF( ln_sco      )  ioptio = ioptio + 1 
    110111      IF( ioptio /= 1 )   CALL ctl_stop( ' none or several vertical coordinate options used' ) 
    111112      ! 
     
    114115                          CALL zgr_z            ! Reference z-coordinate system (always called) 
    115116                          CALL zgr_bat          ! Bathymetry fields (levels and meters) 
     117      IF( lk_c1d      )   CALL lbc_lnk( bathy , 'T', 1._wp )   ! 1D config.: same bathy value over the 3x3 domain 
    116118      IF( ln_zco      )   CALL zgr_zco          ! z-coordinate 
    117119      IF( ln_zps      )   CALL zgr_zps          ! Partial step z-coordinate 
    118120      IF( ln_sco      )   CALL zgr_sco          ! s-coordinate or hybrid z-s coordinate 
    119121      ! 
     122      ! 
    120123      ! final adjustment of mbathy & check  
    121124      ! ----------------------------------- 
    122125      IF( lzoom       )   CALL zgr_bat_zoom     ! correct mbathy in case of zoom subdomain 
    123       IF( .NOT.lk_c1d )   CALL zgr_bat_ctl      ! check bathymetry (mbathy) and suppress isoated ocean points 
     126      IF( .NOT.lk_c1d )   CALL zgr_bat_ctl      ! check bathymetry (mbathy) and suppress isolated ocean points 
    124127                          CALL zgr_bot_level    ! deepest ocean level for t-, u- and v-points 
    125128      ! 
    126       ! 
    127  
     129      IF( lk_c1d ) THEN                         ! 1D config.: same mbathy value over the 3x3 domain 
     130         ibat = mbathy(2,2) 
     131         mbathy(:,:) = ibat 
     132      END IF 
     133      ! 
    128134      IF( nprint == 1 .AND. lwp )   THEN 
    129135         WRITE(numout,*) ' MIN val mbathy ', MINVAL( mbathy(:,:) ), ' MAX ', MAXVAL( mbathy(:,:) ) 
     
    465471                    END DO 
    466472                 END DO 
    467                  IF(lwp) WRITE(numout,*) 
     473                 IF(lwp) WRITE(numout,*)      
    468474                 IF(lwp) WRITE(numout,*) '      orca_r2: Gibraltar strait open at i=',ii0,' j=',ij0 
    469475                 ! 
     
    502508      ENDIF 
    503509      ! 
     510      !  
    504511      CALL wrk_dealloc( jpidta, jpjdta, idta ) 
    505512      CALL wrk_dealloc( jpidta, jpjdta, zdta ) 
     
    729736      ! 
    730737      mbkt(:,:) = MAX( mbathy(:,:) , 1 )    ! bottom k-index of T-level (=1 over land) 
     738  
    731739      !                                     ! bottom k-index of W-level = mbkt+1 
    732740      DO jj = 1, jpjm1                      ! bottom k-index of u- (v-) level 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r3294 r3720  
    44   !! Input/Output manager :  Library to read input files 
    55   !!==================================================================== 
    6    !! History :  9.0  ! 05 12  (J. Belier) Original code 
    7    !!            9.0  ! 06 02  (S. Masson) Adaptation to NEMO 
    8    !!             "   ! 07 07  (D. Storkey) Changes to iom_gettime 
     6   !! History :  2.0  ! 2005-12  (J. Belier) Original code 
     7   !!            2.0  ! 2006-02  (S. Masson) Adaptation to NEMO 
     8   !!            3.0  ! 2007-07  (D. Storkey) Changes to iom_gettime 
     9   !!            3.4  ! 2012-12  (R. Bourdalle-Badie and G. Reffray)  add C1D case   
    910   !!-------------------------------------------------------------------- 
    10    !!gm  caution add !DIR nec: improved performance to be checked as well as no result changes 
    1111 
    1212   !!-------------------------------------------------------------------- 
     
    1919   !!-------------------------------------------------------------------- 
    2020   USE dom_oce         ! ocean space and time domain 
     21   USE c1d             ! 1D vertical configuration 
    2122   USE flo_oce         ! floats module declarations 
    2223   USE lbclnk          ! lateal boundary condition / mpp exchanges 
     
    751752            ENDIF 
    752753             
     754            ! C1D case : always call lbc_lnk to replicate the central value over the whole 3X3 domain 
     755            IF( lk_c1d .AND. PRESENT(pv_r2d) )   CALL lbc_lnk( pv_r2d,'Z',1. ) 
     756            IF( lk_c1d .AND. PRESENT(pv_r3d) )   CALL lbc_lnk( pv_r3d,'Z',1. ) 
     757     
    753758            !--- Apply scale_factor and offset 
    754759            zscf = iom_file(kiomid)%scf(idvar)      ! scale factor 
  • trunk/NEMOGCM/NEMO/OPA_SRC/LBC/lbclnk.F90

    r2442 r3720  
    77   !!   NEMO     1.0  ! 2002-09  (G. Madec)     F90: Free form and module 
    88   !!            3.2  ! 2009-03  (R. Benshila)  External north fold treatment   
    9    !!---------------------------------------------------------------------- 
    10 #if   defined key_mpp_mpi 
     9   !!            3.4  ! 2012-12  (R. Bourdalle-Badie and G. Reffray)  add a C1D case   
     10   !!---------------------------------------------------------------------- 
     11#if defined key_mpp_mpi 
    1112   !!---------------------------------------------------------------------- 
    1213   !!   'key_mpp_mpi'             MPI massively parallel processing library 
     
    6768   !!---------------------------------------------------------------------- 
    6869CONTAINS 
     70 
     71# if defined key_c1d 
     72   !!---------------------------------------------------------------------- 
     73   !!   'key_c1d'                                          1D configuration 
     74   !!---------------------------------------------------------------------- 
     75 
     76   SUBROUTINE lbc_lnk_3d_gather( pt3d1, cd_type1, pt3d2, cd_type2, psgn ) 
     77      !!--------------------------------------------------------------------- 
     78      !!                  ***  ROUTINE lbc_lnk_3d_gather  *** 
     79      !! 
     80      !! ** Purpose :   set lateral boundary conditions on two 3D arrays (C1D case) 
     81      !! 
     82      !! ** Method  :   call lbc_lnk_3d on pt3d1 and pt3d2 
     83      !!---------------------------------------------------------------------- 
     84      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type1, cd_type2   ! nature of pt3d grid-points 
     85      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pt3d1   , pt3d2      ! 3D array on which the lbc is applied 
     86      REAL(wp)                        , INTENT(in   ) ::   psgn                 ! control of the sign  
     87      !!---------------------------------------------------------------------- 
     88      ! 
     89      CALL lbc_lnk_3d( pt3d1, cd_type1, psgn) 
     90      CALL lbc_lnk_3d( pt3d2, cd_type2, psgn) 
     91      ! 
     92   END SUBROUTINE lbc_lnk_3d_gather 
     93 
     94 
     95   SUBROUTINE lbc_lnk_3d( pt3d, cd_type, psgn, cd_mpp, pval ) 
     96      !!--------------------------------------------------------------------- 
     97      !!                  ***  ROUTINE lbc_lnk_3d  *** 
     98      !! 
     99      !! ** Purpose :   set lateral boundary conditions on a 3D array (C1D case) 
     100      !! 
     101      !! ** Method  :   1D case, the central water column is set everywhere 
     102      !!---------------------------------------------------------------------- 
     103      CHARACTER(len=1)                , INTENT(in   )           ::   cd_type   ! nature of pt3d grid-points 
     104      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout)           ::   pt3d      ! 3D array on which the lbc is applied 
     105      REAL(wp)                        , INTENT(in   )           ::   psgn      ! control of the sign  
     106      CHARACTER(len=3)                , INTENT(in   ), OPTIONAL ::   cd_mpp    ! MPP only (here do nothing) 
     107      REAL(wp)                        , INTENT(in   ), OPTIONAL ::   pval      ! background value (for closed boundaries) 
     108      ! 
     109      INTEGER  ::   jk     ! dummy loop index 
     110      REAL(wp) ::   ztab   ! local scalar 
     111      !!---------------------------------------------------------------------- 
     112      ! 
     113      DO jk = 1, jpk 
     114         ztab = pt3d(2,2,jk) 
     115         pt3d(:,:,jk) = ztab 
     116      END DO 
     117      ! 
     118   END SUBROUTINE lbc_lnk_3d 
     119 
     120 
     121   SUBROUTINE lbc_lnk_2d( pt2d, cd_type, psgn, cd_mpp, pval ) 
     122      !!--------------------------------------------------------------------- 
     123      !!                 ***  ROUTINE lbc_lnk_2d  *** 
     124      !! 
     125      !! ** Purpose :   set lateral boundary conditions on a 2D array (non mpp case) 
     126      !! 
     127      !! ** Method  :   1D case, the central water column is set everywhere 
     128      !!---------------------------------------------------------------------- 
     129      CHARACTER(len=1)            , INTENT(in   )           ::   cd_type   ! nature of pt3d grid-points 
     130      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout)           ::   pt2d      ! 2D array on which the lbc is applied 
     131      REAL(wp)                    , INTENT(in   )           ::   psgn      ! control of the sign  
     132      CHARACTER(len=3)            , INTENT(in   ), OPTIONAL ::   cd_mpp    ! MPP only (here do nothing) 
     133      REAL(wp)                    , INTENT(in   ), OPTIONAL ::   pval      ! background value (for closed boundaries) 
     134      ! 
     135      REAL(wp) ::   ztab   ! local scalar 
     136      !!---------------------------------------------------------------------- 
     137      ! 
     138      ztab = pt2d(2,2) 
     139      pt2d(:,:) = ztab 
     140      ! 
     141   END SUBROUTINE lbc_lnk_2d 
     142 
     143#else 
     144   !!---------------------------------------------------------------------- 
     145   !!   Default option                           3D shared memory computing 
     146   !!---------------------------------------------------------------------- 
    69147 
    70148   SUBROUTINE lbc_lnk_3d_gather( pt3d1, cd_type1, pt3d2, cd_type2, psgn ) 
     
    113191 
    114192      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value (zero by default) 
    115       ELSE                         ;   zland = 0.e0 
     193      ELSE                         ;   zland = 0._wp 
    116194      ENDIF 
    117195 
     
    203281 
    204282      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value (zero by default) 
    205       ELSE                         ;   zland = 0.e0 
     283      ELSE                         ;   zland = 0._wp 
    206284      ENDIF 
    207285 
     
    270348   END SUBROUTINE lbc_lnk_2d 
    271349 
     350# endif 
    272351#endif 
    273352 
Note: See TracChangeset for help on using the changeset viewer.