ROMS
Loading...
Searching...
No Matches
mod_coupler Module Reference

Data Types

type  t_clock
 
type  t_field
 
type  t_integer
 
type  t_mesh
 
type  t_string
 

Functions/Subroutines

subroutine allocate_coupler (nnodes)
 

Variables

integer nmodels
 
integer atmid = 3
 
integer wavid = 2
 
integer ocnid = 1
 
logical lreport = .FALSE.
 
character(len=20), dimension(:), allocatable orderlabel
 
integer iatmos = 0
 
integer iocean = 0
 
integer iwaves = 0
 
character(len=256), dimension(:), allocatable inpname
 
character(len=256) cplname
 
integer, dimension(:), allocatable nthreads
 
type(t_integer), dimension(:), allocatable pets
 
real(r8), dimension(:,:), allocatable timeinterval
 
integer, dimension(:,:), allocatable couplesteps
 
integer, parameter maxnumberfields = 50
 
type(t_field), dimension(maxnumberfieldsfields
 
integer, dimension(:), allocatable nexport
 
integer, dimension(:), allocatable nimport
 
type(t_integer), dimension(:), allocatable exportid
 
type(t_integer), dimension(:), allocatable importid
 
type(t_string), dimension(:), allocatable export
 
type(t_string), dimension(:), allocatable import
 
character(len=240), dimension(:), allocatable exportlist
 

Function/Subroutine Documentation

◆ allocate_coupler()

subroutine mod_coupler::allocate_coupler ( integer, intent(in) nnodes)

Definition at line 168 of file mod_coupler.F.

169!
170!=======================================================================
171! !
172! This routine allocates all variables in the module for all coupled !
173! models. It also initialize variable when appropriate. !
174! !
175!=======================================================================
176!
177 USE mod_parallel
178 USE mod_iounits
179 USE mod_ncparam
180 USE mod_scalars
181!
182! Imported variable declarations.
183!
184 integer, intent(in) :: Nnodes
185!
186! Local variable declarations.
187!
188 logical :: load
189!
190 integer, parameter :: inp = 20
191!
192 integer :: Nfields
193 integer :: gtype, i, id, ifield, inode, lvar, model, ng, varid
194 integer :: io_err
195!
196 real(r8) :: add_offset, scale
197!
198 character (len=40 ) :: code
199 character (len=80 ) :: string
200 character (len=256) :: io_errmsg
201 character (len=MaxLen), dimension(5) :: Vinfo
202!
203!-----------------------------------------------------------------------
204! Read in coupling export/import variable information.
205!-----------------------------------------------------------------------
206!
207! Open input coupling variable information file.
208!
209 OPEN (inp, file=trim(cplname), form='formatted', status='old', &
210 & iostat=io_err, iomsg=io_errmsg)
211 IF (io_err.ne.0) THEN
212 IF (myrank.eq.0) WRITE(stdout,50) trim(cplname), trim(io_errmsg)
213 exit_flag=5
214 RETURN
215 END IF
216!
217! Read in variable information. Ignore blank and comment [char(33)=!]
218! input lines.
219!
220 varid=0
221 DO WHILE (.true.)
222 READ (inp,*,err=30,END=40) Vinfo(1)
223 lvar=len_trim(vinfo(1))
224!
225! Read in other variable information.
226!
227 IF ((lvar.gt.0).and.(vinfo(1)(1:1).ne.char(33))) THEN
228 READ (inp,*,err=30) vinfo(2)
229 READ (inp,*,err=30) vinfo(3)
230 READ (inp,*,err=30) vinfo(4)
231 READ (inp,*,err=30) vinfo(5)
232 READ (inp,*,err=30) add_offset
233 READ (inp,*,err=30) scale
234!
235! Determine staggered C-grid variable.
236!
237 SELECT CASE (trim(adjustl(vinfo(5))))
238 CASE ('p2dvar')
239 gtype=p2dvar
240 CASE ('r2dvar')
241 gtype=r2dvar
242 CASE ('u2dvar')
243 gtype=u2dvar
244 CASE ('v2dvar')
245 gtype=v2dvar
246 CASE ('p3dvar')
247 gtype=p3dvar
248 CASE ('r3dvar')
249 gtype=r3dvar
250 CASE ('u3dvar')
251 gtype=u3dvar
252 CASE ('v3dvar')
253 gtype=v3dvar
254 CASE ('w3dvar')
255 gtype=w3dvar
256 CASE ('b3dvar')
257 gtype=b3dvar
258 CASE DEFAULT
259 gtype=0
260 END SELECT
261!
262! Load variable data into information arrays.
263!
264 varid=varid+1
265 IF (varid.gt.maxnumberfields) THEN
266 WRITE (stdout,60) maxnumberfields, varid
267 stop
268 END IF
269 fields(varid) % code = trim(adjustl(vinfo(1)))
270 fields(varid) % variable = trim(adjustl(vinfo(2)))
271 fields(varid) % name = trim(adjustl(vinfo(3)))
272 fields(varid) % units = trim(adjustl(vinfo(4)))
273 fields(varid) % FieldID = varid
274 fields(varid) % GridType = gtype
275 fields(varid) % AddOffset = add_offset
276 fields(varid) % scale = scale
277 END IF
278 END DO
279 30 WRITE (stdout,80) trim(adjustl(vinfo(1)))
280 stop
281 40 CLOSE (inp)
282 nfields=varid
283!
284!-----------------------------------------------------------------------
285! Determine identification index for export and import fields.
286!-----------------------------------------------------------------------
287!
288! Allocate IDs structures.
289!
290 IF (.not.allocated(exportid)) THEN
291 allocate ( exportid(nmodels) )
292 DO model=1,nmodels
293 allocate ( exportid(model)%val(nexport(model)) )
294 exportid(model)%val=0
295 END DO
296 END IF
297 IF (.not.allocated(importid)) THEN
298 allocate ( importid(nmodels) )
299 DO model=1,nmodels
300 allocate ( importid(model)%val(nimport(model)) )
301 importid(model)%val=0
302 END DO
303 END IF
304 IF (.not.allocated(exportlist)) THEN
305 allocate ( exportlist(nmodels) )
306 END IF
307!
308! Look fields information and extract Export/Import fields IDs for
309! each coupled model.
310!
311 DO model=1,nmodels
312 DO ifield=1,nexport(model)
313 DO i=1,nfields
314 IF (trim(adjustl(fields(i)%code)).eq. &
315 & trim(adjustl(export(model)%code(ifield)))) THEN
316 exportid(model)%val(ifield)=fields(i)%FieldID
317 END IF
318 END DO
319 END DO
320 DO ifield=1,nimport(model)
321 DO i=1,nfields
322 IF (trim(adjustl(fields(i)%code)).eq. &
323 & trim(adjustl(import(model)%code(ifield)))) THEN
324 importid(model)%val(ifield)=fields(i)%FieldID
325 END IF
326 END DO
327 END DO
328 END DO
329 DO model=1,nmodels
330 exportlist(model)=' '
331 DO ifield=1,nexport(model)
332 id=exportid(model)%val(ifield)
333 IF (id.gt.0) THEN
334 code=adjustl(fields(id)%code)
335 IF (ifield.eq.1) THEN
336 exportlist(model)=trim(exportlist(model))//trim(code)
337 ELSE
338 exportlist(model)=trim(exportlist(model))//':'//trim(code)
339 END IF
340 ELSE
341 WRITE (stdout,70) model, trim(exportlist(model)), &
342 & trim(cplname)
343 stop
344 END IF
345 END DO
346 END DO
347!
348!-----------------------------------------------------------------------
349! Assign processors to coupled models.
350!-----------------------------------------------------------------------
351!
352! Allocate structure.
353!
354 IF (.not.allocated(pets)) THEN
355 allocate ( pets(nmodels) )
356 DO model=1,nmodels
357 allocate ( pets(model)%val(nthreads(model)) )
358 END DO
359 END IF
360!
361! Assign parallel threads for each coupled model. Start counting from
362! zero. That is, they are [0:Nnodes-1] available.
363!
364 inode=-1
365 DO model=1,nmodels
366 DO i=1,nthreads(model)
367 inode=inode+1
368 pets(model)%val(i)=inode
369 END DO
370 END DO
371!
372! Report.
373!
374 IF ((inode+1).ne.nnodes) THEN
375 IF (myrank.eq.0) THEN
376 WRITE (stdout,80) inode, nnodes
377 END IF
378 stop
379 ELSE
380 IF (myrank.eq.0) THEN
381 WRITE (stdout,90)
382 DO model=1,nmodels
383 IF (model.eq.iocean) THEN
384 string='Ocean Model MPI nodes:'
385 ELSE IF (model.eq.iwaves) THEN
386 string='Waves Model MPI nodes:'
387 ELSE IF (model.eq.iatmos) THEN
388 string='Atmos Model MPI nodes:'
389 END IF
390 WRITE (stdout,100) trim(string), &
391 & pets(model)%val(1), &
392 & pets(model)%val(nthreads(model))
393 END DO
394 END IF
395 WRITE (stdout,'(/)')
396 END IF
397 IF (myrank.eq.0) THEN
398 DO model=1,nmodels
399 IF (model.eq.iocean) THEN
400 string='Ocean Export:'
401 ELSE IF (model.eq.iwaves) THEN
402 string='Waves Export:'
403 ELSE IF (model.eq.iatmos) THEN
404 string='Atmos Export:'
405 END IF
406 WRITE (stdout,110) trim(string), trim(exportlist(model))
407 END DO
408 WRITE (stdout,'(/)')
409 END IF
410
411!
412 50 FORMAT (/,' MOD_COUPLER - Unable to open variable information', &
413 & ' file: ',/,15x,a,/,15x,'ERROR: ',a, &
414 /,15x,'Default file is located in source directory.')
415 60 FORMAT (/,' MOD_COUPLER - too small dimension ', &
416 & 'parameter, MV = ',2i5,/,15x, &
417 & 'change file mod_ncparam.F and recompile.')
418 70 FORMAT (/,' MOD_COUPLER - Unregistered export field for ', &
419 & ' model = ',i1,/,15x,'ExportList = ',a,/,15x, &
420 & ' check file = ',a)
421 80 FORMAT (/,' MOD_COUPLER - Number assigned processors: ', &
422 & i3.3,/,15x,'not equal to spawned MPI nodes: ',i3.3)
423 90 FORMAT (/,' Model Coupling Parallel Threads:',/)
424100 FORMAT (3x,a,3x,i3.3,' - ',i3.3)
425110 FORMAT (3x,a,1x,a)
426
type(t_io), dimension(:), allocatable err
integer stdout
integer exit_flag

References mod_param::b3dvar, cplname, mod_iounits::err, mod_scalars::exit_flag, export, exportid, exportlist, fields, iatmos, import, importid, iocean, iwaves, maxnumberfields, mod_parallel::myrank, nexport, nimport, nmodels, nthreads, mod_param::p2dvar, mod_param::p3dvar, pets, mod_param::r2dvar, mod_param::r3dvar, mod_iounits::stdout, mod_param::u2dvar, mod_param::u3dvar, mod_param::v2dvar, mod_param::v3dvar, and mod_param::w3dvar.

Referenced by mct_driver().

Here is the caller graph for this function:

Variable Documentation

◆ atmid

integer mod_coupler::atmid = 3

Definition at line 88 of file mod_coupler.F.

88 integer :: ATMid = 3

Referenced by mct_driver().

◆ couplesteps

integer, dimension(:,:), allocatable mod_coupler::couplesteps

Definition at line 138 of file mod_coupler.F.

138 integer, allocatable :: CoupleSteps(:,:)

Referenced by ad_main3d(), main3d(), rp_main3d(), and tl_main3d().

◆ cplname

character (len=256) mod_coupler::cplname

Definition at line 114 of file mod_coupler.F.

114 character (len=256) :: CPLname

Referenced by allocate_coupler().

◆ export

type (t_string), dimension(:), allocatable mod_coupler::export

Definition at line 159 of file mod_coupler.F.

159 TYPE (T_STRING), allocatable :: Export(:)

Referenced by allocate_coupler().

◆ exportid

type (t_integer), dimension(:), allocatable mod_coupler::exportid

Definition at line 154 of file mod_coupler.F.

154 TYPE (T_INTEGER), allocatable :: ExportID(:)

Referenced by allocate_coupler().

◆ exportlist

character (len=240), dimension(:), allocatable mod_coupler::exportlist

Definition at line 164 of file mod_coupler.F.

164 character (len=240), allocatable :: ExportList(:)

Referenced by allocate_coupler().

◆ fields

type (t_field), dimension(maxnumberfields) mod_coupler::fields

Definition at line 145 of file mod_coupler.F.

145 TYPE (T_FIELD) :: Fields(MaxNumberFields)

Referenced by allocate_coupler().

◆ iatmos

integer mod_coupler::iatmos = 0

Definition at line 104 of file mod_coupler.F.

104 integer :: Iatmos = 0 ! atmospheric model

Referenced by ad_main3d(), allocate_coupler(), main3d(), mct_driver(), rp_main3d(), and tl_main3d().

◆ import

type (t_string), dimension(:), allocatable mod_coupler::import

Definition at line 160 of file mod_coupler.F.

160 TYPE (T_STRING), allocatable :: Import(:)

Referenced by allocate_coupler().

◆ importid

type (t_integer), dimension(:), allocatable mod_coupler::importid

Definition at line 155 of file mod_coupler.F.

155 TYPE (T_INTEGER), allocatable :: ImportID(:)

Referenced by allocate_coupler().

◆ inpname

character (len=256), dimension(:), allocatable mod_coupler::inpname

Definition at line 110 of file mod_coupler.F.

110 character (len=256), allocatable :: INPname(:)

Referenced by mct_driver().

◆ iocean

integer mod_coupler::iocean = 0

Definition at line 105 of file mod_coupler.F.

105 integer :: Iocean = 0 ! ocean model

Referenced by allocate_coupler(), and mct_driver().

◆ iwaves

integer mod_coupler::iwaves = 0

Definition at line 106 of file mod_coupler.F.

106 integer :: Iwaves = 0 ! wave model

Referenced by ad_main3d(), allocate_coupler(), main3d(), mct_driver(), rp_main3d(), and tl_main3d().

◆ lreport

logical mod_coupler::lreport = .FALSE.

Definition at line 94 of file mod_coupler.F.

94 logical :: Lreport = .false.

◆ maxnumberfields

integer, parameter mod_coupler::maxnumberfields = 50

Definition at line 143 of file mod_coupler.F.

143 integer, parameter :: MaxNumberFields = 50

Referenced by allocate_coupler().

◆ nexport

integer, dimension(:), allocatable mod_coupler::nexport

Definition at line 149 of file mod_coupler.F.

149 integer, allocatable :: Nexport(:)

Referenced by allocate_coupler().

◆ nimport

integer, dimension(:), allocatable mod_coupler::nimport

Definition at line 150 of file mod_coupler.F.

150 integer, allocatable :: Nimport(:)

Referenced by allocate_coupler().

◆ nmodels

integer mod_coupler::nmodels

Definition at line 84 of file mod_coupler.F.

84 integer :: Nmodels

Referenced by allocate_coupler().

◆ nthreads

integer, dimension(:), allocatable mod_coupler::nthreads

Definition at line 119 of file mod_coupler.F.

119 integer, allocatable :: Nthreads(:)

Referenced by allocate_coupler(), and mct_driver().

◆ ocnid

integer mod_coupler::ocnid = 1

Definition at line 90 of file mod_coupler.F.

90 integer :: OCNid = 1

Referenced by mct_driver().

◆ orderlabel

character (len=20), dimension(:), allocatable mod_coupler::orderlabel

Definition at line 99 of file mod_coupler.F.

99 character (len=20), allocatable :: OrderLabel(:)

◆ pets

type (t_integer), dimension(:), allocatable mod_coupler::pets

Definition at line 124 of file mod_coupler.F.

124 TYPE (T_INTEGER), allocatable :: pets(:)

Referenced by allocate_coupler(), and mct_driver().

◆ timeinterval

real(r8), dimension(:,:), allocatable mod_coupler::timeinterval

Definition at line 132 of file mod_coupler.F.

132 real(r8), allocatable :: TimeInterval(:,:)

Referenced by mct_driver().

◆ wavid

integer mod_coupler::wavid = 2

Definition at line 89 of file mod_coupler.F.

89 integer :: WAVid = 2

Referenced by mct_driver().