Skip to content

Commit

Permalink
modify global variables in wav_restart
Browse files Browse the repository at this point in the history
  • Loading branch information
DeniseWorthen committed Sep 19, 2024
1 parent 6527760 commit e51a32b
Show file tree
Hide file tree
Showing 3 changed files with 16 additions and 15 deletions.
5 changes: 3 additions & 2 deletions model/src/w3wavemd.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1278,7 +1278,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT &
tmpice(ix,iy) = ice(isea)
end do
do iy = 1,ny
write(iceio,'(360f8.2)')(tmpice(ix,iy),ix=1,nx)
write(iceio,'(360f8.4)')(tmpice(ix,iy),ix=1,nx)
end do
close(iceio)

Expand All @@ -1303,6 +1303,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT &
END IF
!
IF ( IDACT(13:13).NE.' ' ) THEN
if (iaproc == 1)print '(a,2f8.2,2(2i12))','YY1 call w3uice at ',dttst,dti0,time,tin
CALL W3UICE ( VA )
DTI0 = 0.
FLACT = .TRUE.
Expand All @@ -1328,7 +1329,7 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT &
tmpice(ix,iy) = ice(isea)
end do
do iy = 1,ny
write(iceio,'(360f8.2)')(tmpice(ix,iy),ix=1,nx)
write(iceio,'(360f8.4)')(tmpice(ix,iy),ix=1,nx)
end do
close(iceio)

Expand Down
1 change: 1 addition & 0 deletions model/src/wav_comp_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -390,6 +390,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
if (isPresent .and. isSet) addice=(trim(cvalue)=="true")
write(logmsg,*) addice
call ESMF_LogWrite('WW3_cap: Add ice to/from restart = '//trim(logmsg), ESMF_LOGMSG_INFO)

call advertise_fields(importState, exportState, flds_scalar_name, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

Expand Down
25 changes: 12 additions & 13 deletions model/src/wav_restart_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -226,8 +226,8 @@ subroutine read_restart (fname, va, mapsta, mapst2)

! local variables
type(MPI_Comm) :: wave_communicator ! needed for mpi_f08
integer :: global_input(nsea), global_output(nsea)
real :: rglobal_input(nsea), rglobal_output(nsea)
!integer :: global_input(nsea), global_output(nsea)
real :: global_input(nsea), global_output(nsea)
integer :: ifill
real :: rfill
real , allocatable :: lva(:,:)
Expand Down Expand Up @@ -324,25 +324,25 @@ subroutine read_restart (fname, va, mapsta, mapst2)
call handle_err(ierr, 'get variable _FillValue'//trim(vname))

! fill global array with PE local values
global_input = 0
global_output = 0
global_input = 0.0
global_output = 0.0
do jsea = 1,nseal_cpl
call init_get_isea(isea, jsea)
ix = mapsf(isea,1)
iy = mapsf(isea,2)
if (lmap(jsea) .ne. ifill) then
global_input(isea) = lmap(jsea)
global_input(isea) = real(lmap(jsea))
end if
end do
! reduce across all PEs to create global array
call MPI_AllReduce(global_input, global_output, nsea, MPI_INTEGER, MPI_SUM, wave_communicator, ierr)
call MPI_AllReduce(global_input, global_output, nsea, MPI_REAL, MPI_SUM, wave_communicator, ierr)

! fill global array on each PE
lmap2d = 0
do isea = 1,nsea
ix = mapsf(isea,1)
iy = mapsf(isea,2)
lmap2d(iy,ix) = global_output(isea)
lmap2d(iy,ix) = int(global_output(isea))
end do

mapsta = mod(lmap2d+2,8) - 2
Expand All @@ -358,25 +358,24 @@ subroutine read_restart (fname, va, mapsta, mapst2)
ierr = pio_get_att(pioid, varid, "_FillValue", rfill)
call handle_err(ierr, 'get variable _FillValue'//trim(vname))

! TODO: do mapsta reduction w/ reals, then only one set of global_in/out is required
! fill global array with PE local values
rglobal_input = 0.0
rglobal_output = 0.0
global_input = 0.0
global_output = 0.0
do jsea = 1,nseal_cpl
call init_get_isea(isea, jsea)
if (lmap(jsea) .ne. rfill) then
rglobal_input(isea) = lvar(jsea)
global_input(isea) = lvar(jsea)
end if
end do
! reduce across all PEs to create global array
call MPI_AllReduce(rglobal_input, rglobal_output, nsea, MPI_REAL, MPI_SUM, wave_communicator, ierr)
call MPI_AllReduce(global_input, global_output, nsea, MPI_REAL, MPI_SUM, wave_communicator, ierr)

! fill global array on each PE
ice = 0.0
do isea = 1,nsea
ix = mapsf(isea,1)
iy = mapsf(isea,2)
ice(isea) = rglobal_output(isea)
ice(isea) = global_output(isea)
end do
end if
call pio_syncfile(pioid)
Expand Down

0 comments on commit e51a32b

Please sign in to comment.