1 MODULE module_quilt_outbuf_ops
4 ! This module contains routines and data structures used by the I/O quilt
5 ! servers to assemble fields ("quilting") and write them to disk.
8 INTEGER, PARAMETER :: tabsize = 5
9 ! The number of entries in outpatch_table (up to a maximum of tabsize)
10 INTEGER, SAVE :: num_entries
12 ! ARP, for PNC-enabled quilting, 02/06/2010
14 LOGICAL :: forDeletion ! TRUE if patch to be
16 INTEGER, DIMENSION(3) :: PatchStart, PatchEnd, PatchExtent
17 REAL, POINTER, DIMENSION(:,:,:) :: rptr
18 INTEGER, POINTER, DIMENSION(:,:,:) :: iptr
21 ! With PNC-enabled quilting, each table entry consists of a series of
22 ! 'npatch' patches (one for each of the compute PEs that this IOServer has
23 ! as clients). We attempt to stitch these together before finally
24 ! writing the data to disk.
26 CHARACTER*80 :: VarName, DateStr, MemoryOrder, &
28 INTEGER, DIMENSION(3) :: DomainStart, DomainEnd
30 ! Total no. of patches in the list PatchList
32 ! How many of the patches remain active in PatchList
33 INTEGER :: nActivePatch
34 TYPE(varpatch), ALLOCATABLE, DIMENSION(:) :: PatchList
35 ! TYPE(varpatch), DIMENSION(tabsize) :: PatchList
38 TYPE(outpatchlist), DIMENSION(tabsize), SAVE :: outpatch_table
40 ! List of which of the initial set of patches saved by the IOServer have
41 ! been successfully stitched together. Without any stitching, each patch's
42 ! entry contains just itself:
43 ! JoinedPatches(1,ipatch) = ipatch
44 ! If jpatch is then stitched to ipatch then we do:
45 ! JoinedPatches(2,ipatch) = jpatch
47 INTEGER, ALLOCATABLE, DIMENSION(:,:), SAVE :: JoinedPatches
49 ! The no. of original patches to be stitched together to make each new patch
50 ! i.e. if the 2nd new patch consists of 4 of the original patches stitched
53 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: PatchCount
55 ! endARP, for PNC-enabled quilting, 02/06/2010
58 CHARACTER*80 :: VarName, DateStr, MemoryOrder, &
61 INTEGER, DIMENSION(3) :: DomainStart, DomainEnd
63 REAL, POINTER, DIMENSION(:,:,:) :: rptr
64 INTEGER, POINTER, DIMENSION(:,:,:) :: iptr
67 TYPE(outrec), DIMENSION(tabsize) :: outbuf_table
71 SUBROUTINE init_outbuf
74 ! This routine re-initializes module data structures.
82 ! This section for PNC-enabled IO quilting
83 outpatch_table(i)%VarName = ""
84 outpatch_table(i)%DateStr = ""
85 outpatch_table(i)%MemoryOrder = ""
86 outpatch_table(i)%Stagger = ""
87 outpatch_table(i)%DimNames(1:3) = ""
88 outpatch_table(i)%DomainStart(1:3) = 0
89 outpatch_table(i)%DomainEnd(1:3) = 0
90 ! We don't free any memory here - that is done immediately after the
91 ! write of each patch is completed
92 DO j = 1, outpatch_table(i)%npatch
93 IF (ALLOCATED(outpatch_table(i)%PatchList)) THEN
94 outpatch_table(i)%PatchList(j)%forDeletion = .FALSE.
95 outpatch_table(i)%PatchList(j)%PatchStart(:) = 0
96 outpatch_table(i)%PatchList(j)%PatchEnd(:) = 0
97 outpatch_table(i)%PatchList(j)%PatchExtent(:)= 0
98 IF (ASSOCIATED(outpatch_table(i)%PatchList(j)%rptr)) &
99 NULLIFY( outpatch_table(i)%PatchList(j)%rptr )
100 IF (ASSOCIATED(outpatch_table(i)%PatchList(j)%iptr)) &
101 NULLIFY( outpatch_table(i)%PatchList(j)%iptr )
102 DEALLOCATE(outpatch_table(i)%PatchList)
105 outpatch_table(i)%npatch = 0
106 outpatch_table(i)%nActivePatch = 0
108 outbuf_table(i)%VarName = ""
109 outbuf_table(i)%DateStr = ""
110 outbuf_table(i)%MemoryOrder = ""
111 outbuf_table(i)%Stagger = ""
112 outbuf_table(i)%DimNames(1) = ""
113 outbuf_table(i)%DimNames(2) = ""
114 outbuf_table(i)%DimNames(3) = ""
115 outbuf_table(i)%ndim = 0
116 NULLIFY( outbuf_table(i)%rptr )
117 NULLIFY( outbuf_table(i)%iptr )
121 !write(0,*)'initializing num_entries to 0 '
123 END SUBROUTINE init_outbuf
126 SUBROUTINE write_outbuf_pnc ( DataHandle, io_form_arg, local_comm, &
130 ! This routine writes all of the records stored in outpatch_table to the
131 ! file referenced by DataHandle using pNetCDF. The patches constituting
132 ! each record are stitched together as far as is possible before
133 ! the pNetCDF I/O routines are called to accomplish the write.
135 ! It then re-initializes module data structures.
138 USE module_state_description
141 #include "wrf_io_flags.h"
142 INTEGER , INTENT(IN) :: DataHandle, io_form_arg, &
143 local_comm, mytask, ntasks
145 INTEGER :: DomainDesc ! dummy
147 INTEGER :: ipatch, icnt
148 INTEGER, ALLOCATABLE, DIMENSION(:) :: count_buf
150 LOGICAL :: do_indep_write ! If no. of patches differs between
151 ! IO Servers then we will have to
152 ! switch pnetcdf into
153 ! independent-writes mode for some
155 CHARACTER*256 :: mess
159 ALLOCATE(count_buf(ntasks), Stat=Status)
161 CALL wrf_error_fatal("write_outbuf_pnc: allocate failed")
164 WRITE(mess,"('write_outbuf_pnc: table has ', I3,' entries')") num_entries
165 CALL wrf_debug ( 200, TRIM( mess ) )
167 DO ii = 1, num_entries
169 WRITE(mess,*)'write_outbuf_pnc: writing ', &
170 TRIM(outpatch_table(ii)%DateStr)," ", &
171 TRIM(outpatch_table(ii)%VarName)," ", &
172 TRIM(outpatch_table(ii)%MemoryOrder)
173 CALL wrf_debug ( 200, TRIM( mess ) )
175 SELECT CASE ( io_form_arg )
179 ! Situation is more complicated in this case since field data stored
180 ! as a list of patches rather than in one array of global-domain
182 ! PatchStart(1) - PatchEnd(1) is dimension with unit stride.
184 ! Quilt patches back together where possible in order to minimise
185 ! number of individual writes
186 CALL stitch_outbuf_patches(ii)
188 ! Check how many patches each of the other IO servers has - we can
189 ! only use pNetCDF in collective mode for the same no. of writes
190 ! on each IO server. Any other patches will have to be written in
192 do_indep_write = .FALSE.
194 min_count = outpatch_table(ii)%nActivePatch
196 CALL MPI_AllGather(min_count, 1, MPI_INTEGER, &
197 count_buf, 1, MPI_INTEGER, &
200 ! Work out the minimum no. of patches on any IO Server and whether
201 ! or not we will have to enter independent IO mode.
202 min_count = outpatch_table(ii)%nActivePatch
204 IF(count_buf(jj) < min_count) min_count = count_buf(jj)
205 IF(outpatch_table(ii)%nActivePatch /= count_buf(jj)) do_indep_write = .TRUE.
209 ! WRITE(mess,*) 'ARPDBG: Min. no. of patches is ', min_count
210 ! CALL wrf_message(mess)
211 ! WRITE(mess,*) 'ARPDBG: I have ',count_buf(mytask+1),' patches.'
212 ! CALL wrf_message(mess)
214 IF ( outpatch_table(ii)%FieldType .EQ. WRF_FLOAT ) THEN
216 ! Loop over the patches in this field up to the number that
217 ! every IO Server has. This is slightly tricky now
218 ! that some of them may be 'deleted.'
222 DO WHILE ( icnt < min_count )
226 IF(outpatch_table(ii)%PatchList(ipatch)%forDeletion) CYCLE
230 WRITE (mess, "('Calling write for patch: ',I3, ' Start = ',3I4)") ipatch, outpatch_table(ii)%PatchList(ipatch)%PatchStart(1:3)
231 CALL wrf_debug ( 200, TRIM( mess ) )
232 WRITE (mess,"(29x,'End = ',3I4)") outpatch_table(ii)%PatchList(ipatch)%PatchEnd(1:3)
233 CALL wrf_debug ( 200, TRIM( mess ) )
235 CALL ext_pnc_write_field ( DataHandle , &
236 TRIM(outpatch_table(ii)%DateStr), &
237 TRIM(outpatch_table(ii)%VarName), &
238 outpatch_table(ii)%PatchList(ipatch)%rptr, &
239 outpatch_table(ii)%FieldType, &!*
240 local_comm, local_comm, DomainDesc , &
241 TRIM(outpatch_table(ii)%MemoryOrder), &
242 TRIM(outpatch_table(ii)%Stagger), &!*
243 outpatch_table(ii)%DimNames , &!*
244 outpatch_table(ii)%DomainStart, &
245 outpatch_table(ii)%DomainEnd, &
246 ! ARP supply magic number as MemoryStart and
247 ! MemoryEnd to signal that this routine is
248 ! being called from quilting.
251 outpatch_table(ii)%PatchList(ipatch)%PatchStart,&
252 outpatch_table(ii)%PatchList(ipatch)%PatchEnd, &
255 ! Free memory associated with this patch
256 DEALLOCATE(outpatch_table(ii)%PatchList(ipatch)%rptr)
260 IF( do_indep_write )THEN
261 ! We must do the next few patches (if any) in independent IO
262 ! mode as not all of the IO Servers have the same no. of
264 ! outpatch_table(ii)%nActivePatch holds the no. of live patches
267 CALL ext_pnc_start_independent_mode(DataHandle, Status)
269 DO WHILE ( icnt<outpatch_table(ii)%nActivePatch )
273 IF(outpatch_table(ii)%PatchList(ipatch)%forDeletion) CYCLE
277 CALL ext_pnc_write_field ( DataHandle , &
278 TRIM(outpatch_table(ii)%DateStr), &
279 TRIM(outpatch_table(ii)%VarName), &
280 outpatch_table(ii)%PatchList(ipatch)%rptr, &
281 outpatch_table(ii)%FieldType, &!*
282 local_comm, local_comm, DomainDesc , &
283 TRIM(outpatch_table(ii)%MemoryOrder), &
284 TRIM(outpatch_table(ii)%Stagger), &!*
285 outpatch_table(ii)%DimNames , &!*
286 outpatch_table(ii)%DomainStart, &
287 outpatch_table(ii)%DomainEnd, &
288 ! ARP supply magic number as MemoryStart and
289 ! MemoryEnd to signal that this routine is
290 ! being called from quilting.
293 outpatch_table(ii)%PatchList(ipatch)%PatchStart,&
294 outpatch_table(ii)%PatchList(ipatch)%PatchEnd, &
297 ! Free memory associated with this patch
298 DEALLOCATE(outpatch_table(ii)%PatchList(ipatch)%rptr)
302 ! End of patches that not every IO Server has so can switch
303 ! back to collective mode.
304 CALL ext_pnc_end_independent_mode(DataHandle, Status)
307 END IF ! Additional patches
309 ELSE IF ( outpatch_table(ii)%FieldType .EQ. WRF_INTEGER ) THEN
311 ! Loop over the patches in this field up to the number that
312 ! every IO Server has. This is slightly tricky now
313 ! that some of them may be 'deleted.'
316 DO WHILE ( icnt < min_count )
320 IF(outpatch_table(ii)%PatchList(ipatch)%forDeletion) CYCLE
324 CALL ext_pnc_write_field ( DataHandle , &
325 TRIM(outpatch_table(ii)%DateStr), &
326 TRIM(outpatch_table(ii)%VarName), &
327 outpatch_table(ii)%PatchList(ipatch)%iptr, &
328 outpatch_table(ii)%FieldType, &!*
329 local_comm, local_comm, DomainDesc, &
330 TRIM(outpatch_table(ii)%MemoryOrder), &
331 TRIM(outpatch_table(ii)%Stagger), &!*
332 outpatch_table(ii)%DimNames , &!*
333 outpatch_table(ii)%DomainStart, &
334 outpatch_table(ii)%DomainEnd, &
335 ! ARP supply magic number as MemoryStart and
336 ! MemoryEnd to signal that this routine is
337 ! being called from quilting.
340 outpatch_table(ii)%PatchList(ipatch)%PatchStart, &
341 outpatch_table(ii)%PatchList(ipatch)%PatchEnd, &
344 ! Free memory associated with this patch
345 DEALLOCATE(outpatch_table(ii)%PatchList(ipatch)%iptr)
349 IF( do_indep_write )THEN
351 ! We have to do the next few patches in independent IO mode as
352 ! not all of the IO Servers have this many patches.
353 ! outpatch_table(ii)%npatch holds the no. of live patches for
355 CALL ext_pnc_start_independent_mode(DataHandle, Status)
357 DO WHILE ( icnt<outpatch_table(ii)%nActivePatch )
361 IF(outpatch_table(ii)%PatchList(ipatch)%forDeletion) CYCLE
365 CALL ext_pnc_write_field ( DataHandle , &
366 TRIM(outpatch_table(ii)%DateStr), &
367 TRIM(outpatch_table(ii)%VarName), &
368 outpatch_table(ii)%PatchList(ipatch)%iptr, &
369 outpatch_table(ii)%FieldType, &!*
370 local_comm, local_comm, DomainDesc , &
371 TRIM(outpatch_table(ii)%MemoryOrder), &
372 TRIM(outpatch_table(ii)%Stagger), &!*
373 outpatch_table(ii)%DimNames , &!*
374 outpatch_table(ii)%DomainStart, &
375 outpatch_table(ii)%DomainEnd, &
376 ! ARP supply magic number as MemoryStart and
377 ! MemoryEnd to signal that this routine is
378 ! being called from quilting.
381 outpatch_table(ii)%PatchList(ipatch)%PatchStart,&
382 outpatch_table(ii)%PatchList(ipatch)%PatchEnd, &
385 ! Free memory associated with this patch
386 DEALLOCATE(outpatch_table(ii)%PatchList(ipatch)%iptr)
390 ! End of patches that not every IO Server has so can switch
391 ! back to collective mode.
392 CALL ext_pnc_end_independent_mode(DataHandle, Status)
394 ENDIF ! Have additional patches
400 ENDDO ! Loop over output buffers
402 ! Reset the table of output buffers
405 DEALLOCATE(count_buf)
407 END SUBROUTINE write_outbuf_pnc
410 SUBROUTINE write_outbuf ( DataHandle , io_form_arg )
413 ! This routine writes all of the records stored in outbuf_table to the
414 ! file referenced by DataHandle using format specified by io_form_arg.
415 ! This routine calls the package-specific I/O routines to accomplish
417 ! It then re-initializes module data structures.
420 USE module_state_description
422 #include "wrf_io_flags.h"
423 INTEGER , INTENT(IN) :: DataHandle, io_form_arg
424 INTEGER :: ii,ds1,de1,ds2,de2,ds3,de3
425 INTEGER :: Comm, IOComm, DomainDesc ! dummy
427 CHARACTER*256 :: mess
428 Comm = 0 ; IOComm = 0 ; DomainDesc = 0
430 DO ii = 1, num_entries
431 WRITE(mess,*)'writing ', &
432 TRIM(outbuf_table(ii)%DateStr)," ", &
433 TRIM(outbuf_table(ii)%VarName)," ", &
434 TRIM(outbuf_table(ii)%MemoryOrder)
435 ds1 = outbuf_table(ii)%DomainStart(1) ; de1 = outbuf_table(ii)%DomainEnd(1)
436 ds2 = outbuf_table(ii)%DomainStart(2) ; de2 = outbuf_table(ii)%DomainEnd(2)
437 ds3 = outbuf_table(ii)%DomainStart(3) ; de3 = outbuf_table(ii)%DomainEnd(3)
439 SELECT CASE ( io_form_arg )
444 IF ( outbuf_table(ii)%FieldType .EQ. WRF_FLOAT ) THEN
446 CALL ext_ncd_write_field ( DataHandle , &
447 TRIM(outbuf_table(ii)%DateStr), &
448 TRIM(outbuf_table(ii)%VarName), &
449 outbuf_table(ii)%rptr(ds1:de1,ds2:de2,ds3:de3), &
450 outbuf_table(ii)%FieldType, & !*
451 Comm, IOComm, DomainDesc , &
452 TRIM(outbuf_table(ii)%MemoryOrder), &
453 TRIM(outbuf_table(ii)%Stagger), & !*
454 outbuf_table(ii)%DimNames , & !*
455 outbuf_table(ii)%DomainStart, &
456 outbuf_table(ii)%DomainEnd, &
457 outbuf_table(ii)%DomainStart, &
458 outbuf_table(ii)%DomainEnd, &
459 outbuf_table(ii)%DomainStart, &
460 outbuf_table(ii)%DomainEnd, &
463 ELSE IF ( outbuf_table(ii)%FieldType .EQ. WRF_INTEGER ) THEN
464 CALL ext_ncd_write_field ( DataHandle , &
465 TRIM(outbuf_table(ii)%DateStr), &
466 TRIM(outbuf_table(ii)%VarName), &
467 outbuf_table(ii)%iptr(ds1:de1,ds2:de2,ds3:de3), &
468 outbuf_table(ii)%FieldType, & !*
469 Comm, IOComm, DomainDesc , &
470 TRIM(outbuf_table(ii)%MemoryOrder), &
471 TRIM(outbuf_table(ii)%Stagger), & !*
472 outbuf_table(ii)%DimNames , & !*
473 outbuf_table(ii)%DomainStart, &
474 outbuf_table(ii)%DomainEnd, &
475 outbuf_table(ii)%DomainStart, &
476 outbuf_table(ii)%DomainEnd, &
477 outbuf_table(ii)%DomainStart, &
478 outbuf_table(ii)%DomainEnd, &
485 IF ( outbuf_table(ii)%FieldType .EQ. WRF_FLOAT ) THEN
487 CALL ext_yyy_write_field ( DataHandle , &
488 TRIM(outbuf_table(ii)%DateStr), &
489 TRIM(outbuf_table(ii)%VarName), &
490 outbuf_table(ii)%rptr(ds1:de1,ds2:de2,ds3:de3), &
491 outbuf_table(ii)%FieldType, & !*
492 Comm, IOComm, DomainDesc , &
493 TRIM(outbuf_table(ii)%MemoryOrder), &
494 TRIM(outbuf_table(ii)%Stagger), & !*
495 outbuf_table(ii)%DimNames , & !*
496 outbuf_table(ii)%DomainStart, &
497 outbuf_table(ii)%DomainEnd, &
498 outbuf_table(ii)%DomainStart, &
499 outbuf_table(ii)%DomainEnd, &
500 outbuf_table(ii)%DomainStart, &
501 outbuf_table(ii)%DomainEnd, &
504 ELSE IF ( outbuf_table(ii)%FieldType .EQ. WRF_INTEGER ) THEN
505 CALL ext_yyy_write_field ( DataHandle , &
506 TRIM(outbuf_table(ii)%DateStr), &
507 TRIM(outbuf_table(ii)%VarName), &
508 outbuf_table(ii)%iptr(ds1:de1,ds2:de2,ds3:de3), &
509 outbuf_table(ii)%FieldType, & !*
510 Comm, IOComm, DomainDesc , &
511 TRIM(outbuf_table(ii)%MemoryOrder), &
512 TRIM(outbuf_table(ii)%Stagger), & !*
513 outbuf_table(ii)%DimNames , & !*
514 outbuf_table(ii)%DomainStart, &
515 outbuf_table(ii)%DomainEnd, &
516 outbuf_table(ii)%DomainStart, &
517 outbuf_table(ii)%DomainEnd, &
518 outbuf_table(ii)%DomainStart, &
519 outbuf_table(ii)%DomainEnd, &
526 IF ( outbuf_table(ii)%FieldType .EQ. WRF_FLOAT ) THEN
528 CALL ext_gr1_write_field ( DataHandle , &
529 TRIM(outbuf_table(ii)%DateStr), &
530 TRIM(outbuf_table(ii)%VarName), &
531 outbuf_table(ii)%rptr(ds1:de1,ds2:de2,ds3:de3), &
532 outbuf_table(ii)%FieldType, & !*
533 Comm, IOComm, DomainDesc , &
534 TRIM(outbuf_table(ii)%MemoryOrder), &
535 TRIM(outbuf_table(ii)%Stagger), & !*
536 outbuf_table(ii)%DimNames , & !*
537 outbuf_table(ii)%DomainStart, &
538 outbuf_table(ii)%DomainEnd, &
539 outbuf_table(ii)%DomainStart, &
540 outbuf_table(ii)%DomainEnd, &
541 outbuf_table(ii)%DomainStart, &
542 outbuf_table(ii)%DomainEnd, &
545 ELSE IF ( outbuf_table(ii)%FieldType .EQ. WRF_INTEGER ) THEN
546 CALL ext_gr1_write_field ( DataHandle , &
547 TRIM(outbuf_table(ii)%DateStr), &
548 TRIM(outbuf_table(ii)%VarName), &
549 outbuf_table(ii)%iptr(ds1:de1,ds2:de2,ds3:de3), &
550 outbuf_table(ii)%FieldType, & !*
551 Comm, IOComm, DomainDesc , &
552 TRIM(outbuf_table(ii)%MemoryOrder), &
553 TRIM(outbuf_table(ii)%Stagger), & !*
554 outbuf_table(ii)%DimNames , & !*
555 outbuf_table(ii)%DomainStart, &
556 outbuf_table(ii)%DomainEnd, &
557 outbuf_table(ii)%DomainStart, &
558 outbuf_table(ii)%DomainEnd, &
559 outbuf_table(ii)%DomainStart, &
560 outbuf_table(ii)%DomainEnd, &
567 IF ( outbuf_table(ii)%FieldType .EQ. WRF_FLOAT ) THEN
569 CALL ext_gr2_write_field ( DataHandle , &
570 TRIM(outbuf_table(ii)%DateStr), &
571 TRIM(outbuf_table(ii)%VarName), &
572 outbuf_table(ii)%rptr(ds1:de1,ds2:de2,ds3:de3), &
573 outbuf_table(ii)%FieldType, & !*
574 Comm, IOComm, DomainDesc , &
575 TRIM(outbuf_table(ii)%MemoryOrder), &
576 TRIM(outbuf_table(ii)%Stagger), & !*
577 outbuf_table(ii)%DimNames , & !*
578 outbuf_table(ii)%DomainStart, &
579 outbuf_table(ii)%DomainEnd, &
580 outbuf_table(ii)%DomainStart, &
581 outbuf_table(ii)%DomainEnd, &
582 outbuf_table(ii)%DomainStart, &
583 outbuf_table(ii)%DomainEnd, &
586 ELSE IF ( outbuf_table(ii)%FieldType .EQ. WRF_INTEGER ) THEN
587 CALL ext_gr2_write_field ( DataHandle , &
588 TRIM(outbuf_table(ii)%DateStr), &
589 TRIM(outbuf_table(ii)%VarName), &
590 outbuf_table(ii)%iptr(ds1:de1,ds2:de2,ds3:de3), &
591 outbuf_table(ii)%FieldType, & !*
592 Comm, IOComm, DomainDesc , &
593 TRIM(outbuf_table(ii)%MemoryOrder), &
594 TRIM(outbuf_table(ii)%Stagger), & !*
595 outbuf_table(ii)%DimNames , & !*
596 outbuf_table(ii)%DomainStart, &
597 outbuf_table(ii)%DomainEnd, &
598 outbuf_table(ii)%DomainStart, &
599 outbuf_table(ii)%DomainEnd, &
600 outbuf_table(ii)%DomainStart, &
601 outbuf_table(ii)%DomainEnd, &
607 IF ( outbuf_table(ii)%FieldType .EQ. WRF_FLOAT ) THEN
609 CALL ext_int_write_field ( DataHandle , &
610 TRIM(outbuf_table(ii)%DateStr), &
611 TRIM(outbuf_table(ii)%VarName), &
612 outbuf_table(ii)%rptr(ds1:de1,ds2:de2,ds3:de3), &
613 outbuf_table(ii)%FieldType, & !*
614 Comm, IOComm, DomainDesc , &
615 TRIM(outbuf_table(ii)%MemoryOrder), &
616 TRIM(outbuf_table(ii)%Stagger), & !*
617 outbuf_table(ii)%DimNames , & !*
618 outbuf_table(ii)%DomainStart, &
619 outbuf_table(ii)%DomainEnd, &
620 outbuf_table(ii)%DomainStart, &
621 outbuf_table(ii)%DomainEnd, &
622 outbuf_table(ii)%DomainStart, &
623 outbuf_table(ii)%DomainEnd, &
626 ELSE IF ( outbuf_table(ii)%FieldType .EQ. WRF_INTEGER ) THEN
628 CALL ext_int_write_field ( DataHandle , &
629 TRIM(outbuf_table(ii)%DateStr), &
630 TRIM(outbuf_table(ii)%VarName), &
631 outbuf_table(ii)%iptr(ds1:de1,ds2:de2,ds3:de3), &
632 outbuf_table(ii)%FieldType, & !*
633 Comm, IOComm, DomainDesc , &
634 TRIM(outbuf_table(ii)%MemoryOrder), &
635 TRIM(outbuf_table(ii)%Stagger), & !*
636 outbuf_table(ii)%DimNames , & !*
637 outbuf_table(ii)%DomainStart, &
638 outbuf_table(ii)%DomainEnd, &
639 outbuf_table(ii)%DomainStart, &
640 outbuf_table(ii)%DomainEnd, &
641 outbuf_table(ii)%DomainStart, &
642 outbuf_table(ii)%DomainEnd, &
651 IF ( ASSOCIATED( outbuf_table(ii)%rptr) ) DEALLOCATE(outbuf_table(ii)%rptr)
652 IF ( ASSOCIATED( outbuf_table(ii)%iptr) ) DEALLOCATE(outbuf_table(ii)%iptr)
653 NULLIFY( outbuf_table(ii)%rptr )
654 NULLIFY( outbuf_table(ii)%iptr )
657 END SUBROUTINE write_outbuf
660 SUBROUTINE stitch_outbuf_patches(ibuf)
663 INTEGER, INTENT(in) :: ibuf
666 ! This routine does the "output quilting" for the case where quilting has been
667 ! built to use Parallel NetCDF. Unlike store_patch_in_outbuf() we do not have
668 ! data for the whole domain --- instead we aim to quilt as much of the data as
669 ! possible in order to reduce the number of separate writes that we must do.
672 #include "wrf_io_flags.h"
673 INTEGER :: ipatch, jpatch, ii
676 INTEGER, DIMENSION(3) :: newExtent, pos
677 INTEGER, ALLOCATABLE, DIMENSION(:,:) :: OldPatchStart
678 INTEGER, POINTER, DIMENSION(:,:,:) :: ibuffer
679 REAL, POINTER, DIMENSION(:,:,:) :: rbuffer
680 CHARACTER*256 :: mess
683 ! CALL start_timing()
685 IF(LEN_TRIM(outpatch_table(ibuf)%MemoryOrder) < 2)THEN
686 ! This field is a scalar or 1D array. Such quantities are replicated
687 ! across compute nodes and therefore we need only keep a single
688 ! patch - delete all but the first in the list
689 IF ( outpatch_table(ibuf)%FieldType .EQ. WRF_FLOAT ) THEN
691 DO jpatch=2,outpatch_table(ibuf)%npatch,1
692 outpatch_table(ibuf)%PatchList(jpatch)%forDeletion = .TRUE.
693 outpatch_table(ibuf)%nActivePatch = &
694 outpatch_table(ibuf)%nActivePatch - 1
695 DEALLOCATE(outpatch_table(ibuf)%PatchList(jpatch)%rptr)
698 ELSE IF ( outpatch_table(ibuf)%FieldType .EQ. WRF_INTEGER ) THEN
700 DO jpatch=2,outpatch_table(ibuf)%npatch,1
701 outpatch_table(ibuf)%PatchList(jpatch)%forDeletion = .TRUE.
702 outpatch_table(ibuf)%nActivePatch = &
703 outpatch_table(ibuf)%nActivePatch - 1
704 DEALLOCATE(outpatch_table(ibuf)%PatchList(jpatch)%iptr)
708 CALL wrf_error_fatal("stitch_outbuf_patches: unrecognised Field Type")
711 ! CALL end_timing("stitch_outbuf_patches: deleting replicated patches")
715 END IF ! Field is scalar or 1D
717 ! Otherwise, this field _is_ distributed across compute PEs and therefore
718 ! it's worth trying to stitch patches together...
719 ALLOCATE(OldPatchStart(3,outpatch_table(ibuf)%npatch), &
720 JoinedPatches(outpatch_table(ibuf)%npatch, &
721 outpatch_table(ibuf)%npatch), &
722 PatchCount(outpatch_table(ibuf)%npatch), &
725 CALL wrf_message('stitch_outbuf_patches: unable to stitch patches as allocate failed.')
729 JoinedPatches(:,:) = -1
730 ! Initialise these arrays to catch failures in the above allocate on
731 ! linux-based systems (e.g. Cray XE) where allocation only actually
732 ! performed when requested memory is touched.
734 OldPatchStart(:,:) = 0
739 DO jpatch=1,outpatch_table(ibuf)%npatch,1
741 ! Each patch consists of just itself initially
742 JoinedPatches(1,jpatch) = jpatch
743 PatchCount(jpatch) = 1
745 ! Store the location of each patch for use after we've decided how to
746 ! stitch them together
747 OldPatchStart(:,jpatch) = outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(:)
750 ! Search through patches to find pairs that we can stitch together
752 OUTER: DO WHILE(ipatch < outpatch_table(ibuf)%npatch)
754 IF( outpatch_table(ibuf)%PatchList(ipatch)%forDeletion )THEN
759 INNER: DO jpatch=ipatch+1,outpatch_table(ibuf)%npatch,1
761 IF(outpatch_table(ibuf)%PatchList(jpatch)%forDeletion )THEN
765 ! Look for patches that can be concatenated with ipatch in the first
766 ! dimension (preferred since that is contiguous in memory in F90)
767 ! ________________ ____________
769 ! Startx(j) Endx(j) Startx(i) Endx(i)
771 IF(outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(1) == &
772 (outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(1) - 1) )THEN
774 ! Patches contiguous in first dimension - do they have the same
775 ! extents in the other two dimensions?
776 IF( (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(2)== &
777 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(2) ) .AND.&
778 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(2) == &
779 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(2) ) .AND.&
780 (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(3)== &
781 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(3) ) .AND.&
782 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(3) == &
783 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(3)) )THEN
785 ! We can concatenate these two patches in first dimension
786 ! WRITE(mess,"('Can concatenate patches ',I3,' and ',I3,' in dim 1')") ipatch, jpatch
787 ! CALL wrf_message(mess)
789 ! Grow patch ipatch to include jpatch
790 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(1) = &
791 outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(1)
792 CALL merge_patches(ibuf, ipatch, jpatch)
799 ! ______________ ____________
801 ! Startx(i) Endx(i) Startx(j) Endx(j)
803 IF(outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(1) == &
804 (outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(1) + 1))THEN
806 ! Patches contiguous in first dimension - do they have the same
807 ! extents in the other two dimensions?
808 IF( (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(2)== &
809 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(2) ) .AND.&
810 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(2) == &
811 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(2) ) .AND.&
812 (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(3)== &
813 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(3) ) .AND.&
814 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(3) == &
815 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(3)) )THEN
817 ! We can concatenate these two patches in first dimension
818 ! WRITE(mess,"('Can concatenate patches ',I3,' and ',I3,' in dim 1')") ipatch, jpatch
819 ! CALL wrf_message(mess)
821 ! Grow patch ipatch to include jpatch
822 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(1) = &
823 outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(1)
824 CALL merge_patches(ibuf, ipatch, jpatch)
832 ! Try the second dimension
833 IF(outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(2) == &
834 (outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(2) - 1))THEN
836 ! Patches contiguous in second dimension - do they have the same
837 ! extents in the other two dimensions?
838 IF( (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(1)== &
839 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(1) ) .AND.&
840 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(1) == &
841 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(1) ) .AND.&
842 (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(3)== &
843 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(3) ) .AND.&
844 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(3) == &
845 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(3)) )THEN
847 ! We can concatenate these two patches in second dimension
848 ! WRITE(mess,"('Can concatenate patches ',I3,' and ',I3,' in dim 2')") ipatch, jpatch
849 ! CALL wrf_message(mess)
851 ! Grow patch ipatch to include jpatch
852 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(2) = &
853 outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(2)
854 CALL merge_patches(ibuf, ipatch, jpatch)
862 IF(outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(2) == &
863 (outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(2) + 1) )THEN
865 ! Patches contiguous in second dimension - do they have the same
866 ! extents in the other two dimensions?
867 IF( (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(1)== &
868 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(1) ) .AND.&
869 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(1) == &
870 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(1) ) .AND.&
871 (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(3)== &
872 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(3) ) .AND.&
873 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(3) == &
874 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(3)) )THEN
876 ! We can concatenate these two patches in second dimension
877 ! WRITE(mess,"('Can concatenate patches ',I3,' and ',I3,' in dim 2')") ipatch, jpatch
878 ! CALL wrf_message(mess)
880 ! Grow patch ipatch to include jpatch
881 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(2) = &
882 outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(2)
883 CALL merge_patches(ibuf, ipatch, jpatch)
891 ! Try the third dimension
892 IF(outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(3) == &
893 (outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(3) - 1) )THEN
895 ! Patches contiguous in second dimension - do they have the same
896 ! extents in the other two dimensions?
897 IF( (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(1)== &
898 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(1) ) .AND.&
899 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(1) == &
900 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(1) ) .AND.&
901 (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(2)== &
902 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(2) ) .AND.&
903 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(2) == &
904 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(2)) )THEN
906 ! We can concatenate these two patches in the third dimension
907 ! WRITE(mess,"('Can concatenate patches ',I3,' and ',I3,' in dim 3')") ipatch, jpatch
908 ! CALL wrf_message(mess)
910 ! Grow patch ipatch to include jpatch
911 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(3) = &
912 outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(3)
913 CALL merge_patches(ibuf, ipatch, jpatch)
921 IF(outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(3) == &
922 (outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(3) + 1))THEN
924 ! Patches contiguous in second dimension - do they have the same
925 ! extents in the other two dimensions?
926 IF( (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(1)== &
927 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(1) ) .AND.&
928 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(1) == &
929 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(1) ) .AND.&
930 (outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(2)== &
931 outpatch_table(ibuf)%PatchList(ipatch)%PatchStart(2) ) .AND.&
932 (outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(2) == &
933 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(2)) )THEN
935 ! We can concatenate these two patches in the third dimension
936 ! WRITE(mess,"('Can concatenate patches ',I3,' and ',I3,' in dim 3')") ipatch, jpatch
937 ! CALL wrf_message(mess)
939 ! Grow patch ipatch to include jpatch
940 outpatch_table(ibuf)%PatchList(ipatch)%PatchEnd(3) = &
941 outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(3)
942 CALL merge_patches(ibuf, ipatch, jpatch)
958 DO jpatch=1,outpatch_table(ibuf)%npatch,1
960 IF ( outpatch_table(ibuf)%PatchList(jpatch)%forDeletion ) CYCLE
962 ! WRITE(mess,"('Patch ',I3,': [',I3,': ',I3,'],[',I3,':',I3,'],[',I3,':',I3,']')") jpatch, outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(1), &
963 ! outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(1), &
964 ! outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(2), &
965 ! outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(2), &
966 ! outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(3), &
967 ! outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(3)
968 ! CALL wrf_message(mess)
970 ! Count how many patches we're left with
971 npatches = npatches + 1
973 ! If no patches have been merged together to make this patch then we
974 ! don't have to do any more with it
975 IF(PatchCount(jpatch) == 1) CYCLE
977 ! Get the extent of this patch
978 newExtent(:) = outpatch_table(ibuf)%PatchList(jpatch)%PatchEnd(:) - &
979 outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(:) + 1
980 ! Allocate a buffer to hold all of its data
981 IF ( outpatch_table(ibuf)%FieldType .EQ. WRF_FLOAT ) THEN
982 ALLOCATE(rbuffer(newExtent(1), newExtent(2), newExtent(3)), &
984 ELSE IF ( outpatch_table(ibuf)%FieldType .EQ. WRF_INTEGER ) THEN
985 ALLOCATE(ibuffer(newExtent(1), newExtent(2), newExtent(3)), &
989 CALL wrf_error_fatal('stitch_outbuf_patches: unable to stitch patches as allocate for merge buffer failed.')
993 ! Copy data into this buffer from each of the patches that are being
995 IF( ASSOCIATED(rbuffer) )THEN
997 ! CALL start_timing()
999 DO ipatch=1,PatchCount(jpatch),1
1001 ii = JoinedPatches(ipatch, jpatch)
1003 ! Work out where to put it - the PatchList(i)%PatchStart() has been
1004 ! updated to hold the start of the newly quilted patch i. It will
1005 ! therefore be less than or equal to the starts of each of the
1006 ! constituent patches.
1007 pos(:) = OldPatchStart(:,ii) - &
1008 outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(:) + 1
1009 ! Do the copy - can use the PatchExtent data here because that
1010 ! wasn't modified during the stitching of the patches.
1012 rbuffer(pos(1): pos(1)+outpatch_table(ibuf)%PatchList(ii)%PatchExtent(1)-1, &
1013 pos(2): pos(2)+outpatch_table(ibuf)%PatchList(ii)%PatchExtent(2)-1, &
1014 pos(3): pos(3)+outpatch_table(ibuf)%PatchList(ii)%PatchExtent(3)-1 ) &
1016 outpatch_table(ibuf)%PatchList(ii)%rptr(:, :, :)
1018 ! Having copied the data from this patch, we can free-up the
1020 DEALLOCATE(outpatch_table(ibuf)%PatchList(ii)%rptr)
1023 ! CALL end_timing("Data copy into new real patch")
1025 ! Re-assign the pointer associated with this patch to the new,
1026 ! larger, buffer containing the quilted patches
1027 outpatch_table(ibuf)%PatchList(jpatch)%rptr => rbuffer
1029 ! Unset the original pointer to this buffer
1032 ELSE IF( ASSOCIATED(ibuffer) )THEN
1034 ! CALL start_timing()
1036 DO ipatch=1,PatchCount(jpatch),1
1038 ii = JoinedPatches(ipatch, jpatch)
1040 ! Work out where to put it
1041 pos(:) = OldPatchStart(:,ii) - &
1042 outpatch_table(ibuf)%PatchList(jpatch)%PatchStart(:) + 1
1043 ! Do the copy - can use the PatchExtent data here because that
1044 ! wasn't modified during the stitching of the patches.
1046 pos(1)+outpatch_table(ibuf)%PatchList(ii)%PatchExtent(1)-1, &
1048 pos(2)+outpatch_table(ibuf)%PatchList(ii)%PatchExtent(2)-1, &
1050 pos(3)+outpatch_table(ibuf)%PatchList(ii)%PatchExtent(3)-1 ) = &
1051 outpatch_table(ibuf)%PatchList(ii)%iptr(:, :, :)
1053 DEALLOCATE(outpatch_table(ibuf)%PatchList(ii)%iptr)
1056 ! CALL end_timing("Data copy into new integer patch")
1058 ! Re-assign the pointer associated with this patch to the new,
1059 ! larger, buffer containing the quilted patches
1060 outpatch_table(ibuf)%PatchList(jpatch)%iptr => ibuffer
1067 WRITE(mess,*) "--------------------------"
1068 CALL wrf_debug ( 200, TRIM( mess ) )
1070 ! Record how many patches we're left with
1071 outpatch_table(ibuf)%nPatch = npatches
1073 DEALLOCATE(OldPatchStart, JoinedPatches, PatchCount)
1075 ! CALL end_timing("stitch patches")
1077 END SUBROUTINE stitch_outbuf_patches
1079 !-------------------------------------------------------------------------
1080 SUBROUTINE merge_patches(itab, ipatch, jpatch)
1081 INTEGER, INTENT(in) :: itab, ipatch, jpatch
1082 ! Merge patch jpatch into patch ipatch and then 'delete' jpatch
1085 ! Keep track of which patches we've merged: ipatch takes
1086 ! on all of the original patches which currently make up
1088 DO ii=1,PatchCount(jpatch),1
1089 PatchCount(ipatch) = PatchCount(ipatch) + 1
1090 JoinedPatches(PatchCount(ipatch),ipatch) = JoinedPatches(ii,jpatch)
1092 ! and mark patch jpatch for deletion
1093 outpatch_table(itab)%PatchList(jpatch)%forDeletion = .TRUE.
1094 ! decrement the count of active patches
1095 outpatch_table(itab)%nActivePatch = outpatch_table(itab)%nActivePatch - 1
1097 END SUBROUTINE merge_patches
1099 END MODULE module_quilt_outbuf_ops
1101 ! don't let other programs see the definition of this; type mismatches
1102 ! on inbuf will result; may want to make a module program at some point
1103 SUBROUTINE store_patch_in_outbuf( inbuf_r, inbuf_i, DateStr, VarName , FieldType, MemoryOrder, Stagger, DimNames, &
1104 DomainStart , DomainEnd , &
1105 MemoryStart , MemoryEnd , &
1106 PatchStart , PatchEnd )
1109 ! This routine does the "output quilting".
1111 ! It stores a patch in the appropriate location in a domain-sized array
1112 ! within an element of the outbuf_table data structure. DateStr, VarName, and
1113 ! MemoryOrder are used to uniquely identify which element of outbuf_table is
1114 ! associated with this array. If no element is associated, then this routine
1115 ! first assigns an unused element and allocates space within that element for
1116 ! the globally-sized array. This routine also stores DateStr, VarName,
1117 ! FieldType, MemoryOrder, Stagger, DimNames, DomainStart, and DomainEnd within
1118 ! the same element of outbuf.
1121 USE module_quilt_outbuf_ops
1123 #include "wrf_io_flags.h"
1124 INTEGER , INTENT(IN) :: FieldType
1125 REAL , DIMENSION(*) , INTENT(IN) :: inbuf_r
1126 INTEGER , DIMENSION(*) , INTENT(IN) :: inbuf_i
1127 INTEGER , DIMENSION(3) , INTENT(IN) :: DomainStart , DomainEnd , MemoryStart , MemoryEnd , PatchStart , PatchEnd
1128 CHARACTER*(*) , INTENT(IN) :: DateStr , VarName, MemoryOrder , Stagger, DimNames(3)
1130 CHARACTER*256 :: mess
1131 INTEGER :: l,m,n,ii,jj
1134 ! Find the VarName if it's in the buffer already
1137 DO WHILE ( .NOT. found .AND. ii .LE. num_entries )
1138 !TBH: need to test other attributes too!
1139 IF ( TRIM(VarName) .EQ. TRIM(outbuf_table(ii)%VarName) ) THEN
1140 IF ( TRIM(DateStr) .EQ. TRIM(outbuf_table(ii)%DateStr) ) THEN
1141 IF ( TRIM(MemoryOrder) .EQ. TRIM(outbuf_table(ii)%MemoryOrder) ) THEN
1144 CALL wrf_error_fatal("store_patch_in_outbuf: memory order disagreement")
1147 CALL wrf_error_fatal("store_patch_in_outbuf: multiple dates in buffer")
1153 IF ( .NOT. found ) THEN
1154 num_entries = num_entries + 1
1155 IF ( FieldType .EQ. WRF_FLOAT ) THEN
1156 ALLOCATE( outbuf_table(num_entries)%rptr(DomainStart(1):DomainEnd(1), &
1157 DomainStart(2):DomainEnd(2),DomainStart(3):DomainEnd(3)) )
1158 ELSE IF ( FieldType .EQ. WRF_INTEGER ) THEN
1159 ALLOCATE( outbuf_table(num_entries)%iptr(DomainStart(1):DomainEnd(1), &
1160 DomainStart(2):DomainEnd(2),DomainStart(3):DomainEnd(3)) )
1162 write(mess,*)"store_patch_in_outbuf: unsupported type ", FieldType
1163 CALL wrf_error_fatal(mess)
1165 outbuf_table(num_entries)%VarName = TRIM(VarName)
1166 outbuf_table(num_entries)%DateStr = TRIM(DateStr)
1167 outbuf_table(num_entries)%MemoryOrder = TRIM(MemoryOrder)
1168 outbuf_table(num_entries)%Stagger = TRIM(Stagger)
1169 outbuf_table(num_entries)%DimNames(1) = TRIM(DimNames(1))
1170 outbuf_table(num_entries)%DimNames(2) = TRIM(DimNames(2))
1171 outbuf_table(num_entries)%DimNames(3) = TRIM(DimNames(3))
1172 outbuf_table(num_entries)%DomainStart = DomainStart
1173 outbuf_table(num_entries)%DomainEnd = DomainEnd
1174 outbuf_table(num_entries)%FieldType = FieldType
1178 IF ( FieldType .EQ. WRF_FLOAT ) THEN
1179 DO n = PatchStart(3),PatchEnd(3)
1180 DO m = PatchStart(2),PatchEnd(2)
1181 DO l = PatchStart(1),PatchEnd(1)
1182 outbuf_table(ii)%rptr(l,m,n) = inbuf_r(jj)
1188 IF ( FieldType .EQ. WRF_INTEGER ) THEN
1189 DO n = PatchStart(3),PatchEnd(3)
1190 DO m = PatchStart(2),PatchEnd(2)
1191 DO l = PatchStart(1),PatchEnd(1)
1192 outbuf_table(ii)%iptr(l,m,n) = inbuf_i(jj)
1201 END SUBROUTINE store_patch_in_outbuf
1203 ! don't let other programs see the definition of this; type mismatches
1204 ! on inbuf will result; may want to make a module program at some point
1205 SUBROUTINE store_patch_in_outbuf_pnc( inbuf_r, inbuf_i, DateStr, VarName , &
1206 FieldType, MemoryOrder, Stagger, &
1208 DomainStart , DomainEnd , &
1209 MemoryStart , MemoryEnd , &
1210 PatchStart , PatchEnd , &
1214 ! This routine stores a patch in an array within an element of the
1215 ! outpatch_table%PatchList data structure. DateStr, VarName, and
1216 ! MemoryOrder are used to uniquely identify which element of outpatch_table is
1217 ! associated with this array. If no element is associated, then this routine
1218 ! first assigns an unused element and allocates space within that element.
1219 ! This routine also stores DateStr, VarName,
1220 ! FieldType, MemoryOrder, Stagger, DimNames, DomainStart, and DomainEnd within
1221 ! the same element of outpatch.
1224 USE module_quilt_outbuf_ops, Only: outpatch_table, tabsize, num_entries
1227 #include "wrf_io_flags.h"
1228 INTEGER , INTENT(IN) :: FieldType
1229 REAL , DIMENSION(*), INTENT(IN) :: inbuf_r
1230 INTEGER , DIMENSION(*), INTENT(IN) :: inbuf_i
1231 INTEGER , DIMENSION(3), INTENT(IN) :: DomainStart, DomainEnd, MemoryStart,&
1232 MemoryEnd , PatchStart , PatchEnd
1233 CHARACTER*(*) , INTENT(IN) :: DateStr , VarName, MemoryOrder , &
1234 Stagger, DimNames(3)
1235 INTEGER, INTENT(IN) :: ntasks ! Number of compute tasks associated with
1238 CHARACTER*256 :: mess
1239 INTEGER :: l,m,n,ii,jj,ipatch,ierr
1242 ! CALL start_timing()
1244 ! Find the VarName if it's in the buffer already
1247 DO WHILE ( .NOT. found .AND. ii .LE. num_entries )
1248 !TBH: need to test other attributes too!
1249 IF ( TRIM(VarName) .EQ. TRIM(outpatch_table(ii)%VarName) ) THEN
1250 IF ( TRIM(DateStr) .EQ. TRIM(outpatch_table(ii)%DateStr) ) THEN
1251 IF ( TRIM(MemoryOrder) .EQ. TRIM(outpatch_table(ii)%MemoryOrder) ) THEN
1254 CALL wrf_error_fatal("store_patch_in_outbuf_pnc: memory order disagreement")
1257 CALL wrf_error_fatal("store_patch_in_outbuf_pnc: multiple dates in buffer")
1263 IF ( .NOT. found ) THEN
1264 num_entries = num_entries + 1
1265 IF(num_entries > tabsize)THEN
1266 WRITE(mess,*) 'Number of entries in outpatch_table has exceeded tabsize (',&
1267 tabsize,') in module_quilt_outbuf_ops::store_patch_in_outbuf_pnc'
1268 CALL wrf_error_fatal(mess)
1270 outpatch_table(num_entries)%npatch = 0
1272 outpatch_table(num_entries)%VarName = TRIM(VarName)
1273 outpatch_table(num_entries)%DateStr = TRIM(DateStr)
1274 outpatch_table(num_entries)%MemoryOrder = TRIM(MemoryOrder)
1275 outpatch_table(num_entries)%Stagger = TRIM(Stagger)
1276 outpatch_table(num_entries)%DimNames(1) = TRIM(DimNames(1))
1277 outpatch_table(num_entries)%DimNames(2) = TRIM(DimNames(2))
1278 outpatch_table(num_entries)%DimNames(3) = TRIM(DimNames(3))
1279 outpatch_table(num_entries)%DomainStart = DomainStart
1280 outpatch_table(num_entries)%DomainEnd = DomainEnd
1281 outpatch_table(num_entries)%FieldType = FieldType
1282 ! Allocate the table for the list of patches for this output - it
1283 ! will have as many entries as there are compute tasks associated with
1285 IF ( ALLOCATED(outpatch_table(num_entries)%PatchList) ) &
1286 DEALLOCATE(outpatch_table(num_entries)%PatchList)
1287 ALLOCATE(outpatch_table(num_entries)%PatchList(ntasks), Stat=ierr)
1289 WRITE(mess,*)'num_entries ',num_entries,' ntasks ',ntasks,' ierr ',ierr
1290 CALL wrf_message(mess)
1291 WRITE(mess,*)'Allocation for ',ntasks, &
1292 ' patches in store_patch_in_outbuf_pnc() failed.'
1293 CALL wrf_error_fatal( mess )
1295 ! Initialise the list of patches
1297 outpatch_table(num_entries)%PatchList(ii)%forDeletion = .FALSE.
1298 NULLIFY(outpatch_table(num_entries)%PatchList(ii)%rptr)
1299 NULLIFY(outpatch_table(num_entries)%PatchList(ii)%iptr)
1300 outpatch_table(num_entries)%PatchList(ii)%PatchStart(:) = 0
1301 outpatch_table(num_entries)%PatchList(ii)%PatchEnd(:) = 0
1302 outpatch_table(num_entries)%PatchList(ii)%PatchExtent(:) = 0
1307 WRITE(mess,*)'Adding field entry no. ',num_entries
1308 CALL wrf_debug ( 200, TRIM( mess ) )
1309 WRITE(mess,*)'Variable = ',TRIM(VarName)
1310 CALL wrf_debug ( 200, TRIM( mess ) )
1311 WRITE(mess,*)'Domain start = ',DomainStart(:)
1312 CALL wrf_debug ( 200, TRIM( mess ) )
1313 WRITE(mess,*)'Domain end = ',DomainEnd(:)
1314 CALL wrf_debug ( 200, TRIM( mess ) )
1317 ! We only store > 1 patch if the field has two or more dimensions. Scalars
1318 ! and 1D arrays are replicated across compute nodes and therefore we only
1319 ! need keep a single patch.
1320 IF(LEN_TRIM(outpatch_table(ii)%MemoryOrder) >= 2 .OR. &
1321 outpatch_table(ii)%npatch < 1)THEN
1324 outpatch_table(ii)%npatch = outpatch_table(ii)%npatch + 1
1325 outpatch_table(ii)%nActivePatch = outpatch_table(ii)%npatch
1327 ipatch = outpatch_table(ii)%npatch
1329 outpatch_table(ii)%PatchList(ipatch)%PatchStart(:) = PatchStart(:)
1330 outpatch_table(ii)%PatchList(ipatch)%PatchEnd(:) = PatchEnd(:)
1331 outpatch_table(ii)%PatchList(ipatch)%PatchExtent(:)= PatchEnd(:) - PatchStart(:) + 1
1335 IF ( FieldType .EQ. WRF_FLOAT ) THEN
1336 ALLOCATE( outpatch_table(ii)%PatchList(ipatch)%rptr( &
1337 outpatch_table(ii)%PatchList(ipatch)%PatchExtent(1), &
1338 outpatch_table(ii)%PatchList(ipatch)%PatchExtent(2), &
1339 outpatch_table(ii)%PatchList(ipatch)%PatchExtent(3)),&
1341 ELSE IF ( FieldType .EQ. WRF_INTEGER ) THEN
1342 ALLOCATE( outpatch_table(ii)%PatchList(ipatch)%iptr( &
1343 outpatch_table(ii)%PatchList(ipatch)%PatchExtent(1), &
1344 outpatch_table(ii)%PatchList(ipatch)%PatchExtent(2), &
1345 outpatch_table(ii)%PatchList(ipatch)%PatchExtent(3)),&
1348 WRITE(mess,*)"store_patch_in_outbuf_pnc: unsupported type ", FieldType
1349 CALL wrf_error_fatal(mess)
1353 WRITE(mess,*)"store_patch_in_outbuf_pnc: failed to allocate memory to hold patch for var. ", TRIM(VarName)
1354 CALL wrf_error_fatal(mess)
1359 WRITE(mess,"('Variable ',(A),', patch ',I3,': (',I3,':',I3,',',I3,':',I3,',',I3,':',I3,')')")&
1360 TRIM(outpatch_table(ii)%VarName), &
1362 PatchStart(1),PatchEnd(1), &
1363 PatchStart(2),PatchEnd(2), &
1364 PatchStart(3),PatchEnd(3)
1365 CALL wrf_debug ( 200, TRIM( mess ) )
1367 IF ( FieldType .EQ. WRF_FLOAT ) THEN
1368 DO n = 1,outpatch_table(ii)%PatchList(ipatch)%PatchExtent(3),1
1369 DO m = 1,outpatch_table(ii)%PatchList(ipatch)%PatchExtent(2),1
1370 DO l = 1,outpatch_table(ii)%PatchList(ipatch)%PatchExtent(1),1
1371 outpatch_table(ii)%PatchList(ipatch)%rptr(l,m,n) = inbuf_r(jj)
1377 IF ( FieldType .EQ. WRF_INTEGER ) THEN
1378 DO n = 1,outpatch_table(ii)%PatchList(ipatch)%PatchExtent(3),1
1379 DO m = 1,outpatch_table(ii)%PatchList(ipatch)%PatchExtent(2),1
1380 DO l = 1,outpatch_table(ii)%PatchList(ipatch)%PatchExtent(1),1
1381 outpatch_table(ii)%PatchList(ipatch)%iptr(l,m,n) = inbuf_i(jj)
1388 END IF ! We need to add another patch
1390 ! CALL end_timing("store patch in outbuf")
1394 END SUBROUTINE store_patch_in_outbuf_pnc
1396 !call add_to_bufsize_for_field( VarName, hdrbufsize+chunksize )
1398 SUBROUTINE add_to_bufsize_for_field( VarName, Nbytes )
1401 ! This routine is a wrapper for C routine add_to_bufsize_for_field_c() that
1402 ! is used to accumulate buffer sizes. Buffer size Nbytes is added to the
1403 ! curent buffer size for the buffer named VarName. Any buffer space
1404 ! associated with VarName is freed. If a buffer named VarName does not exist,
1405 ! a new one is assigned and its size is set to Nbytes.
1408 USE module_quilt_outbuf_ops
1410 CHARACTER*(*) , INTENT(IN) :: VarName
1411 INTEGER , INTENT(IN) :: Nbytes
1413 CHARACTER*256 :: mess
1415 INTEGER :: VarNameAsInts( 256 )
1416 VarNameAsInts( 1 ) = len(trim(VarName))
1417 DO i = 2, len(trim(VarName)) + 1
1418 VarNameAsInts( i ) = ICHAR( VarName(i-1:i-1) )
1420 CALL add_to_bufsize_for_field_c ( VarNameAsInts, Nbytes )
1422 END SUBROUTINE add_to_bufsize_for_field
1424 SUBROUTINE store_piece_of_field( inbuf, VarName, Nbytes )
1427 ! This routine is a wrapper for C routine store_piece_of_field_c() that
1428 ! is used to store pieces of a field in an internal buffer. Nbytes bytes of
1429 ! buffer inbuf are appended to the end of the internal buffer named VarName.
1430 ! An error occurs if either an internal buffer named VarName does not exist or
1431 ! if there are fewer than Nbytes bytes left in the internal buffer.
1434 USE module_quilt_outbuf_ops
1436 INTEGER , INTENT(IN) :: Nbytes
1437 INTEGER , DIMENSION(*) , INTENT(IN) :: inbuf
1438 CHARACTER*(*) , INTENT(IN) :: VarName
1440 CHARACTER*256 :: mess
1442 INTEGER :: VarNameAsInts( 256 )
1444 VarNameAsInts( 1 ) = len(trim(VarName))
1445 DO i = 2, len(trim(VarName)) + 1
1446 VarNameAsInts( i ) = ICHAR( VarName(i-1:i-1) )
1448 CALL store_piece_of_field_c ( inbuf, VarNameAsInts, Nbytes, ierr )
1449 IF ( ierr .NE. 0 ) CALL wrf_error_fatal ( "store_piece_of_field" )
1451 END SUBROUTINE store_piece_of_field
1453 SUBROUTINE retrieve_pieces_of_field( outbuf, VarName, obufsz, Nbytes_tot, lret )
1456 ! This routine is a wrapper for C routine retrieve_pieces_of_field_c() that
1457 ! is used to extract the entire contents (i.e. all previously stored pieces of
1458 ! fields) of the next internal buffer. The name associated with this internal
1459 ! buffer is returned in VarName. The number of bytes read is returned in
1460 ! Nbytes_tot. Bytes are stored in outbuf whose size (in bytes) is obufsz.
1461 ! If there are more than obufsz bytes left in the next internal buffer, then
1462 ! only obufsz bytes are returned and the rest are discarded (probably an error
1463 ! in the making!). The internal buffer is then freed. Flag lret is set to
1464 ! .TRUE. iff there are more fields left to extract.
1467 USE module_quilt_outbuf_ops
1469 INTEGER , INTENT(IN) :: obufsz
1470 INTEGER , INTENT(OUT) :: Nbytes_tot
1471 INTEGER , DIMENSION(*) , INTENT(OUT) :: outbuf
1472 CHARACTER*(*) , INTENT(OUT) :: VarName
1473 LOGICAL :: lret ! true if more, false if not
1475 CHARACTER*256 :: mess
1477 INTEGER :: VarNameAsInts( 256 )
1479 CALL retrieve_pieces_of_field_c ( outbuf, VarNameAsInts, obufsz, Nbytes_tot, iret )
1480 IF ( iret .NE. 0 ) THEN
1485 DO i = 2, VarNameAsInts(1) + 1
1486 VarName(i-1:i-1) = CHAR(VarNameAsInts( i ))
1490 END SUBROUTINE retrieve_pieces_of_field