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 6440 for branches/UKMO/dev_r5518_GC3p0_package/NEMOGCM/TOOLS/SIREN/src/create_bathy.f90 – NEMO

Ignore:
Timestamp:
2016-04-07T16:32:24+02:00 (8 years ago)
Author:
dancopsey
Message:

Merged in nemo_v3_6_STABLE_copy up to revision 6436.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GC3p0_package/NEMOGCM/TOOLS/SIREN/src/create_bathy.f90

    r5037 r6440  
    88!> @file 
    99!> @brief  
    10 !> This program create fine grid bathymetry file. 
     10!> This program creates fine grid bathymetry file. 
    1111!> 
    1212!> @details 
     
    2020!>    ./SIREN/bin/create_bathy create_bathy.nam 
    2121!> @endcode 
    22 !>     
    23 !>    create_bathy.nam comprise 7 namelists:<br/> 
     22!> <br/>     
     23!> \image html  bathy_40.png  
     24!> \image latex bathy_30.png 
     25!> 
     26!> @note  
     27!>    you could find a template of the namelist in templates directory. 
     28!> 
     29!>    create_bathy.nam contains 7 namelists:<br/> 
    2430!>       - logger namelist (namlog) 
    2531!>       - config namelist (namcfg) 
     
    3036!>       - output namelist (namout) 
    3137!>     
    32 !>    @note  
    33 !>       All namelists have to be in file create_bathy.nam, however variables of 
    34 !>       those namelists are all optional. 
    35 !> 
    3638!>    * _logger namelist (namlog)_:<br/> 
    3739!>       - cn_logfile   : log filename 
    3840!>       - cn_verbosity : verbosity ('trace','debug','info', 
    39 !> 'warning','error','fatal') 
     41!> 'warning','error','fatal','none') 
    4042!>       - in_maxerror  : maximum number of error allowed 
    4143!> 
     
    4345!>       - cn_varcfg : variable configuration file  
    4446!> (see ./SIREN/cfg/variable.cfg) 
     47!>       - cn_dumcfg : useless (dummy) configuration file, for useless  
     48!> dimension or variable (see ./SIREN/cfg/dummy.cfg). 
    4549!> 
    4650!>    * _coarse grid namelist (namcrs)_:<br/> 
     
    5256!>       - cn_coord1 : coordinate file 
    5357!>       - in_perio1 : periodicity index 
    54 !>       - ln_fillclosed : fill closed sea or not 
     58!>       - ln_fillclosed : fill closed sea or not (default is .TRUE.) 
    5559!> 
    5660!>    * _variable namelist (namvar)_:<br/> 
    57 !>       - cn_varinfo : list of variable and extra information about request(s)  
    58 !>       to be used.<br/> 
    59 !>          each elements of *cn_varinfo* is a string character.<br/> 
    60 !>          it is composed of the variable name follow by ':',  
    61 !>          then request(s) to be used on this variable.<br/>  
    62 !>          request could be: 
    63 !>             - interpolation method 
    64 !>             - extrapolation method 
    65 !>             - filter method 
    66 !>             - > minimum value 
    67 !>             - < maximum value 
    68 !> 
    69 !>                requests must be separated by ';'.<br/> 
    70 !>                order of requests does not matter.<br/> 
    71 !> 
    72 !>          informations about available method could be find in @ref interp, 
    73 !>          @ref extrap and @ref filter modules.<br/> 
    74 !>          Example: 'Bathymetry: 2*hamming(2,3); > 0' 
    75 !>          @note  
    76 !>             If you do not specify a method which is required,  
    77 !>             default one is apply. 
    78 !>          @warning  
    79 !>             variable name must be __Bathymetry__ here. 
    8061!>       - cn_varfile : list of variable, and corresponding file.<br/>  
    8162!>          *cn_varfile* is the path and filename of the file where find 
     
    9071!>                - ',' for line 
    9172!>                - '/' for row 
    92 !>                - '\' for level<br/> 
    9373!>                Example:<br/> 
    9474!>                   3,2,3/1,4,5  =>  @f$ \left( \begin{array}{ccc} 
     
    10080!>             - 'Bathymetry:5000,5000,5000/5000,3000,5000/5000,5000,5000' 
    10181!> 
    102 !>          \image html  bathy_40.png  
    103 !>          \image latex bathy_30.png 
     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. 
    104108!> 
    105109!>    * _nesting namelist (namnst)_:<br/> 
     
    119123!> - add header for user 
    120124!> - Bug fix, compute offset depending of grid point 
     125!> @date June, 2015 
     126!> - extrapolate all land points. 
     127!> - 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 
    121135! 
     136!> @todo 
     137!> - check tl_multi is not empty 
     138!> 
    122139!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    123140!---------------------------------------------------------------------- 
     
    154171   INTEGER(i4)                                        :: il_status 
    155172   INTEGER(i4)                                        :: il_fileid 
    156    INTEGER(i4)                                        :: il_varid 
    157173   INTEGER(i4)                                        :: il_attid 
    158174   INTEGER(i4)                                        :: il_imin0 
     
    166182 
    167183   LOGICAL                                            :: ll_exist 
     184   LOGICAL                                            :: ll_fillclosed 
    168185 
    169186   TYPE(TMPP)                                         :: tl_coord0 
     
    195212   ! namelist variable 
    196213   ! namlog 
    197    CHARACTER(LEN=lc) :: cn_logfile = 'create_bathy.log'  
    198    CHARACTER(LEN=lc) :: cn_verbosity = 'warning'  
    199    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 
    200217 
    201218   ! namcfg 
    202    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'  
    203221 
    204222   ! namcrs 
    205    CHARACTER(LEN=lc) :: cn_coord0 = ''  
    206    INTEGER(i4)       :: in_perio0 = -1 
     223   CHARACTER(LEN=lc)                       :: cn_coord0 = ''  
     224   INTEGER(i4)                             :: in_perio0 = -1 
    207225 
    208226   ! namfin 
    209    CHARACTER(LEN=lc) :: cn_coord1 = '' 
    210    INTEGER(i4)       :: in_perio1 = -1 
    211    LOGICAL           :: ln_fillclosed = .TRUE. 
     227   CHARACTER(LEN=lc)                       :: cn_coord1 = '' 
     228   INTEGER(i4)                             :: in_perio1 = -1 
     229   LOGICAL                                 :: ln_fillclosed = .TRUE. 
    212230 
    213231   ! namvar 
     232   CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varfile = '' 
    214233   CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varinfo = '' 
    215    CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varfile = '' 
    216234 
    217235   ! namnst 
    218    INTEGER(i4)       :: in_rhoi  = 1 
    219    INTEGER(i4)       :: in_rhoj  = 1 
     236   INTEGER(i4)                             :: in_rhoi  = 1 
     237   INTEGER(i4)                             :: in_rhoj  = 1 
    220238 
    221239   ! namout 
    222    CHARACTER(LEN=lc) :: cn_fileout = 'bathy_fine.nc'  
     240   CHARACTER(LEN=lc)                       :: cn_fileout = 'bathy_fine.nc'  
    223241   !------------------------------------------------------------------- 
    224242 
     
    229247 
    230248   NAMELIST /namcfg/ &   !< configuration namelist 
    231    &  cn_varcfg          !< variable configuration file 
     249   &  cn_varcfg, &       !< variable configuration file 
     250   &  cn_dumcfg          !< dummy configuration file 
    232251 
    233252   NAMELIST /namcrs/ &   !< coarse grid namelist 
     
    241260  
    242261   NAMELIST /namvar/ &   !< variable namelist 
    243    &  cn_varinfo, &      !< list of variable and interpolation method to be used. (ex: 'votemper:linear','vosaline:cubic' ) 
    244    &  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' ) 
    245264    
    246265   NAMELIST /namnst/ &   !< nesting namelist 
     
    289308      CALL var_def_extra(TRIM(cn_varcfg)) 
    290309 
     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 
    291317      READ( il_fileid, NML = namcrs ) 
    292318      READ( il_fileid, NML = namfin ) 
     
    296322      ! match variable with file 
    297323      tl_multi=multi_init(cn_varfile) 
    298        
     324  
    299325      READ( il_fileid, NML = namnst ) 
    300326      READ( il_fileid, NML = namout ) 
     
    309335 
    310336      PRINT *,"ERROR in create_bathy: can't find "//TRIM(cl_namelist) 
     337      STOP 
    311338 
    312339   ENDIF 
     
    330357      &     "check namelist") 
    331358   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. 
    332363 
    333364   ! check 
     
    404435 
    405436            ! get or check depth value 
    406             IF( tl_multi%t_mpp(ji)%t_proc(1)%i_depthid /= 0 )THEN 
    407                il_varid=tl_multi%t_mpp(ji)%t_proc(1)%i_depthid 
    408                IF( ASSOCIATED(tl_depth%d_value) )THEN 
    409                   tl_tmp=iom_mpp_read_var(tl_mpp,il_varid) 
    410                   IF( ANY( tl_depth%d_value(:,:,:,:) /= & 
    411                   &        tl_tmp%d_value(:,:,:,:) ) )THEN 
    412                      CALL logger_fatal("CREATE BATHY: depth value from "//& 
    413                      &  TRIM(tl_multi%t_mpp(ji)%c_name)//" not conform "//& 
    414                      &  " to those from former file(s).") 
    415                   ENDIF 
    416                   CALL var_clean(tl_tmp) 
    417                ELSE 
    418                   tl_depth=iom_mpp_read_var(tl_mpp,il_varid) 
    419                ENDIF 
    420             ENDIF 
     437            CALL create_bathy_check_depth( tl_mpp, tl_depth ) 
    421438 
    422439            ! get or check time value 
    423             IF( tl_multi%t_mpp(ji)%t_proc(1)%i_timeid /= 0 )THEN 
    424                il_varid=tl_multi%t_mpp(ji)%t_proc(1)%i_timeid 
    425                IF( ASSOCIATED(tl_time%d_value) )THEN 
    426                   tl_tmp=iom_mpp_read_var(tl_mpp,il_varid) 
    427                   IF( ANY( tl_time%d_value(:,:,:,:) /= & 
    428                   &        tl_tmp%d_value(:,:,:,:) ) )THEN 
    429                      CALL logger_fatal("CREATE BATHY: time value from "//& 
    430                      &  TRIM(tl_multi%t_mpp(ji)%c_name)//" not conform "//& 
    431                      &  " to those from former file(s).") 
    432                   ENDIF 
    433                   CALL var_clean(tl_tmp) 
    434                ELSE 
    435                   tl_time=iom_mpp_read_var(tl_mpp,il_varid) 
    436                ENDIF 
    437             ENDIF 
     440            CALL create_bathy_check_time( tl_mpp, tl_time ) 
    438441 
    439442            ! close mpp file 
    440443            CALL iom_mpp_close(tl_mpp) 
    441444 
    442             IF( ANY( tl_mpp%t_dim(1:2)%i_len /= & 
    443             &        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 
    444447               !- extract bathymetry from fine grid bathymetry  
    445448               DO jj=1,tl_multi%t_mpp(ji)%t_proc(1)%i_nvar 
     
    482485   ENDIF 
    483486 
     487   ! use additional request 
    484488   DO jk=1,tl_multi%i_nvar 
     489 
     490         ! change unit and apply factor 
     491         CALL var_chg_unit(tl_var(jk)) 
     492 
    485493         ! forced min and max value 
    486494         CALL var_limit_value(tl_var(jk)) 
    487495 
    488496         ! fill closed sea 
    489          IF( ln_fillclosed )THEN 
     497         IF( ll_fillclosed )THEN 
    490498            ALLOCATE( il_mask(tl_var(jk)%t_dim(1)%i_len, & 
    491499            &                 tl_var(jk)%t_dim(2)%i_len) ) 
     
    508516         &   dl_minbat <= 0._dp  )THEN 
    509517            CALL logger_debug("CREATE BATHY: min value "//TRIM(fct_str(dl_minbat))) 
    510             CALL logger_error("CREATE BATHY: Bathymetry has value <= 0") 
     518            CALL logger_fatal("CREATE BATHY: Bathymetry has value <= 0") 
    511519         ENDIF 
    512520 
     
    557565 
    558566   ! add other variables 
    559    DO jk=1,tl_multi%i_nvar 
     567   DO jk=tl_multi%i_nvar,1,-1 
    560568      CALL file_add_var(tl_fileout, tl_var(jk)) 
    561569      CALL var_clean(tl_var(jk)) 
     
    623631   !> 
    624632   !> @author J.Paul 
    625    !> - November, 2013- Initial Version 
     633   !> @date November, 2013 - Initial Version 
    626634   !> 
    627635   !> @param[in] td_var    variable structure  
     
    759767   !>  
    760768   !> @author J.Paul 
    761    !> - November, 2013- Initial Version 
     769   !> @date November, 2013 - Initial Version 
    762770   !> 
    763771   !> @param[in] td_var    variable structure  
     
    878886   !>  
    879887   !> @author J.Paul 
    880    !> - November, 2013- Initial Version 
     888   !> @date November, 2013 - Initial Version 
    881889   !> 
    882890   !> @param[in] td_var    variable structure 
     
    897905      IMPLICIT NONE 
    898906      ! Argument 
    899       TYPE(TVAR) , INTENT(IN) :: td_var   
    900       TYPE(TMPP) , INTENT(IN) :: td_mpp  
    901       INTEGER(i4), INTENT(IN) :: id_imin 
    902       INTEGER(i4), INTENT(IN) :: id_imax 
    903       INTEGER(i4), INTENT(IN) :: id_jmin 
    904       INTEGER(i4), INTENT(IN) :: id_jmax 
     907      TYPE(TVAR)                 , INTENT(IN) :: td_var   
     908      TYPE(TMPP)                 , INTENT(IN) :: td_mpp  
     909      INTEGER(i4)                , INTENT(IN) :: id_imin 
     910      INTEGER(i4)                , INTENT(IN) :: id_imax 
     911      INTEGER(i4)                , INTENT(IN) :: id_jmin 
     912      INTEGER(i4)                , INTENT(IN) :: id_jmax 
    905913      INTEGER(i4), DIMENSION(:,:), INTENT(IN) :: id_offset 
    906914      INTEGER(i4), DIMENSION(:)  , INTENT(IN) :: id_rho 
     
    955963      CALL dom_del_extra( tl_var, tl_dom, il_rho(:) ) 
    956964 
     965      CALL dom_clean_extra( tl_dom ) 
     966 
    957967      !- add ghost cell 
    958968      CALL grid_add_ghost(tl_var,tl_dom%i_ghost(:,:)) 
     
    989999   !>  
    9901000   !> @author J.Paul 
    991    !> - November, 2013- Initial Version 
     1001   !> @date November, 2013 - Initial Version 
    9921002   !> 
    9931003   !> @param[inout] td_var variable structure  
     
    10731083 
    10741084      ! extrapolate variable 
    1075       CALL extrap_fill_value( td_var, id_offset=id_offset(:,:), & 
    1076       &                               id_rho=id_rho(:),         & 
    1077       &                               id_iext=il_iext, id_jext=il_jext ) 
     1085      CALL extrap_fill_value( td_var ) 
    10781086 
    10791087      ! interpolate Bathymetry 
     
    10931101 
    10941102   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 
    10951211END PROGRAM create_bathy 
Note: See TracChangeset for help on using the changeset viewer.