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 6436 for branches/UKMO/nemo_v3_6_STABLE_copy/NEMOGCM/TOOLS/SIREN/src/create_restart.f90 – NEMO

Ignore:
Timestamp:
2016-04-07T15:33:32+02:00 (8 years ago)
Author:
timgraham
Message:

Updated to r6424 of nemo_v3_6_STABLE

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/nemo_v3_6_STABLE_copy/NEMOGCM/TOOLS/SIREN/src/create_restart.f90

    r5783 r6436  
    99!> @file 
    1010!> @brief  
    11 !> This program create restart file. 
     11!> This program creates restart file. 
    1212!> 
    1313!> @details 
    1414!> @section sec1 method 
    1515!> Variables could be extracted from fine grid file, interpolated from coarse 
    16 !> grid file or restart file, or manually written.<br/>  
    17 !> Then they are split over new decomposition.  
     16!> grid file or restart file. Variables could also be manually written.<br/>  
     17!> Then they are split over new layout.  
    1818!> @note  
    1919!>    method could be different for each variable. 
     
    2828!>    you could find a template of the namelist in templates directory. 
    2929!> 
    30 !>    create_restart.nam comprise 9 namelists:<br/> 
     30!>    create_restart.nam contains 9 namelists:<br/> 
    3131!>       - logger namelist (namlog) 
    3232!>       - config namelist (namcfg) 
     
    3939!>       - output namelist (namout) 
    4040!>     
    41 !>    @note  
    42 !>       All namelists have to be in file create_restart.nam  
    43 !>       however variables of those namelists are all optional. 
    44 !> 
    4541!>    * _logger namelist (namlog)_:<br/> 
    4642!>       - cn_logfile   : log filename 
     
    5248!>       - cn_varcfg : variable configuration file 
    5349!> (see ./SIREN/cfg/variable.cfg) 
     50!>       - cn_dumcfg : useless (dummy) configuration file, for useless  
     51!> dimension or variable (see ./SIREN/cfg/dummy.cfg). 
    5452!> 
    5553!>    * _coarse grid namelist (namcrs):<br/> 
     
    8280!> 
    8381!>    * _variable namelist (namvar)_:<br/> 
    84 !>       - cn_varinfo : list of variable and extra information about request(s)  
    85 !>       to be used.<br/> 
    86 !>          each elements of *cn_varinfo* is a string character 
    87 !>          (separated by ',').<br/> 
    88 !>          it is composed of the variable name follow by ':',  
    89 !>          then request(s) to be used on this variable.<br/>  
    90 !>          request could be: 
    91 !>             - int = interpolation method 
    92 !>             - ext = extrapolation method 
    93 !>             - flt = filter method 
    94 !>             - min = minimum value 
    95 !>             - max = maximum value 
    96 !>             - unt = new units 
    97 !>             - unf = unit scale factor (linked to new units) 
    98 !> 
    99 !>             requests must be separated by ';'.<br/> 
    100 !>             order of requests does not matter.<br/> 
    101 !> 
    102 !>          informations about available method could be find in @ref interp, 
    103 !>          @ref extrap and @ref filter.<br/> 
    104 !>          Example: 'votemper: int=linear; flt=hann; ext=dist_weight','vosaline: int=cubic' 
    105 !>          @note  
    106 !>             If you do not specify a method which is required,  
    107 !>             default one is apply. 
    108 !>       - cn_varfile : list of variable, and corresponding file<br/>  
     82!>       - cn_varfile : list of variable, and associated file<br/>  
    10983!>          *cn_varfile* is the path and filename of the file where find 
    11084!>          variable.<br/> 
     
    131105!>             - 'all:restart.dimg' 
    132106!> 
     107!>       - cn_varinfo : list of variable and extra information about request(s)  
     108!>       to be used.<br/> 
     109!>          each elements of *cn_varinfo* is a string character 
     110!>          (separated by ',').<br/> 
     111!>          it is composed of the variable name follow by ':',  
     112!>          then request(s) to be used on this variable.<br/>  
     113!>          request could be: 
     114!>             - int = interpolation method 
     115!>             - ext = extrapolation method 
     116!>             - flt = filter method 
     117!>             - min = minimum value 
     118!>             - max = maximum value 
     119!>             - unt = new units 
     120!>             - unf = unit scale factor (linked to new units) 
     121!> 
     122!>             requests must be separated by ';'.<br/> 
     123!>             order of requests does not matter.<br/> 
     124!> 
     125!>          informations about available method could be find in @ref interp, 
     126!>          @ref extrap and @ref filter.<br/> 
     127!>          Example: 'votemper: int=linear; flt=hann; ext=dist_weight', 
     128!>                   'vosaline: int=cubic' 
     129!>          @note  
     130!>             If you do not specify a method which is required,  
     131!>             default one is apply. 
     132!> 
    133133!>    * _nesting namelist (namnst)_:<br/> 
    134134!>       - in_rhoi  : refinement factor in i-direction 
    135135!>       - in_rhoj  : refinement factor in j-direction 
    136136!>       @note  
    137 !>          coarse grid indices will be deduced from fine grid 
     137!>          coarse grid indices will be computed from fine grid 
    138138!>          coordinate file. 
    139139!> 
     
    141141!>       - cn_fileout : output file 
    142142!>       - ln_extrap : extrapolate land point or not 
    143 !>       - in_niproc : i-direction number of processor 
    144 !>       - in_njproc : j-direction numebr of processor 
     143!>       - in_niproc : number of processor in i-direction 
     144!>       - in_njproc : number of processor in j-direction 
    145145!>       - in_nproc  : total number of processor to be used 
    146146!>       - cn_type   : output format ('dimg', 'cdf') 
     
    156156!> - extrapolate all land points, and add ln_extrap in namelist. 
    157157!> - allow to change unit. 
     158!> @date September, 2015 
     159!> - manage useless (dummy) variable, attributes, and dimension 
    158160!> 
    159161!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    173175   USE iom                             ! I/O manager 
    174176   USE grid                            ! grid manager 
    175    USE vgrid                            ! vertical grid manager 
     177   USE vgrid                           ! vertical grid manager 
    176178   USE extrap                          ! extrapolation manager 
    177179   USE interp                          ! interpolation manager 
     
    183185 
    184186   IMPLICIT NONE 
    185  
    186187 
    187188   ! local variable 
     
    212213 
    213214   LOGICAL                                            :: ll_exist 
     215   LOGICAL                                            :: ll_sameGrid 
    214216 
    215217   TYPE(TDOM)                                         :: tl_dom1 
     
    242244   ! namelist variable 
    243245   ! namlog 
    244    CHARACTER(LEN=lc) :: cn_logfile = 'create_restart.log'  
    245    CHARACTER(LEN=lc) :: cn_verbosity = 'warning'  
    246    INTEGER(i4)       :: in_maxerror = 5 
     246   CHARACTER(LEN=lc)                       :: cn_logfile = 'create_restart.log'  
     247   CHARACTER(LEN=lc)                       :: cn_verbosity = 'warning'  
     248   INTEGER(i4)                             :: in_maxerror = 5 
    247249 
    248250   ! namcfg 
    249    CHARACTER(LEN=lc) :: cn_varcfg = 'variable.cfg'  
     251   CHARACTER(LEN=lc)                       :: cn_varcfg = 'variable.cfg'  
     252   CHARACTER(LEN=lc)                       :: cn_dumcfg = 'dummy.cfg' 
    250253 
    251254   ! namcrs 
    252    CHARACTER(LEN=lc) :: cn_coord0 = ''  
    253    INTEGER(i4)       :: in_perio0 = -1 
     255   CHARACTER(LEN=lc)                       :: cn_coord0 = ''  
     256   INTEGER(i4)                             :: in_perio0 = -1 
    254257 
    255258   ! namfin 
    256    CHARACTER(LEN=lc) :: cn_coord1 = '' 
    257    CHARACTER(LEN=lc) :: cn_bathy1 = '' 
    258    INTEGER(i4)       :: in_perio1 = -1 
     259   CHARACTER(LEN=lc)                       :: cn_coord1 = '' 
     260   CHARACTER(LEN=lc)                       :: cn_bathy1 = '' 
     261   INTEGER(i4)                             :: in_perio1 = -1 
    259262 
    260263   !namzgr 
    261    REAL(dp)          :: dn_pp_to_be_computed = 0._dp 
    262    REAL(dp)          :: dn_ppsur     = -3958.951371276829_dp 
    263    REAL(dp)          :: dn_ppa0      =   103.9530096000000_dp 
    264    REAL(dp)          :: dn_ppa1      =     2.4159512690000_dp 
    265    REAL(dp)          :: dn_ppa2      =   100.7609285000000_dp 
    266    REAL(dp)          :: dn_ppkth     =    15.3510137000000_dp 
    267    REAL(dp)          :: dn_ppkth2    =    48.0298937200000_dp 
    268    REAL(dp)          :: dn_ppacr     =     7.0000000000000_dp 
    269    REAL(dp)          :: dn_ppacr2    =    13.000000000000_dp 
    270    REAL(dp)          :: dn_ppdzmin  = 6._dp 
    271    REAL(dp)          :: dn_pphmax    = 5750._dp 
    272    INTEGER(i4)       :: in_nlevel    = 75 
     264   REAL(dp)                                :: dn_pp_to_be_computed = 0._dp 
     265   REAL(dp)                                :: dn_ppsur   = -3958.951371276829_dp 
     266   REAL(dp)                                :: dn_ppa0    =   103.953009600000_dp 
     267   REAL(dp)                                :: dn_ppa1    =     2.415951269000_dp 
     268   REAL(dp)                                :: dn_ppa2    =   100.760928500000_dp 
     269   REAL(dp)                                :: dn_ppkth   =    15.351013700000_dp 
     270   REAL(dp)                                :: dn_ppkth2  =    48.029893720000_dp 
     271   REAL(dp)                                :: dn_ppacr   =     7.000000000000_dp 
     272   REAL(dp)                                :: dn_ppacr2  =    13.000000000000_dp 
     273   REAL(dp)                                :: dn_ppdzmin = 6._dp 
     274   REAL(dp)                                :: dn_pphmax  = 5750._dp 
     275   INTEGER(i4)                             :: in_nlevel  = 75 
    273276 
    274277   !namzps 
    275    REAL(dp)          :: dn_e3zps_min = 25._dp 
    276    REAL(dp)          :: dn_e3zps_rat = 0.2_dp 
     278   REAL(dp)                                :: dn_e3zps_min = 25._dp 
     279   REAL(dp)                                :: dn_e3zps_rat = 0.2_dp 
    277280 
    278281   ! namvar 
     282   CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varfile = '' 
    279283   CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varinfo = '' 
    280    CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varfile = '' 
    281284 
    282285   ! namnst 
    283    INTEGER(i4)       :: in_rhoi = 0 
    284    INTEGER(i4)       :: in_rhoj = 0 
     286   INTEGER(i4)                             :: in_rhoi = 0 
     287   INTEGER(i4)                             :: in_rhoj = 0 
    285288 
    286289   ! namout 
    287    CHARACTER(LEN=lc) :: cn_fileout = 'restart.nc'  
    288    LOGICAL           :: ln_extrap  = .FALSE. 
    289    INTEGER(i4)       :: in_nproc   = 0 
    290    INTEGER(i4)       :: in_niproc  = 0 
    291    INTEGER(i4)       :: in_njproc  = 0 
    292    CHARACTER(LEN=lc) :: cn_type    = '' 
     290   CHARACTER(LEN=lc)                       :: cn_fileout = 'restart.nc'  
     291   LOGICAL                                 :: ln_extrap  = .FALSE. 
     292   INTEGER(i4)                             :: in_nproc   = 0 
     293   INTEGER(i4)                             :: in_niproc  = 0 
     294   INTEGER(i4)                             :: in_njproc  = 0 
     295   CHARACTER(LEN=lc)                       :: cn_type    = '' 
    293296 
    294297   !------------------------------------------------------------------- 
     
    300303 
    301304   NAMELIST /namcfg/ &  !< configuration namelist 
    302    &  cn_varcfg         !< variable configuration file 
     305   &  cn_varcfg, &      !< variable configuration file 
     306   &  cn_dumcfg         !< dummy configuration file 
    303307 
    304308   NAMELIST /namcrs/ &  !< coarse grid namelist 
     
    330334 
    331335   NAMELIST /namvar/ &  !< variable namelist 
    332    &  cn_varinfo, &     !< list of variable and interpolation method to be used. 
    333    &  cn_varfile        !< list of variable file 
     336   &  cn_varfile, &     !< list of variable file 
     337   &  cn_varinfo        !< list of variable and interpolation method to be used. 
    334338    
    335339   NAMELIST /namnst/ &  !< nesting namelist 
     
    382386      ! get variable extra information 
    383387      CALL var_def_extra(TRIM(cn_varcfg)) 
     388 
     389      ! get dummy variable 
     390      CALL var_get_dummy(TRIM(cn_dumcfg)) 
     391      ! get dummy dimension 
     392      CALL dim_get_dummy(TRIM(cn_dumcfg)) 
     393      ! get dummy attribute 
     394      CALL att_get_dummy(TRIM(cn_dumcfg)) 
    384395 
    385396      READ( il_fileid, NML = namcrs ) 
     
    509520 
    510521               jvar=jvar+1 
    511                 
     522 
    512523               WRITE(*,'(2x,a,a)') "work on variable "//& 
    513524               &  TRIM(tl_multi%t_mpp(ji)%t_proc(1)%t_var(jj)%c_name) 
     
    541552            CALL iom_mpp_open(tl_mpp) 
    542553 
    543  
    544554            ! get or check depth value 
    545555            CALL create_restart_check_depth( tl_mpp, tl_depth ) 
     
    551561            CALL iom_mpp_close(tl_mpp) 
    552562 
    553             IF( ANY( tl_mpp%t_dim(1:2)%i_len /= & 
    554             &        tl_coord0%t_dim(1:2)%i_len) )THEN 
     563            IF( ANY(tl_mpp%t_dim(1:2)%i_len /= tl_coord0%t_dim(1:2)%i_len) .OR.& 
     564            &   ALL(il_rho(:)==1) )THEN 
    555565            !!! extract value from fine grid  
    556566 
    557                IF( ANY( tl_mpp%t_dim(1:2)%i_len <= & 
     567               IF( ANY( tl_mpp%t_dim(1:2)%i_len < & 
    558568               &        tl_coord1%t_dim(1:2)%i_len) )THEN 
    559                   CALL logger_fatal("CREATE RESTART: dimension in file "//& 
     569                  CALL logger_fatal("CREATE RESTART: dimensions in file "//& 
    560570                  &  TRIM(tl_mpp%c_name)//" smaller than those in fine"//& 
    561571                  &  " grid coordinates.") 
    562572               ENDIF 
    563573 
     574               ! use coord0 instead of mpp for restart file case  
     575               !  (without lon,lat) 
     576               ll_sameGrid=.FALSE. 
     577               IF( ALL(tl_mpp%t_dim(1:2)%i_len /= tl_coord0%t_dim(1:2)%i_len) & 
     578               &   )THEN 
     579                  ll_sameGrid=.TRUE.  
     580               ENDIF 
     581 
    564582               ! compute domain on fine grid 
    565                il_ind(:,:)=grid_get_coarse_index(tl_mpp, tl_coord1 ) 
     583               IF( ll_sameGrid )THEN 
     584                  il_ind(:,:)=grid_get_coarse_index(tl_mpp, tl_coord1 ) 
     585               ELSE 
     586                  il_ind(:,:)=grid_get_coarse_index(tl_coord0, tl_coord1 ) 
     587               ENDIF 
    566588 
    567589               il_imin1=il_ind(1,1) ; il_imax1=il_ind(1,2) 
     
    569591 
    570592               !- check grid coincidence 
    571                CALL grid_check_coincidence( tl_mpp, tl_coord1, & 
    572                &                            il_imin1, il_imax1, & 
    573                &                            il_jmin1, il_jmax1, & 
    574                &                            il_rho(:) ) 
     593               IF( ll_sameGrid )THEN 
     594                  CALL grid_check_coincidence( tl_mpp, tl_coord1, & 
     595                  &                            il_imin1, il_imax1, & 
     596                  &                            il_jmin1, il_jmax1, & 
     597                  &                            il_rho(:) ) 
     598               ELSE 
     599                  CALL grid_check_coincidence( tl_coord0, tl_coord1, & 
     600                  &                            il_imin1, il_imax1, & 
     601                  &                            il_jmin1, il_jmax1, & 
     602                  &                            il_rho(:) ) 
     603               ENDIF 
    575604 
    576605               ! compute domain 
     
    754783 
    755784   DO ji=1,ip_maxdim 
     785 
    756786      IF( tl_dim(ji)%l_use )THEN 
    757787         CALL mpp_move_dim(tl_mppout, tl_dim(ji)) 
     
    763793         END SELECT  
    764794      ENDIF 
     795 
    765796   ENDDO 
    766797 
     
    879910   !> and with dimension of the coordinate file.<br/>  
    880911   !> Then the variable array of value is split into equal subdomain. 
    881    !> Each subdomain is filled with the corresponding value of the matrix. 
     912   !> Each subdomain is filled with the associated value of the matrix. 
    882913   !> 
    883914   !> @author J.Paul 
     
    11691200            &        tl_depth%d_value(:,:,:,:) ) )THEN 
    11701201 
    1171                CALL logger_fatal("CREATE BOUNDARY: depth value from "//& 
    1172                &  TRIM(tl_multi%t_mpp(ji)%c_name)//" not conform "//& 
     1202               CALL logger_warn("CREATE BOUNDARY: depth value from "//& 
     1203               &  TRIM(td_mpp%c_name)//" not conform "//& 
    11731204               &  " to those from former file(s).") 
    11741205 
     
    12261257            IF( tl_date1 - tl_date2 /= 0 )THEN 
    12271258 
    1228                CALL logger_fatal("CREATE BOUNDARY: date from "//& 
    1229                &  TRIM(tl_multi%t_mpp(ji)%c_name)//" not conform "//& 
     1259               CALL logger_warn("CREATE BOUNDARY: date from "//& 
     1260               &  TRIM(td_mpp%c_name)//" not conform "//& 
    12301261               &  " to those from former file(s).") 
    12311262 
Note: See TracChangeset for help on using the changeset viewer.