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 7261 for branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/TOOLS/SIREN/src/create_coord.f90 – NEMO

Ignore:
Timestamp:
2016-11-18T09:34:22+01:00 (7 years ago)
Author:
cbricaud
Message:

phaze the rest of NEMOGCM directory ( all except NEMO directory) of the CRS branch with nemo_v3_6_STABLE branch at rev 7213 (09-09-2016) (merge -r 5519:7213 )

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/TOOLS/SIREN/src/create_coord.f90

    r5602 r7261  
    99!> @file 
    1010!> @brief  
    11 !> This program create fine grid coordinate file. 
     11!> This program creates fine grid coordinate file. 
    1212!> 
    1313!> @details 
     
    2424!> @endcode 
    2525!>     
    26 !>    create_coord.nam comprise 6 namelists:<br/> 
     26!> @note  
     27!>    you could find a template of the namelist in templates directory. 
     28!> 
     29!>    create_coord.nam contains 6 namelists:<br/> 
    2730!>       - logger namelist (namlog) 
    2831!>       - config namelist (namcfg) 
     
    3235!>       - output namelist (namout) 
    3336!>     
    34 !>    @note  
    35 !>       All namelists have to be in file create_coord.nam,  
    36 !>       however variables of those namelists are all optional. 
    37 !> 
    3837!>    * _logger namelist (namlog)_:<br/> 
    3938!>       - cn_logfile   : log filename 
    4039!>       - cn_verbosity : verbosity ('trace','debug','info', 
    41 !> 'warning','error','fatal') 
     40!> 'warning','error','fatal','none') 
    4241!>       - in_maxerror  : maximum number of error allowed 
    4342!> 
     
    4544!>       - cn_varcfg : variable configuration file  
    4645!> (see ./SIREN/cfg/variable.cfg) 
     46!>       - cn_dumcfg : useless (dummy) configuration file, for useless  
     47!> dimension or variable (see ./SIREN/cfg/dummy.cfg). 
    4748!> 
    4849!>    * _coarse grid namelist (namcrs)_:<br/> 
     
    5455!>       - cn_varinfo : list of variable and extra information about request(s) 
    5556!> to be used.<br/> 
    56 !>          each elements of *cn_varinfo* is a string character.<br/> 
     57!>          each elements of *cn_varinfo* is a string character  
     58!>          (separated by ',').<br/> 
    5759!>          it is composed of the variable name follow by ':',  
    5860!>          then request(s) to be used on this variable.<br/>  
    5961!>          request could be: 
    60 !>             - interpolation method 
    61 !>             - extrapolation method 
    62 !>             - filter method 
     62!>             - int = interpolation method 
     63!>             - ext = extrapolation method 
    6364!>  
    6465!>                requests must be separated by ';' .<br/> 
     
    6869!>          @ref extrap and @ref filter modules.<br/> 
    6970!> 
    70 !>          Example: 'votemper: linear; hann(2,3); dist_weight',  
    71 !>          'vosaline: cubic'<br/> 
     71!>          Example: 'glamt: int=linear; ext=dist_weight',  
     72!>          'e1t: int=cubic/rhoi'<br/> 
    7273!>          @note  
    7374!>             If you do not specify a method which is required,  
     
    9091!> 
    9192!>    * _output namelist (namout)_: 
    92 !>       - cn_fileout : output coordinate file 
     93!>       - cn_fileout : output coordinate file name 
    9394!> 
    9495!> @author J.Paul 
     
    99100!> - compute offset considering grid point 
    100101!> - add global attributes in output file 
     102!> @date September, 2015 
     103!> - manage useless (dummy) variable, attributes, and dimension 
    101104!> 
    102105!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    152155   TYPE(TFILE)                                          :: tl_fileout 
    153156 
    154    ! check  
    155 !   INTEGER(i4)                                          :: il_imin0 
    156 !   INTEGER(i4)                                          :: il_imax0 
    157 !   INTEGER(i4)                                          :: il_jmin0 
    158 !   INTEGER(i4)                                          :: il_jmax0 
    159 !   INTEGER(i4)      , DIMENSION(2,2)                    :: il_ind2 
    160 !   TYPE(TMPP)                                           :: tl_mppout 
    161  
    162157   ! loop indices 
    163158   INTEGER(i4) :: ji 
     
    165160 
    166161   ! namelist variable 
     162   ! namlog 
    167163   CHARACTER(LEN=lc) :: cn_logfile = 'create_coord.log'  
    168164   CHARACTER(LEN=lc) :: cn_verbosity = 'warning'  
    169165   INTEGER(i4)       :: in_maxerror = 5 
    170166 
     167   ! namcfg 
     168   CHARACTER(LEN=lc) :: cn_varcfg = './cfg/variable.cfg'  
     169   CHARACTER(LEN=lc) :: cn_dumcfg = './cfg/dummy.cfg' 
     170 
     171   ! namcrs 
    171172   CHARACTER(LEN=lc) :: cn_coord0 = ''  
    172173   INTEGER(i4)       :: in_perio0 = -1 
    173174 
    174    CHARACTER(LEN=lc) :: cn_varcfg = '../cfg/variable.cfg'  
    175  
     175   ! namvar 
    176176   CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varinfo = '' 
    177177 
     178   !namnst 
    178179   INTEGER(i4)       :: in_imin0 = 0 
    179180   INTEGER(i4)       :: in_imax0 = 0 
     
    183184   INTEGER(i4)       :: in_rhoj  = 1 
    184185 
     186   !namout 
    185187   CHARACTER(LEN=lc) :: cn_fileout= 'coord_fine.nc' 
    186188   !------------------------------------------------------------------- 
     
    192194 
    193195   NAMELIST /namcfg/ &  !  config namelist 
    194    &  cn_varcfg         !< variable configuration file 
     196   &  cn_varcfg, &       !< variable configuration file 
     197   &  cn_dumcfg          !< dummy configuration file 
    195198 
    196199   NAMELIST /namcrs/ &  !  coarse grid namelist 
     
    252255      CALL var_def_extra(TRIM(cn_varcfg)) 
    253256 
     257      ! get dummy variable 
     258      CALL var_get_dummy(TRIM(cn_dumcfg)) 
     259      ! get dummy dimension 
     260      CALL dim_get_dummy(TRIM(cn_dumcfg)) 
     261      ! get dummy attribute 
     262      CALL att_get_dummy(TRIM(cn_dumcfg)) 
     263 
    254264      READ( il_fileid, NML = namcrs ) 
    255265      READ( il_fileid, NML = namvar ) 
     
    305315 
    306316      il_offset(:,:,:)=create_coord_get_offset(il_rho(:)) 
    307  
    308317   ENDIF 
    309318 
     
    348357      CALL dom_del_extra( tl_var(ji), tl_dom, il_rho(:), .true. ) 
    349358 
    350       ! do not add ghost cell.  
    351       ! ghost cell already replace by value for coordinates  
    352       ! CALL grid_add_ghost(tl_var(ji),tl_dom%i_ghost(:,:)) 
    353  
    354359      ! filter 
    355360      CALL filter_fill_value(tl_var(ji))       
    356361 
    357362   ENDDO 
     363 
     364   ! clean 
     365   CALL dom_clean_extra( tl_dom ) 
    358366 
    359367   ! close mpp files 
     
    375383 
    376384   ! add variables 
    377    DO ji=1,il_nvar 
     385   DO ji=il_nvar,1,-1 
    378386      CALL file_add_var(tl_fileout, tl_var(ji)) 
     387      CALL var_clean(tl_var(ji)) 
    379388   ENDDO 
    380  
    381    ! recompute some attribute 
    382389 
    383390   ! add some attribute 
     
    392399   CALL file_add_att(tl_fileout, tl_att)    
    393400 
    394    tl_att=att_init("src_i_indices",(/in_imin0,in_imax0/)) 
     401   tl_att=att_init("src_i_indices",(/tl_dom%i_imin,tl_dom%i_imax/)) 
    395402   CALL file_add_att(tl_fileout, tl_att)    
    396    tl_att=att_init("src_j_indices",(/in_jmin0,in_jmax0/)) 
     403   tl_att=att_init("src_j_indices",(/tl_dom%i_jmin,tl_dom%i_jmax/)) 
    397404   CALL file_add_att(tl_fileout, tl_att) 
    398405   IF( .NOT. ALL(il_rho(:)==1) )THEN 
     
    440447 
    441448   CALL file_clean(tl_fileout) 
    442  
    443 !   ! check domain 
    444 !   tl_coord0=mpp_init( file_init(TRIM(cn_coord0)), id_perio=in_perio0) 
    445 !   tl_mppout=mpp_init( file_init(TRIM(cn_fileout)) ) 
    446 !   CALL grid_get_info(tl_coord0) 
    447 !   CALL iom_mpp_open(tl_mppout) 
    448 ! 
    449 !   il_ind2(:,:)=grid_get_coarse_index( tl_coord0, tl_mppout, & 
    450 !   &                                   id_rho=il_rho(:) ) 
    451 ! 
    452 !   il_imin0=il_ind2(1,1) ; il_imax0=il_ind2(1,2) 
    453 !   il_jmin0=il_ind2(2,1) ; il_jmax0=il_ind2(2,2) 
    454 ! 
    455 !   IF( il_imin0 /= in_imin0 .OR. & 
    456 !   &   il_imax0 /= in_imax0 .OR. & 
    457 !   &   il_jmin0 /= in_jmin0 .OR. & 
    458 !   &   il_jmax0 /= in_jmax0 )THEN 
    459 !      CALL logger_debug("CREATE COORD: output indices ("//& 
    460 !      &                 TRIM(fct_str(il_imin0))//","//& 
    461 !      &                 TRIM(fct_str(il_imax0))//") ("//& 
    462 !      &                 TRIM(fct_str(il_jmin0))//","//& 
    463 !      &                 TRIM(fct_str(il_jmax0))//")" )  
    464 !      CALL logger_debug("CREATE COORD: input indices ("//& 
    465 !      &                 TRIM(fct_str(in_imin0))//","//& 
    466 !      &                 TRIM(fct_str(in_imax0))//") ("//& 
    467 !      &                 TRIM(fct_str(in_jmin0))//","//& 
    468 !      &                 TRIM(fct_str(in_jmax0))//")" )  
    469 !      CALL logger_fatal("CREATE COORD: output domain not confrom "//& 
    470 !      &                 "with input indices") 
    471 !   ENDIF 
    472 ! 
    473 !   CALL iom_mpp_close(tl_coord0) 
    474 !   CALL iom_mpp_close(tl_mppout) 
    475449 
    476450   ! close log file 
     
    539513   !> @param[in] id_iext   number of points to be extrapolated in i-direction 
    540514   !> @param[in] id_jext   number of points to be extrapolated in j-direction 
     515   !> 
     516   !> @todo check if mask is really needed 
    541517   !------------------------------------------------------------------- 
    542518   SUBROUTINE create_coord_interp( td_var,          & 
     
    626602 
    627603         ! extrapolate variable 
    628          CALL extrap_fill_value( td_var, id_iext=il_iext, id_jext=il_jext ) 
     604         CALL extrap_fill_value( td_var ) 
    629605 
    630606         ! interpolate variable 
Note: See TracChangeset for help on using the changeset viewer.