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_bathy.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_bathy.f90

    r5783 r6436  
    88!> @file 
    99!> @brief  
    10 !> This program create fine grid bathymetry file. 
     10!> This program creates fine grid bathymetry file. 
    1111!> 
    1212!> @details 
     
    2727!>    you could find a template of the namelist in templates directory. 
    2828!> 
    29 !>    create_bathy.nam comprise 7 namelists:<br/> 
     29!>    create_bathy.nam contains 7 namelists:<br/> 
    3030!>       - logger namelist (namlog) 
    3131!>       - config namelist (namcfg) 
     
    3636!>       - output namelist (namout) 
    3737!>     
    38 !>    @note  
    39 !>       All namelists have to be in file create_bathy.nam, however variables of 
    40 !>       those namelists are all optional. 
    41 !> 
    4238!>    * _logger namelist (namlog)_:<br/> 
    4339!>       - cn_logfile   : log filename 
     
    4945!>       - cn_varcfg : variable configuration file  
    5046!> (see ./SIREN/cfg/variable.cfg) 
     47!>       - cn_dumcfg : useless (dummy) configuration file, for useless  
     48!> dimension or variable (see ./SIREN/cfg/dummy.cfg). 
    5149!> 
    5250!>    * _coarse grid namelist (namcrs)_:<br/> 
     
    6159!> 
    6260!>    * _variable namelist (namvar)_:<br/> 
    63 !>       - cn_varinfo : list of variable and extra information about request(s)  
    64 !>       to be used.<br/> 
    65 !>          each elements of *cn_varinfo* is a string character 
    66 !>          (separated by ',').<br/> 
    67 !>          it is composed of the variable name follow by ':',  
    68 !>          then request(s) to be used on this variable.<br/>  
    69 !>          request could be: 
    70 !>             - int = interpolation method 
    71 !>             - ext = extrapolation method 
    72 !>             - flt = filter method 
    73 !>             - min = minimum value 
    74 !>             - max = maximum value 
    75 !>             - unt = new units 
    76 !>             - unf = unit scale factor (linked to new units) 
    77 !> 
    78 !>                requests must be separated by ';'.<br/> 
    79 !>                order of requests does not matter.<br/> 
    80 !> 
    81 !>          informations about available method could be find in @ref interp, 
    82 !>          @ref extrap and @ref filter modules.<br/> 
    83 !>          Example: 'Bathymetry: flt=2*hamming(2,3); min=0' 
    84 !>          @note  
    85 !>             If you do not specify a method which is required,  
    86 !>             default one is apply. 
    87 !>          @warning  
    88 !>             variable name must be __Bathymetry__ here. 
    8961!>       - cn_varfile : list of variable, and corresponding file.<br/>  
    9062!>          *cn_varfile* is the path and filename of the file where find 
     
    10880!>             - 'Bathymetry:5000,5000,5000/5000,3000,5000/5000,5000,5000' 
    10981!> 
     82!>       - cn_varinfo : list of variable and extra information about request(s)  
     83!>       to be used.<br/> 
     84!>          each elements of *cn_varinfo* is a string character 
     85!>          (separated by ',').<br/> 
     86!>          it is composed of the variable name follow by ':',  
     87!>          then request(s) to be used on this variable.<br/>  
     88!>          request could be: 
     89!>             - int = interpolation method 
     90!>             - ext = extrapolation method 
     91!>             - flt = filter method 
     92!>             - min = minimum value 
     93!>             - max = maximum value 
     94!>             - unt = new units 
     95!>             - unf = unit scale factor (linked to new units) 
     96!> 
     97!>                requests must be separated by ';'.<br/> 
     98!>                order of requests does not matter.<br/> 
     99!> 
     100!>          informations about available method could be find in @ref interp, 
     101!>          @ref extrap and @ref filter modules.<br/> 
     102!>          Example: 'Bathymetry: flt=2*hamming(2,3); min=0' 
     103!>          @note  
     104!>             If you do not specify a method which is required,  
     105!>             default one is apply. 
     106!>          @warning  
     107!>             variable name must be __Bathymetry__ here. 
     108!> 
    110109!>    * _nesting namelist (namnst)_:<br/> 
    111110!>       - in_rhoi  : refinement factor in i-direction 
     
    127126!> - extrapolate all land points. 
    128127!> - allow to change unit. 
     128!> @date September, 2015 
     129!> - manage useless (dummy) variable, attributes, and dimension 
     130!> @date January,2016 
     131!> - add create_bathy_check_depth as in create_boundary 
     132!> - add create_bathy_check_time  as in create_boundary 
     133!> @date February, 2016 
     134!> - do not closed sea for east-west cyclic domain 
    129135! 
    130136!> @todo 
    131 !> - use create_bathy_check_depth as in create_boundary 
    132 !> - use create_bathy_check_time  as in create_boundary 
    133137!> - check tl_multi is not empty 
    134138!> 
     
    167171   INTEGER(i4)                                        :: il_status 
    168172   INTEGER(i4)                                        :: il_fileid 
    169    INTEGER(i4)                                        :: il_varid 
    170173   INTEGER(i4)                                        :: il_attid 
    171174   INTEGER(i4)                                        :: il_imin0 
     
    179182 
    180183   LOGICAL                                            :: ll_exist 
     184   LOGICAL                                            :: ll_fillclosed 
    181185 
    182186   TYPE(TMPP)                                         :: tl_coord0 
     
    208212   ! namelist variable 
    209213   ! namlog 
    210    CHARACTER(LEN=lc) :: cn_logfile = 'create_bathy.log'  
    211    CHARACTER(LEN=lc) :: cn_verbosity = 'warning'  
    212    INTEGER(i4)       :: in_maxerror = 5 
     214   CHARACTER(LEN=lc)                       :: cn_logfile = 'create_bathy.log'  
     215   CHARACTER(LEN=lc)                       :: cn_verbosity = 'warning'  
     216   INTEGER(i4)                             :: in_maxerror = 5 
    213217 
    214218   ! namcfg 
    215    CHARACTER(LEN=lc) :: cn_varcfg = 'variable.cfg'  
     219   CHARACTER(LEN=lc)                       :: cn_varcfg = './cfg/variable.cfg'  
     220   CHARACTER(LEN=lc)                       :: cn_dumcfg = './cfg/dummy.cfg'  
    216221 
    217222   ! namcrs 
    218    CHARACTER(LEN=lc) :: cn_coord0 = ''  
    219    INTEGER(i4)       :: in_perio0 = -1 
     223   CHARACTER(LEN=lc)                       :: cn_coord0 = ''  
     224   INTEGER(i4)                             :: in_perio0 = -1 
    220225 
    221226   ! namfin 
    222    CHARACTER(LEN=lc) :: cn_coord1 = '' 
    223    INTEGER(i4)       :: in_perio1 = -1 
    224    LOGICAL           :: ln_fillclosed = .TRUE. 
     227   CHARACTER(LEN=lc)                       :: cn_coord1 = '' 
     228   INTEGER(i4)                             :: in_perio1 = -1 
     229   LOGICAL                                 :: ln_fillclosed = .TRUE. 
    225230 
    226231   ! namvar 
     232   CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varfile = '' 
    227233   CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varinfo = '' 
    228    CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varfile = '' 
    229234 
    230235   ! namnst 
    231    INTEGER(i4)       :: in_rhoi  = 1 
    232    INTEGER(i4)       :: in_rhoj  = 1 
     236   INTEGER(i4)                             :: in_rhoi  = 1 
     237   INTEGER(i4)                             :: in_rhoj  = 1 
    233238 
    234239   ! namout 
    235    CHARACTER(LEN=lc) :: cn_fileout = 'bathy_fine.nc'  
     240   CHARACTER(LEN=lc)                       :: cn_fileout = 'bathy_fine.nc'  
    236241   !------------------------------------------------------------------- 
    237242 
     
    242247 
    243248   NAMELIST /namcfg/ &   !< configuration namelist 
    244    &  cn_varcfg          !< variable configuration file 
     249   &  cn_varcfg, &       !< variable configuration file 
     250   &  cn_dumcfg          !< dummy configuration file 
    245251 
    246252   NAMELIST /namcrs/ &   !< coarse grid namelist 
     
    254260  
    255261   NAMELIST /namvar/ &   !< variable namelist 
    256    &  cn_varinfo, &      !< list of variable and interpolation method to be used. (ex: 'votemper:linear','vosaline:cubic' ) 
    257    &  cn_varfile         !< list of variable file 
     262   &  cn_varfile, &      !< list of variable file 
     263   &  cn_varinfo         !< list of variable and interpolation method to be used. (ex: 'votemper:linear','vosaline:cubic' ) 
    258264    
    259265   NAMELIST /namnst/ &   !< nesting namelist 
     
    302308      CALL var_def_extra(TRIM(cn_varcfg)) 
    303309 
     310      ! get dummy variable 
     311      CALL var_get_dummy(TRIM(cn_dumcfg)) 
     312      ! get dummy dimension 
     313      CALL dim_get_dummy(TRIM(cn_dumcfg)) 
     314      ! get dummy attribute 
     315      CALL att_get_dummy(TRIM(cn_dumcfg)) 
     316 
    304317      READ( il_fileid, NML = namcrs ) 
    305318      READ( il_fileid, NML = namfin ) 
     
    309322      ! match variable with file 
    310323      tl_multi=multi_init(cn_varfile) 
    311        
     324  
    312325      READ( il_fileid, NML = namnst ) 
    313326      READ( il_fileid, NML = namout ) 
     
    322335 
    323336      PRINT *,"ERROR in create_bathy: can't find "//TRIM(cl_namelist) 
     337      STOP 
    324338 
    325339   ENDIF 
     
    343357      &     "check namelist") 
    344358   ENDIF 
     359 
     360   ! do not closed sea for east-west cyclic domain 
     361   ll_fillclosed=ln_fillclosed 
     362   IF( tl_coord1%i_perio == 1 ) ll_fillclosed=.FALSE. 
    345363 
    346364   ! check 
     
    417435 
    418436            ! get or check depth value 
    419             IF( tl_multi%t_mpp(ji)%t_proc(1)%i_depthid /= 0 )THEN 
    420                il_varid=tl_multi%t_mpp(ji)%t_proc(1)%i_depthid 
    421                IF( ASSOCIATED(tl_depth%d_value) )THEN 
    422                   tl_tmp=iom_mpp_read_var(tl_mpp,il_varid) 
    423                   IF( ANY( tl_depth%d_value(:,:,:,:) /= & 
    424                   &        tl_tmp%d_value(:,:,:,:) ) )THEN 
    425                      CALL logger_fatal("CREATE BATHY: depth value from "//& 
    426                      &  TRIM(tl_multi%t_mpp(ji)%c_name)//" not conform "//& 
    427                      &  " to those from former file(s).") 
    428                   ENDIF 
    429                   CALL var_clean(tl_tmp) 
    430                ELSE 
    431                   tl_depth=iom_mpp_read_var(tl_mpp,il_varid) 
    432                ENDIF 
    433             ENDIF 
     437            CALL create_bathy_check_depth( tl_mpp, tl_depth ) 
    434438 
    435439            ! get or check time value 
    436             IF( tl_multi%t_mpp(ji)%t_proc(1)%i_timeid /= 0 )THEN 
    437                il_varid=tl_multi%t_mpp(ji)%t_proc(1)%i_timeid 
    438                IF( ASSOCIATED(tl_time%d_value) )THEN 
    439                   tl_tmp=iom_mpp_read_var(tl_mpp,il_varid) 
    440                   IF( ANY( tl_time%d_value(:,:,:,:) /= & 
    441                   &        tl_tmp%d_value(:,:,:,:) ) )THEN 
    442                      CALL logger_fatal("CREATE BATHY: time value from "//& 
    443                      &  TRIM(tl_multi%t_mpp(ji)%c_name)//" not conform "//& 
    444                      &  " to those from former file(s).") 
    445                   ENDIF 
    446                   CALL var_clean(tl_tmp) 
    447                ELSE 
    448                   tl_time=iom_mpp_read_var(tl_mpp,il_varid) 
    449                ENDIF 
    450             ENDIF 
     440            CALL create_bathy_check_time( tl_mpp, tl_time ) 
    451441 
    452442            ! close mpp file 
    453443            CALL iom_mpp_close(tl_mpp) 
    454444 
    455             IF( ANY( tl_mpp%t_dim(1:2)%i_len /= & 
    456             &        tl_coord0%t_dim(1:2)%i_len) )THEN 
     445            IF( ANY(tl_mpp%t_dim(1:2)%i_len /= tl_coord0%t_dim(1:2)%i_len).OR.& 
     446            &   ALL(il_rho(:)==1) )THEN 
    457447               !- extract bathymetry from fine grid bathymetry  
    458448               DO jj=1,tl_multi%t_mpp(ji)%t_proc(1)%i_nvar 
     
    505495 
    506496         ! fill closed sea 
    507          IF( ln_fillclosed )THEN 
     497         IF( ll_fillclosed )THEN 
    508498            ALLOCATE( il_mask(tl_var(jk)%t_dim(1)%i_len, & 
    509499            &                 tl_var(jk)%t_dim(2)%i_len) ) 
     
    526516         &   dl_minbat <= 0._dp  )THEN 
    527517            CALL logger_debug("CREATE BATHY: min value "//TRIM(fct_str(dl_minbat))) 
    528             CALL logger_error("CREATE BATHY: Bathymetry has value <= 0") 
     518            CALL logger_fatal("CREATE BATHY: Bathymetry has value <= 0") 
    529519         ENDIF 
    530520 
     
    973963      CALL dom_del_extra( tl_var, tl_dom, il_rho(:) ) 
    974964 
     965      CALL dom_clean_extra( tl_dom ) 
     966 
    975967      !- add ghost cell 
    976968      CALL grid_add_ghost(tl_var,tl_dom%i_ghost(:,:)) 
     
    11091101 
    11101102   END SUBROUTINE create_bathy_interp 
     1103   !------------------------------------------------------------------- 
     1104   !> @brief 
     1105   !> This subroutine get depth variable value in an open mpp structure 
     1106   !> and check if agree with already input depth variable. 
     1107   !>  
     1108   !> @details  
     1109   !> 
     1110   !> @author J.Paul 
     1111   !> @date January, 2016 - Initial Version 
     1112   !> 
     1113   !> @param[in] td_mpp       mpp structure 
     1114   !> @param[inout] td_depth  depth variable structure  
     1115   !------------------------------------------------------------------- 
     1116   SUBROUTINE create_bathy_check_depth( td_mpp, td_depth ) 
     1117 
     1118      IMPLICIT NONE 
     1119 
     1120      ! Argument 
     1121      TYPE(TMPP) , INTENT(IN   ) :: td_mpp 
     1122      TYPE(TVAR) , INTENT(INOUT) :: td_depth 
     1123 
     1124      ! local variable 
     1125      INTEGER(i4) :: il_varid 
     1126      TYPE(TVAR)  :: tl_depth 
     1127      ! loop indices 
     1128      !---------------------------------------------------------------- 
     1129 
     1130      ! get or check depth value 
     1131      IF( td_mpp%t_proc(1)%i_depthid /= 0 )THEN 
     1132 
     1133         il_varid=td_mpp%t_proc(1)%i_depthid 
     1134         IF( ASSOCIATED(td_depth%d_value) )THEN 
     1135 
     1136            tl_depth=iom_mpp_read_var(td_mpp, il_varid) 
     1137 
     1138            IF( ANY( td_depth%d_value(:,:,:,:) /= & 
     1139            &        tl_depth%d_value(:,:,:,:) ) )THEN 
     1140 
     1141               CALL logger_warn("CREATE BATHY: depth value from "//& 
     1142               &  TRIM(td_mpp%c_name)//" not conform "//& 
     1143               &  " to those from former file(s).") 
     1144 
     1145            ENDIF 
     1146            CALL var_clean(tl_depth) 
     1147 
     1148         ELSE 
     1149            td_depth=iom_mpp_read_var(td_mpp,il_varid) 
     1150         ENDIF 
     1151 
     1152      ENDIF 
     1153       
     1154   END SUBROUTINE create_bathy_check_depth 
     1155   !------------------------------------------------------------------- 
     1156   !> @brief 
     1157   !> This subroutine get date and time in an open mpp structure 
     1158   !> and check if agree with date and time already read. 
     1159   !>  
     1160   !> @details  
     1161   !> 
     1162   !> @author J.Paul 
     1163   !> @date January, 2016 - Initial Version 
     1164   !> 
     1165   !> @param[in] td_mpp      mpp structure 
     1166   !> @param[inout] td_time  time variable structure  
     1167   !------------------------------------------------------------------- 
     1168   SUBROUTINE create_bathy_check_time( td_mpp, td_time ) 
     1169 
     1170      IMPLICIT NONE 
     1171 
     1172      ! Argument 
     1173      TYPE(TMPP), INTENT(IN   ) :: td_mpp 
     1174      TYPE(TVAR), INTENT(INOUT) :: td_time 
     1175 
     1176      ! local variable 
     1177      INTEGER(i4) :: il_varid 
     1178      TYPE(TVAR)  :: tl_time 
     1179 
     1180      TYPE(TDATE) :: tl_date1 
     1181      TYPE(TDATE) :: tl_date2 
     1182      ! loop indices 
     1183      !---------------------------------------------------------------- 
     1184 
     1185      ! get or check depth value 
     1186      IF( td_mpp%t_proc(1)%i_timeid /= 0 )THEN 
     1187 
     1188         il_varid=td_mpp%t_proc(1)%i_timeid 
     1189         IF( ASSOCIATED(td_time%d_value) )THEN 
     1190 
     1191            tl_time=iom_mpp_read_var(td_mpp, il_varid) 
     1192 
     1193            tl_date1=var_to_date(td_time) 
     1194            tl_date2=var_to_date(tl_time) 
     1195            IF( tl_date1 - tl_date2 /= 0 )THEN 
     1196 
     1197               CALL logger_warn("CREATE BATHY: date from "//& 
     1198               &  TRIM(td_mpp%c_name)//" not conform "//& 
     1199               &  " to those from former file(s).") 
     1200 
     1201            ENDIF 
     1202            CALL var_clean(tl_time) 
     1203 
     1204         ELSE 
     1205            td_time=iom_mpp_read_var(td_mpp,il_varid) 
     1206         ENDIF 
     1207 
     1208      ENDIF 
     1209       
     1210   END SUBROUTINE create_bathy_check_time 
    11111211END PROGRAM create_bathy 
Note: See TracChangeset for help on using the changeset viewer.