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.
create_layout.f90 in utils/tools/SIREN/src – NEMO

source: utils/tools/SIREN/src/create_layout.f90 @ 12080

Last change on this file since 12080 was 12080, checked in by jpaul, 4 years ago

update nemo trunk

File size: 11.6 KB
Line 
1!----------------------------------------------------------------------
2! MERCATOR OCEAN, System and Interface for oceanic RElocable Nesting
3!----------------------------------------------------------------------
4!
5! DESCRIPTION:
6!> @file
7!> @brief
8!> This program creates/computes the domain layout for you configuration.
9!>
10!> @details
11!> @section sec1 method
12!>
13!> Domain layout is computed, with domain dimension, overlap between subdomain,
14!> and the number of processors available or following i and j-direction.
15!> Then the number of sea/land processors is compute with mask.
16!>
17!> The optimized domain layout is assumed to be the domain layout, with the the most land
18!> processors removed. If no land processor could be removed, it assumed to be the domain layout
19!> with the most sea processors.
20!>
21!> @section sec2 how to
22!> USAGE: create_layout create_layout.nam [-v] [-h]<br/>
23!>    - positional arguments:<br/>
24!>       - create_layout.nam<br/>
25!>          namelist of create_layout
26!>          @note
27!>             a template of the namelist could be created running (in templates directory):
28!>             @code{.sh}
29!>                python create_templates.py create_layout
30!>             @endcode
31!>
32!>    - optional arguments:<br/>
33!>       - -h, --help<br/>
34!>          show this help message (and exit)<br/>
35!>       - -v, --version<br/>
36!>          show Siren's version   (and exit)
37!>
38!> @section sec_layout create_layout.nam
39!>    create_layout.nam contains 4 namelists:<br/>
40!>       - **namlog** to set logger parameters
41!>       - **namcfg** to set configuration file parameters
42!>       - **namvar** to set variable parameters
43!>       - **namout** to set output parameters
44!>
45!>    here after, each sub-namelist parameters is detailed.
46!>    @note
47!>       default values are specified between brackets
48!>
49!> @subsection sublog namlog
50!>    the logger sub-namelist parameters are :
51!>
52!>    - **cn_logfile** [@a create_layout.log]<br/>
53!>       logger filename
54!>
55!>    - **cn_verbosity** [@a warning]<br/>
56!>       verbosity level, choose between :
57!>          - trace
58!>          - debug
59!>          - info
60!>          - warning
61!>          - error
62!>          - fatal
63!>          - none
64!>
65!>    - **in_maxerror** [@a 5]<br/>
66!>       maximum number of error allowed
67!>
68!> @subsection subcfg namcfg
69!>    the configuration sub-namelist parameters are :
70!>
71!>    - **cn_varcfg** [@a ./cfg/variable.cfg]<br/>
72!>       path to the variable configuration file.<br/>
73!>       the variable configuration file defines standard name,
74!>       default interpolation method, axis,...
75!>       to be used for some known variables.<br/>
76!>
77!>    - **cn_dimcfg** [@a ./cfg/dimension.cfg]<br/>
78!>       path to the dimension configuration file.<br/>
79!>       the dimension configuration file defines dimensions allowed.<br/>
80!>
81!>    - **cn_dumcfg** [@a ./cfg/dummy.cfg]<br/>
82!>       path to the useless (dummy) configuration file.<br/>
83!>       the dummy configuration file defines useless
84!>       dimension or variable. these dimension(s) or variable(s) will not be
85!>       processed.<br/>
86!>
87!> @subsection subvar namvar
88!>    the variable sub-namelist parameters are :
89!>
90!>    - **cn_varfile** [@a ]<br/>
91!>       list of variable, and associated file
92!>       @warning
93!>          variable name must be __Bathymetry__ here.
94!>
95!>    - **cn_varfile** [@a ]<br/>:
96!>       list of variable, and associated file.<br/>
97!>       *cn_varfile* is the path and filename of the file where find
98!>       variable to be used as mask grid.<br/>
99!>
100!>       Examples:
101!>          - 'Bathymetry:bathy_meter.nc'
102!>
103!> @subsection subout namout
104!>    the output sub-namelist parameters are :
105!>
106!>    - **in_niproc** [@a 1]<br/>:
107!>       number of processor in i-direction
108!>    - **in_njproc** [@a 1]<br/>:
109!>       number of processor in j-direction
110!>    - **in_nproc** [@a 1]<br/>:
111!>       total number of processor to be used
112!>
113!>    @note
114!>       - if *in_niproc*, and *in_njproc* are provided : the program only look for land
115!>         processor to be removed
116!>       - if *in_nproc* is provided : the program compute each possible domain layout,
117!>         and save the one with the most land processor to be removed
118!>       - with no information about number of processors, the program
119!>         assume to use only one processor
120!>
121!> <hr>
122!> @author
123!> J.Paul
124!>
125!> @date January, 2019 - Initial Version
126!> @date Ocober, 2019
127!> - add help and version optional arguments
128!>
129!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
130!----------------------------------------------------------------------
131PROGRAM create_layout
132
133   USE global                          ! global variable
134   USE kind                            ! F90 kind parameter
135   USE logger                          ! log file manager
136   USE fct                             ! basic useful function
137   USE date                            ! date manager
138   USE math                            !
139   USE att                             ! attribute manager
140   USE dim                             ! dimension manager
141   USE var                             ! variable manager
142   USE file                            ! file manager
143   USE multi                           ! multi file manager
144   USE iom                             ! I/O manager
145   USE dom                             ! domain manager
146   USE grid                            ! grid manager
147   USE mpp                             ! MPP manager
148   USE iom_mpp                         ! MPP I/O manager
149
150   IMPLICIT NONE
151
152   ! parameters
153   CHARACTER(LEN=lc), PARAMETER  :: cp_myname = "create_layout"
154
155   ! local variable
156   CHARACTER(LEN=lc)                       :: cl_arg
157   CHARACTER(LEN=lc)                       :: cl_namelist
158   CHARACTER(LEN=lc)                       :: cl_var
159   CHARACTER(LEN=lc)                       :: cl_errormsg
160
161
162   INTEGER(i4)                             :: il_narg
163   INTEGER(i4)                             :: il_status
164   INTEGER(i4)                             :: il_fileid
165
166   LOGICAL                                 :: ll_exist
167
168   TYPE(TVAR)                              :: tl_var
169
170   TYPE(TFILE)                             :: tl_file
171
172   TYPE(TMPP)                              :: tl_mpp
173   TYPE(TMPP)                              :: tl_mppout
174
175   TYPE(TMULTI)                            :: tl_multi
176   
177   ! namelist variable
178   ! namlog
179   CHARACTER(LEN=lc)                       :: cn_logfile = 'create_layout.log' 
180   CHARACTER(LEN=lc)                       :: cn_verbosity = 'warning' 
181   INTEGER(i4)                             :: in_maxerror = 5
182
183   ! namcfg
184   CHARACTER(LEN=lc)                       :: cn_varcfg = './cfg/variable.cfg' 
185   CHARACTER(LEN=lc)                       :: cn_dimcfg = './cfg/dimension.cfg'
186   CHARACTER(LEN=lc)                       :: cn_dumcfg = './cfg/dummy.cfg'
187
188   ! namvar
189   CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varfile = ''
190
191   ! namout
192   INTEGER(i4)                             :: in_niproc = 0
193   INTEGER(i4)                             :: in_njproc = 0 
194   INTEGER(i4)                             :: in_nproc  = 0
195   !-------------------------------------------------------------------
196
197   NAMELIST /namlog/ &  !< logger namelist
198   &  cn_logfile,    &  !< log file
199   &  cn_verbosity,  &  !< log verbosity
200   &  in_maxerror       !< logger maximum error
201
202   NAMELIST /namcfg/ &  !< configuration namelist
203   &  cn_varcfg,     &  !< variable configuration file
204   &  cn_dimcfg,     &  !< dimension configuration file
205   &  cn_dumcfg         !< dummy configuration file
206
207   NAMELIST /namvar/ &  !< source grid namelist
208   &  cn_varfile        !< input file and mask variable   
209
210   NAMELIST /namout/ &  !< output namelist
211   &  in_niproc,     &
212   &  in_njproc,     &
213   &  in_nproc
214   !-------------------------------------------------------------------   
215
216   !
217   ! Initialisation
218   ! --------------
219   !
220   il_narg=COMMAND_ARGUMENT_COUNT() !f03 intrinsec
221
222   ! Traitement des arguments fournis
223   ! --------------------------------
224   IF( il_narg /= 1 )THEN
225      WRITE(cl_errormsg,*) ' ERROR : one argument is needed '
226      CALL fct_help(cp_myname,cl_errormsg) 
227      CALL EXIT(1)
228   ELSE
229
230      CALL GET_COMMAND_ARGUMENT(1,cl_arg) !f03 intrinsec
231      SELECT CASE (cl_arg)
232         CASE ('-v', '--version')
233
234            CALL fct_version(cp_myname)
235            CALL EXIT(0)
236
237         CASE ('-h', '--help')
238
239            CALL fct_help(cp_myname)
240            CALL EXIT(0)
241
242         CASE DEFAULT
243
244            cl_namelist=cl_arg
245
246            ! read namelist
247            INQUIRE(FILE=TRIM(cl_namelist), EXIST=ll_exist)
248            IF( ll_exist )THEN
249
250               il_fileid=fct_getunit()
251
252               OPEN( il_fileid, FILE=TRIM(cl_namelist),  &
253               &                FORM='FORMATTED',        &
254               &                ACCESS='SEQUENTIAL',     &
255               &                STATUS='OLD',            &
256               &                ACTION='READ',           &
257               &                IOSTAT=il_status)
258               CALL fct_err(il_status)
259               IF( il_status /= 0 )THEN
260                  WRITE(cl_errormsg,*) " ERROR : error opening "//TRIM(cl_namelist)
261                  CALL fct_help(cp_myname,cl_errormsg) 
262                  CALL EXIT(1)
263               ENDIF
264
265               READ( il_fileid, NML = namlog )
266               ! define log file
267               CALL logger_open(TRIM(cn_logfile),TRIM(cn_verbosity),in_maxerror)
268               CALL logger_header()
269
270               READ( il_fileid, NML = namcfg )
271               ! get variable extra information
272               CALL var_def_extra(TRIM(cn_varcfg))
273
274               ! get dimension allowed
275               CALL dim_def_extra(TRIM(cn_dimcfg))
276
277               ! get dummy variable
278               CALL var_get_dummy(TRIM(cn_dumcfg))
279               ! get dummy dimension
280               CALL dim_get_dummy(TRIM(cn_dumcfg))
281               ! get dummy attribute
282               CALL att_get_dummy(TRIM(cn_dumcfg))
283
284               READ( il_fileid, NML = namvar  )
285
286               ! match variable with file
287               tl_multi=multi_init(cn_varfile)
288
289               READ( il_fileid, NML = namout  )
290
291               CLOSE( il_fileid, IOSTAT=il_status )
292               CALL fct_err(il_status)
293               IF( il_status /= 0 )THEN
294                  CALL logger_error("CREATE LAYOUT: closing "//TRIM(cl_namelist))
295               ENDIF
296
297            ELSE
298
299               WRITE(cl_errormsg,*) " ERROR : can't find "//TRIM(cl_namelist)
300               CALL fct_help(cp_myname,cl_errormsg) 
301               CALL EXIT(1)
302
303            ENDIF
304
305      END SELECT
306   ENDIF
307
308   IF( .NOT. ASSOCIATED(tl_multi%t_mpp) .AND. tl_multi%i_nmpp /= 1 )THEN
309      CALL logger_error("CREATE LAYOUT: no (or too much) mpp file to work on. "//&
310      &                 "check cn_varfile in namelist.")
311      CALL logger_fatal("CREATE LAYOUT: no input grid found. "//&
312      &     "check namelist")
313   ELSE
314
315      CALL multi_print(tl_multi)
316     
317      ! open file
318      tl_file=file_init(TRIM(tl_multi%t_mpp(1)%c_name))
319      tl_mpp=mpp_init( tl_file )
320      ! clean
321      CALL file_clean(tl_file)
322      !
323      CALL grid_get_info(tl_mpp)
324
325      CALL iom_mpp_open(tl_mpp)
326
327      cl_var=TRIM((tl_multi%t_mpp(1)%t_proc(1)%t_var(1)%c_name))
328      tl_var=iom_mpp_read_var(tl_mpp,cl_var)
329
330      CALL iom_mpp_close(tl_mpp)
331      ! clean structure
332      CALL mpp_clean(tl_mpp)
333
334      tl_mppout=mpp_init('layout.nc',tl_var,in_niproc, in_njproc,in_nproc)
335
336      CALL mpp_print(tl_mppout)
337
338      ! clean structure
339      CALL var_clean(tl_var)
340      CALL mpp_clean(tl_mppout)
341
342   ENDIF
343
344   ! clean
345   CALL multi_clean(tl_multi)
346
347   ! close log file
348   CALL logger_footer()
349   CALL logger_close()
350
351END PROGRAM
Note: See TracBrowser for help on using the repository browser.