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 5086 for branches/2014/dev_r4650_UKMO3_masked_damping/NEMOGCM/TOOLS/SIREN/src/vgrid.f90 – NEMO

Ignore:
Timestamp:
2015-02-17T10:06:39+01:00 (9 years ago)
Author:
timgraham
Message:

Merged head of trunk into branch in preparation for putting code back onto the trunk
In working copy ran the command:
svn merge svn+sshtimgraham@…/ipsl/forge/projets/nemo/svn/trunk

Also recompiled NEMO_book.pdf with merged input files

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4650_UKMO3_masked_damping/NEMOGCM/TOOLS/SIREN/src/vgrid.f90

    r4213 r5086  
    66! 
    77! DESCRIPTION: 
    8 !> @brief vertical grid manager <br/> 
     8!> @brief This module manage vertical grid. 
    99!> 
    1010!> @details 
     11!>    to set the depth of model levels and the resulting vertical scale 
     12!> factors:<br/> 
     13!> @code 
     14!>    CALL vgrid_zgr_z(dd_gdepw(:), dd_gdept(:), dd_e3w(:), dd_e3t(:),  
     15!>                     dd_ppkth, dd_ppkth2, dd_ppacr, dd_ppacr2,  
     16!>                     dd_ppdzmin, dd_pphmax, dd_pp_to_be_computed,  
     17!>                     dd_ppa0, dd_ppa1, dd_ppa2, dd_ppsur) 
     18!> @endcode 
     19!>       - dd_gdepw is array of depth value on W point 
     20!>       - dd_gdept is array of depth value on T point 
     21!>       - dd_e3w   is array of vertical mesh size on W point 
     22!>       - dd_e3t   is array of vertical mesh size on T point 
     23!>       - dd_ppkth              see NEMO documentation 
     24!>       - dd_ppkth2             see NEMO documentation 
     25!>       - dd_ppacr              see NEMO documentation 
     26!>       - dd_ppdzmin            see NEMO documentation 
     27!>       - dd_pphmax             see NEMO documentation 
     28!>       - dd_pp_to_be_computed  see NEMO documentation 
     29!>       - dd_ppa1               see NEMO documentation 
     30!>       - dd_ppa2               see NEMO documentation 
     31!>       - dd_ppa0               see NEMO documentation 
     32!>       - dd_ppsur              see NEMO documentation 
     33!>     
    1134!>  
     35!>    to set the depth and vertical scale factor in partial step z-coordinate 
     36!>  case:<br/> 
     37!> @code 
     38!>    CALL vgrid_zgr_zps(id_mbathy(:,:), dd_bathy(:,:), id_jpkmax, dd_gdepw(:),  
     39!>                       dd_e3t(:), dd_e3zps_min, dd_e3zps_rat) 
     40!> @endcode 
     41!>       - id_mbathy is array of bathymetry level 
     42!>       - dd_bathy  is array of bathymetry 
     43!>       - id_jpkmax is the maximum number of level to be used 
     44!>       - dd_gdepw  is array of vertical mesh size on W point 
     45!>       - dd_e3t    is array of vertical mesh size on T point 
     46!>       - dd_e3zps_min    see NEMO documentation 
     47!>       - dd_e3zps_rat    see NEMO documentation 
     48!> 
     49!>    to check the bathymetry in levels:<br/> 
     50!> @code 
     51!>    CALL vgrid_zgr_bat_ctl(id_mbathy, id_jpkmax, id_jpk) 
     52!> @endcode 
     53!>       - id_mbathy is array of bathymetry level 
     54!>       - id_jpkmax is the maximum number of level to be used 
     55!>       - id_jpk    is the number of level 
     56!>    
     57!>    to compute bathy level in T,U,V,F point from  Bathymetry file:<br/> 
     58!> @code 
     59!>    tl_level(:)=vgrid_get_level(td_bathy, [cd_namelist,] [td_dom,] [id_nlevel]) 
     60!> @endcode 
     61!>       - td_bathy is Bathymetry file structure 
     62!>       - cd_namelist is namelist [optional] 
     63!>       - td_dom is domain structure [optional] 
     64!>       - id_nlevel is number of lelvel to be used [optional] 
     65!>     
    1266!> @author 
    1367!> J.Paul 
    1468! REVISION HISTORY: 
    15 !> @date Nov, 2013 - Initial Version 
    16 ! 
     69!> @date November, 2013 - Initial Version 
     70!> @date Spetember, 2014 
     71!> - add header 
     72!> 
    1773!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    18 !> @todo 
    1974!---------------------------------------------------------------------- 
    2075MODULE vgrid 
    21    USE netcdf 
     76   USE netcdf                          ! nf90 library 
    2277   USE kind                            ! F90 kind parameter 
    2378   USE fct                             ! basic usefull function 
    2479   USE global                          ! global parameter 
    2580   USE phycst                          ! physical constant 
    26    USE logger                             ! log file manager 
     81   USE logger                          ! log file manager 
    2782   USE file                            ! file manager 
    2883   USE var                             ! variable manager 
    2984   USE dim                             ! dimension manager 
    3085   USE dom                             ! domain manager 
     86   USE grid                            ! grid manager 
    3187   USE iom                             ! I/O manager 
    3288   USE mpp                             ! MPP manager 
    3389   USE iom_mpp                         ! I/O MPP manager 
    3490   IMPLICIT NONE 
    35    PRIVATE 
    3691   ! NOTE_avoid_public_variables_if_possible 
    3792 
     
    4398   PUBLIC :: vgrid_zgr_bat_ctl 
    4499   PUBLIC :: vgrid_get_level 
    45  
    46 !   PRIVATE ::  
    47  
    48100 
    49101CONTAINS 
     
    86138   !> @param[in] dd_ppsur 
    87139   !------------------------------------------------------------------- 
    88    !> @code 
    89140   SUBROUTINE vgrid_zgr_z( dd_gdepw, dd_gdept, dd_e3w, dd_e3t,          & 
    90141   &                       dd_ppkth, dd_ppkth2, dd_ppacr, dd_ppacr2,    & 
     
    218269 
    219270   END SUBROUTINE vgrid_zgr_z 
    220    !> @endcode 
    221271   !------------------------------------------------------------------- 
    222272   !> @brief This subroutine set the depth and vertical scale factor in partial step 
     
    231281   !>      function the derivative of which gives the reference vertical 
    232282   !>      scale factors. 
    233    !>        From  depth and scale factors reference, we compute there new value 
     283   !>      From  depth and scale factors reference, we compute there new value 
    234284   !>      with partial steps  on 3d arrays ( i, j, k ). 
    235285   !> 
    236    !>              w-level: gdepw_ps(i,j,k)  = fsdep(k) 
    237    !>                       e3w_ps(i,j,k) = dk(fsdep)(k)     = fse3(i,j,k) 
    238    !>              t-level: gdept_ps(i,j,k)  = fsdep(k+0.5) 
    239    !>                       e3t_ps(i,j,k) = dk(fsdep)(k+0.5) = fse3(i,j,k+0.5) 
    240    !> 
    241    !>        With the help of the bathymetric file ( bathymetry_depth_ORCA_R2.nc), 
     286   !>      w-level:  
     287   !>          - gdepw_ps(i,j,k)  = fsdep(k) 
     288   !>          - e3w_ps(i,j,k) = dk(fsdep)(k)     = fse3(i,j,k) 
     289   !>      t-level:  
     290   !>          - gdept_ps(i,j,k)  = fsdep(k+0.5) 
     291   !>          - e3t_ps(i,j,k) = dk(fsdep)(k+0.5) = fse3(i,j,k+0.5) 
     292   !> 
     293   !>      With the help of the bathymetric file ( bathymetry_depth_ORCA_R2.nc), 
    242294   !>      we find the mbathy index of the depth at each grid point. 
    243295   !>      This leads us to three cases: 
    244    !> 
    245    !>              - bathy = 0 => mbathy = 0 
    246    !>              - 1 < mbathy < jpkm1     
    247    !>              - bathy > gdepw(jpk) => mbathy = jpkm1   
    248    !> 
    249    !>        Then, for each case, we find the new depth at t- and w- levels 
     296   !>          - bathy = 0 => mbathy = 0 
     297   !>          - 1 < mbathy < jpkm1     
     298   !>          - bathy > gdepw(jpk) => mbathy = jpkm1   
     299   !> 
     300   !>      Then, for each case, we find the new depth at t- and w- levels 
    250301   !>      and the new vertical scale factors at t-, u-, v-, w-, uw-, vw-  
    251302   !>      and f-points. 
     
    257308   !>      schemes. 
    258309   !> 
    259    !>         c a u t i o n : gdept, gdepw and e3 are positives 
    260    !>         - - - - - - -   gdept_ps, gdepw_ps and e3_ps are positives 
     310   !>  @warning  
     311   !>         - gdept, gdepw and e3 are positives 
     312   !>         - gdept_ps, gdepw_ps and e3_ps are positives 
    261313   ! 
    262314   !> @author A. Bozec, G. Madec 
     
    274326   !> @param[in] dd_e3zps_rat 
    275327   !------------------------------------------------------------------- 
    276    !> @code 
    277328   SUBROUTINE vgrid_zgr_zps( id_mbathy, dd_bathy, id_jpkmax, & 
    278329   &                         dd_gdepw, dd_e3t,               & 
     
    362413 
    363414   END SUBROUTINE vgrid_zgr_zps 
    364    !> @endcode 
    365415   !------------------------------------------------------------------- 
    366416   !> @brief This subroutine check the bathymetry in levels  
     
    386436   !> - 03-08 Original code 
    387437   ! 
    388    !> @param[in]  
     438   !> @param[in] id_mbathy  
     439   !> @param[in] id_jpkmax 
     440   !> @param[in] id_jpk 
    389441   !------------------------------------------------------------------- 
    390    !> @code 
    391442   SUBROUTINE vgrid_zgr_bat_ctl( id_mbathy, id_jpkmax, id_jpk) 
    392443      IMPLICIT NONE 
     
    477528 
    478529   END SUBROUTINE vgrid_zgr_bat_ctl 
    479    !> @endcode 
    480530   !------------------------------------------------------------------- 
    481    !> @brief This function  
     531   !> @brief This function compute bathy level in T,U,V,F point, and return  
     532   !> them as array of variable structure 
    482533   ! 
    483534   !> @details 
     535   !> Bathymetry is read on Bathymetry file, then bathy level is computed  
     536   !> on T point, and finally fit to U,V,F point. 
     537   !> 
     538   !> you could specify :<br/> 
     539   !> - namelist where find parameter to set the depth of model levels 
     540   !> (default use GLORYS 75 levels parameters) 
     541   !> - domain structure to specify on e area to work on 
     542   !> - number of level to be used 
     543   !> 
     544   !> @author J.Paul 
     545   !> - November, 2013- Initial Version 
    484546   ! 
    485    !> @author J.Paul 
    486    !> - Nov, 2013- Initial Version 
    487    ! 
    488    !> @param[in]  
     547   !> @param[in] td_bathy     Bathymetry file structure  
     548   !> @param[in] cd_namelist  namelist  
     549   !> @param[in] td_dom       domain structure 
     550   !> @param[in] id_nlevel    number of lelvel to be used  
     551   !> @return array of level on T,U,V,F point (variable structure) 
    489552   !------------------------------------------------------------------- 
    490    !> @code 
    491553   FUNCTION vgrid_get_level(td_bathy, cd_namelist, td_dom, id_nlevel) 
    492554      IMPLICIT NONE 
    493555      ! Argument 
    494       TYPE(TFILE)     , INTENT(IN) :: td_bathy 
    495       CHARACTER(LEN=*), INTENT(IN) :: cd_namelist 
     556      TYPE(TMPP)      , INTENT(IN) :: td_bathy 
     557      CHARACTER(LEN=*), INTENT(IN), OPTIONAL :: cd_namelist 
    496558      TYPE(TDOM)      , INTENT(IN), OPTIONAL :: td_dom 
    497559      INTEGER(i4)     , INTENT(IN), OPTIONAL :: id_nlevel 
    498560 
    499561      ! function 
    500       TYPE(TVAR), DIMENSION(ig_npoint) :: vgrid_get_level 
     562      TYPE(TVAR), DIMENSION(ip_npoint) :: vgrid_get_level 
    501563 
    502564      ! local variable 
    503       TYPE(TFILE) :: tl_bathy 
    504       TYPE(TMPP)  :: tl_mppbathy 
    505  
    506       TYPE(TDOM)  :: tl_dom 
    507  
    508       TYPE(TVAR)  :: tl_var 
    509       TYPE(TVAR) , DIMENSION(ig_npoint)            :: tl_level 
    510  
    511       TYPE(TDIM) , DIMENSION(ip_maxdim)            :: tl_dim 
    512  
    513565      REAL(dp)   , DIMENSION(:)      , ALLOCATABLE :: dl_gdepw  
    514566      REAL(dp)   , DIMENSION(:)      , ALLOCATABLE :: dl_gdept  
     
    519571      INTEGER(i4)                                  :: il_fileid 
    520572      INTEGER(i4)                                  :: il_jpkmax 
     573      INTEGER(i4), DIMENSION(2,2)                  :: il_xghost 
    521574      INTEGER(i4), DIMENSION(:,:)    , ALLOCATABLE :: il_mbathy 
    522575      INTEGER(i4), DIMENSION(:,:,:,:), ALLOCATABLE :: il_level 
    523576       
    524577      LOGICAL                                      :: ll_exist 
     578 
     579      TYPE(TDIM) , DIMENSION(ip_maxdim)            :: tl_dim 
     580 
     581      TYPE(TDOM)                                   :: tl_dom 
     582 
     583      TYPE(TVAR)                                   :: tl_var 
     584 
     585      TYPE(TMPP)                                   :: tl_bathy 
    525586 
    526587      ! loop indices 
     
    567628      !---------------------------------------------------------------- 
    568629 
    569       !1- read namelist 
    570       INQUIRE(FILE=TRIM(cd_namelist), EXIST=ll_exist) 
    571       IF( ll_exist )THEN 
     630      IF( PRESENT(cd_namelist) )THEN 
     631         !1- read namelist 
     632         INQUIRE(FILE=TRIM(cd_namelist), EXIST=ll_exist) 
     633         IF( ll_exist )THEN 
    572634  
    573          il_fileid=fct_getunit() 
    574  
    575          OPEN( il_fileid, FILE=TRIM(cd_namelist), & 
    576          &                FORM='FORMATTED',       & 
    577          &                ACCESS='SEQUENTIAL',    & 
    578          &                STATUS='OLD',           & 
    579          &                ACTION='READ',          & 
    580          &                IOSTAT=il_status) 
    581          CALL fct_err(il_status) 
    582          IF( il_status /= 0 )THEN 
    583             CALL logger_fatal("VGRID GET LEVEL: ERROR opening "//TRIM(cd_namelist)) 
     635            il_fileid=fct_getunit() 
     636 
     637            OPEN( il_fileid, FILE=TRIM(cd_namelist), & 
     638            &                FORM='FORMATTED',       & 
     639            &                ACCESS='SEQUENTIAL',    & 
     640            &                STATUS='OLD',           & 
     641            &                ACTION='READ',          & 
     642            &                IOSTAT=il_status) 
     643            CALL fct_err(il_status) 
     644            IF( il_status /= 0 )THEN 
     645               CALL logger_fatal("VGRID GET LEVEL: ERROR opening "//& 
     646               &  TRIM(cd_namelist)) 
     647            ENDIF 
     648 
     649            READ( il_fileid, NML = namzgr ) 
     650            READ( il_fileid, NML = namzps ) 
     651 
     652            CLOSE( il_fileid, IOSTAT=il_status ) 
     653            CALL fct_err(il_status) 
     654            IF( il_status /= 0 )THEN 
     655               CALL logger_error("VGRID GET LEVELL: ERROR closing "//& 
     656               &  TRIM(cd_namelist)) 
     657            ENDIF 
     658 
     659         ELSE 
     660 
     661            CALL logger_fatal("VGRID GET LEVEL: ERROR. can not find "//& 
     662            &  TRIM(cd_namelist)) 
     663 
    584664         ENDIF 
    585  
    586          READ( il_fileid, NML = namzgr ) 
    587          READ( il_fileid, NML = namzps ) 
    588  
    589          CLOSE( il_fileid, IOSTAT=il_status ) 
    590          CALL fct_err(il_status) 
    591          IF( il_status /= 0 )THEN 
    592             CALL logger_error("VGRID GET LEVELL: ERROR closing "//TRIM(cd_namelist)) 
    593          ENDIF 
    594  
     665      ENDIF 
     666 
     667      ! copy structure 
     668      tl_bathy=mpp_copy(td_bathy) 
     669 
     670      ! get domain 
     671      IF( PRESENT(td_dom) )THEN 
     672         tl_dom=dom_copy(td_dom) 
    595673      ELSE 
    596  
    597          CALL logger_fatal("VGRID GET LEVEL: ERROR. can not find "//TRIM(cd_namelist)) 
    598  
    599       ENDIF 
    600  
    601       !2- open files 
    602       tl_bathy=td_bathy 
    603       !2-1 get domain 
    604       IF( PRESENT(td_dom) )THEN 
    605          tl_dom=td_dom 
    606       ELSE 
    607          CALL iom_open(tl_bathy) 
    608  
    609674         CALL logger_debug("VGRID GET LEVEL: get dom from "//& 
    610675         &  TRIM(tl_bathy%c_name)) 
    611676         tl_dom=dom_init(tl_bathy) 
    612  
    613          CALL iom_close(tl_bathy) 
    614677      ENDIF 
    615678 
    616       !2-2 open mpp  
    617       tl_mppbathy=mpp_init(tl_bathy) 
    618       CALL file_clean(tl_bathy) 
    619  
    620       !2-3 get processor to be used 
    621       CALL mpp_get_use( tl_mppbathy, tl_dom ) 
    622  
    623       !2-4 open mpp files 
    624       CALL iom_mpp_open(tl_mppbathy) 
    625  
    626       !3- check namelist 
     679      ! get ghoste cell 
     680      il_xghost(:,:)=grid_get_ghost(tl_bathy) 
     681 
     682      ! open mpp files 
     683      CALL iom_dom_open(tl_bathy, tl_dom) 
     684 
     685      ! check namelist 
    627686      IF( PRESENT(id_nlevel) ) in_nlevel=id_nlevel 
    628687      IF( in_nlevel == 0 )THEN 
     
    631690      ENDIF 
    632691 
    633       !4- read bathymetry 
    634       tl_var=iom_mpp_read_var(tl_mppbathy,'bathymetry',td_dom=tl_dom) 
    635  
     692      ! read bathymetry 
     693      tl_var=iom_dom_read_var(tl_bathy,'bathymetry',tl_dom) 
     694      ! clean 
     695      CALL dom_clean(tl_dom) 
     696 
     697      ! remove ghost cell 
     698      CALL grid_del_ghost(tl_var, il_xghost(:,:)) 
     699 
     700      ! force _FillValue (land) to be 0 
    636701      WHERE( tl_var%d_value(:,:,1,1) == tl_var%d_fill ) 
    637702         tl_var%d_value(:,:,1,1)=0 
    638703      END WHERE 
    639704 
    640       !5 clean 
    641       CALL iom_mpp_close(tl_mppbathy) 
    642       CALL mpp_clean(tl_mppbathy) 
    643  
    644       !5- compute vertical grid 
     705      ! clean 
     706      CALL iom_dom_close(tl_bathy) 
     707      CALL mpp_clean(tl_bathy) 
     708 
     709      ! compute vertical grid 
    645710      ALLOCATE( dl_gdepw(in_nlevel), dl_gdept(in_nlevel) )  
    646711      ALLOCATE(   dl_e3w(in_nlevel),   dl_e3t(in_nlevel) )  
     
    650715      &                 dn_ppa0, dn_ppa1, dn_ppa2, dn_ppsur ) 
    651716 
    652       !6- compute bathy level on T point 
     717      ! compute bathy level on T point 
    653718      ALLOCATE( il_mbathy(tl_var%t_dim(1)%i_len, & 
    654719      &                   tl_var%t_dim(2)%i_len ) ) 
     
    660725      DEALLOCATE(   dl_e3w,   dl_e3t ) 
    661726 
    662       !7- compute bathy level in T,U,V,F point 
     727      ! compute bathy level in T,U,V,F point 
    663728      ALLOCATE( il_level(tl_var%t_dim(1)%i_len, & 
    664729      &                  tl_var%t_dim(2)%i_len, & 
    665       &                  ig_npoint,1) ) 
     730      &                  ip_npoint,1) ) 
    666731 
    667732      DO jj=1,tl_var%t_dim(2)%i_len 
     
    686751      DEALLOCATE( il_mbathy ) 
    687752 
    688       tl_dim(:)=tl_var%t_dim(:) 
     753      tl_dim(:)=dim_copy(tl_var%t_dim(:)) 
     754      ! clean 
    689755      CALL var_clean(tl_var) 
    690756 
     
    692758      tl_dim(3:4)%l_use=.FALSE. 
    693759 
    694       tl_level(jp_T)=var_init('tlevel',il_level(:,:,jp_T:jp_T,:),td_dim=tl_dim(:)) 
    695       tl_level(jp_U)=var_init('ulevel',il_level(:,:,jp_U:jp_U,:),td_dim=tl_dim(:)) 
    696       tl_level(jp_V)=var_init('vlevel',il_level(:,:,jp_V:jp_V,:),td_dim=tl_dim(:)) 
    697       tl_level(jp_F)=var_init('flevel',il_level(:,:,jp_F:jp_F,:),td_dim=tl_dim(:)) 
     760      vgrid_get_level(jp_T)=var_init( 'tlevel', il_level(:,:,jp_T:jp_T,:), & 
     761      &                                td_dim=tl_dim(:) ) 
     762      vgrid_get_level(jp_U)=var_init( 'ulevel', il_level(:,:,jp_U:jp_U,:), & 
     763      &                                td_dim=tl_dim(:)) 
     764      vgrid_get_level(jp_V)=var_init( 'vlevel', il_level(:,:,jp_V:jp_V,:), & 
     765      &                                td_dim=tl_dim(:)) 
     766      vgrid_get_level(jp_F)=var_init( 'flevel', il_level(:,:,jp_F:jp_F,:), & 
     767      &                                td_dim=tl_dim(:)) 
    698768 
    699769      DEALLOCATE( il_level ) 
    700770 
    701       ! save result 
    702       vgrid_get_level(:)=tl_level(:) 
    703  
    704       DO ji=1,ig_npoint 
    705          CALL var_clean(tl_level(ji)) 
    706       ENDDO 
     771      CALL grid_add_ghost( vgrid_get_level(jp_T), il_xghost(:,:) ) 
     772      CALL grid_add_ghost( vgrid_get_level(jp_U), il_xghost(:,:) ) 
     773      CALL grid_add_ghost( vgrid_get_level(jp_V), il_xghost(:,:) ) 
     774      CALL grid_add_ghost( vgrid_get_level(jp_F), il_xghost(:,:) ) 
     775 
     776      ! clean 
     777      CALL dim_clean(tl_dim(:)) 
    707778 
    708779   END FUNCTION vgrid_get_level 
    709    !> @endcode 
    710 !   !------------------------------------------------------------------- 
    711 !   !> @brief This function  
    712 !   ! 
    713 !   !> @details 
    714 !   ! 
    715 !   !> @author J.Paul 
    716 !   !> - Nov, 2013- Initial Version 
    717 !   ! 
    718 !   !> @param[in]  
    719 !   !------------------------------------------------------------------- 
    720 !   !> @code 
    721 !   FUNCTION vgrid_() 
    722 !      IMPLICIT NONE 
    723 !      ! Argument       
    724 !      ! function 
    725 !      ! local variable 
    726 !      ! loop indices 
    727 !      !---------------------------------------------------------------- 
    728 ! 
    729 !   END FUNCTION vgrid_ 
    730 !   !> @endcode 
    731 !   !------------------------------------------------------------------- 
    732 !   !> @brief This subroutine  
    733 !   ! 
    734 !   !> @details 
    735 !   ! 
    736 !   !> @author J.Paul 
    737 !   !> - Nov, 2013- Initial Version 
    738 !   ! 
    739 !   !> @param[in]  
    740 !   !------------------------------------------------------------------- 
    741 !   !> @code 
    742 !   SUBROUTINE vgrid_() 
    743 !      IMPLICIT NONE 
    744 !      ! Argument       
    745 !      ! local variable 
    746 !      ! loop indices 
    747 !      !---------------------------------------------------------------- 
    748 ! 
    749 !   END SUBROUTINE vgrid_ 
    750 !   !> @endcode 
    751780END MODULE vgrid 
    752781 
Note: See TracChangeset for help on using the changeset viewer.