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 10251 for branches/UKMO/dev_r5518_AMM15_package/NEMOGCM/TOOLS/SIREN/src/create_coord.f90 – NEMO

Ignore:
Timestamp:
2018-10-29T15:20:26+01:00 (5 years ago)
Author:
kingr
Message:

Rolled back to r10247 - i.e., undid merge of pkg br and 3.6_stable br

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_AMM15_package/NEMOGCM/TOOLS/SIREN/src/create_coord.f90

    r10248 r10251  
    2424!> @endcode 
    2525!>     
    26 !> @note  
    27 !>    you could find a template of the namelist in templates directory. 
    28 !> 
    2926!>    create_coord.nam comprise 6 namelists:<br/> 
    3027!>       - logger namelist (namlog) 
     
    4239!>       - cn_logfile   : log filename 
    4340!>       - cn_verbosity : verbosity ('trace','debug','info', 
    44 !> 'warning','error','fatal','none') 
     41!> 'warning','error','fatal') 
    4542!>       - in_maxerror  : maximum number of error allowed 
    4643!> 
     
    5754!>       - cn_varinfo : list of variable and extra information about request(s) 
    5855!> to be used.<br/> 
    59 !>          each elements of *cn_varinfo* is a string character  
    60 !>          (separated by ',').<br/> 
     56!>          each elements of *cn_varinfo* is a string character.<br/> 
    6157!>          it is composed of the variable name follow by ':',  
    6258!>          then request(s) to be used on this variable.<br/>  
    6359!>          request could be: 
    64 !>             - int = interpolation method 
    65 !>             - ext = extrapolation method 
    66 !>             - flt = filter method 
     60!>             - interpolation method 
     61!>             - extrapolation method 
     62!>             - filter method 
    6763!>  
    6864!>                requests must be separated by ';' .<br/> 
     
    7268!>          @ref extrap and @ref filter modules.<br/> 
    7369!> 
    74 !>          Example: 'votemper: int=linear; flt=hann(2,3); ext=dist_weight',  
    75 !>          'vosaline: int=cubic'<br/> 
     70!>          Example: 'votemper: linear; hann(2,3); dist_weight',  
     71!>          'vosaline: cubic'<br/> 
    7672!>          @note  
    7773!>             If you do not specify a method which is required,  
     
    9490!> 
    9591!>    * _output namelist (namout)_: 
    96 !>       - cn_fileout : output coordinate file name 
     92!>       - cn_fileout : output coordinate file 
    9793!> 
    9894!> @author J.Paul 
     
    156152   TYPE(TFILE)                                          :: tl_fileout 
    157153 
     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 
    158162   ! loop indices 
    159163   INTEGER(i4) :: ji 
     
    161165 
    162166   ! namelist variable 
    163    ! namlog 
    164167   CHARACTER(LEN=lc) :: cn_logfile = 'create_coord.log'  
    165168   CHARACTER(LEN=lc) :: cn_verbosity = 'warning'  
    166169   INTEGER(i4)       :: in_maxerror = 5 
    167170 
    168    ! namcfg 
    169    CHARACTER(LEN=lc) :: cn_varcfg = '../cfg/variable.cfg'  
    170  
    171    ! namcrs 
    172171   CHARACTER(LEN=lc) :: cn_coord0 = ''  
    173172   INTEGER(i4)       :: in_perio0 = -1 
    174173 
    175    ! namvar 
     174   CHARACTER(LEN=lc) :: cn_varcfg = '../cfg/variable.cfg'  
     175 
    176176   CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varinfo = '' 
    177177 
    178    !namnst 
    179178   INTEGER(i4)       :: in_imin0 = 0 
    180179   INTEGER(i4)       :: in_imax0 = 0 
     
    184183   INTEGER(i4)       :: in_rhoj  = 1 
    185184 
    186    !namout 
    187185   CHARACTER(LEN=lc) :: cn_fileout= 'coord_fine.nc' 
    188186   !------------------------------------------------------------------- 
     
    307305 
    308306      il_offset(:,:,:)=create_coord_get_offset(il_rho(:)) 
     307 
    309308   ENDIF 
    310309 
     
    349348      CALL dom_del_extra( tl_var(ji), tl_dom, il_rho(:), .true. ) 
    350349 
     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 
    351354      ! filter 
    352355      CALL filter_fill_value(tl_var(ji))       
     
    372375 
    373376   ! add variables 
    374    DO ji=il_nvar,1,-1 
     377   DO ji=1,il_nvar 
    375378      CALL file_add_var(tl_fileout, tl_var(ji)) 
    376       CALL var_clean(tl_var(ji)) 
    377379   ENDDO 
     380 
     381   ! recompute some attribute 
    378382 
    379383   ! add some attribute 
     
    436440 
    437441   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) 
    438475 
    439476   ! close log file 
     
    502539   !> @param[in] id_iext   number of points to be extrapolated in i-direction 
    503540   !> @param[in] id_jext   number of points to be extrapolated in j-direction 
    504    !> 
    505    !> @todo check if mask is really needed 
    506541   !------------------------------------------------------------------- 
    507542   SUBROUTINE create_coord_interp( td_var,          & 
     
    591626 
    592627         ! extrapolate variable 
    593          CALL extrap_fill_value( td_var ) 
     628         CALL extrap_fill_value( td_var, id_iext=il_iext, id_jext=il_jext ) 
    594629 
    595630         ! interpolate variable 
Note: See TracChangeset for help on using the changeset viewer.