Skip to content

Commit

Permalink
Replaced 0,6 with stderr,stdout
Browse files Browse the repository at this point in the history
- Following @marshallward's suggestion we now use stderr and stdout for
  directing messages in unit tests. These are set from output_unit and
  error_unit in iso_fortran_env rather than FMS/mpp.F90. The latter
  is normally used, and should be for error/warning/note messaging, but
  in the unit tests we need to be in direct control of where messages
  appear.
  • Loading branch information
adcroft committed Apr 8, 2020
1 parent 3006337 commit 3767883
Show file tree
Hide file tree
Showing 6 changed files with 92 additions and 75 deletions.
20 changes: 11 additions & 9 deletions src/ALE/MOM_remapping.F90
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,8 @@ module MOM_remapping
use PPM_functions, only : PPM_reconstruction, PPM_boundary_extrapolation
use PQM_functions, only : PQM_reconstruction, PQM_boundary_extrapolation_v1

use iso_fortran_env, only : stdout=>output_unit, stderr=>error_unit

implicit none ; private

#include <MOM_memory.h>
Expand Down Expand Up @@ -1899,13 +1901,13 @@ logical function test_answer(verbose, n, u, u_true, label, tol)
if (abs(u(k) - u_true(k)) > tolerance) test_answer = .true.
enddo
if (test_answer .or. verbose) then
write(*,'(a4,2a24,x,a)') 'k','Calculated value','Correct value',label
write(stdout,'(a4,2a24,x,a)') 'k','Calculated value','Correct value',label
do k = 1, n
if (abs(u(k) - u_true(k)) > tolerance) then
write(*,'(i4,1p2e24.16,a,1pe24.16,a)') k,u(k),u_true(k),' err=',u(k)-u_true(k),' < wrong'
write(0,'(i4,1p2e24.16,a,1pe24.16,a)') k,u(k),u_true(k),' err=',u(k)-u_true(k),' < wrong'
write(stdout,'(i4,1p2e24.16,a,1pe24.16,a)') k,u(k),u_true(k),' err=',u(k)-u_true(k),' < wrong'
write(stderr,'(i4,1p2e24.16,a,1pe24.16,a)') k,u(k),u_true(k),' err=',u(k)-u_true(k),' < wrong'
else
write(*,'(i4,1p2e24.16)') k,u(k),u_true(k)
write(stdout,'(i4,1p2e24.16)') k,u(k),u_true(k)
endif
enddo
endif
Expand All @@ -1919,11 +1921,11 @@ subroutine dumpGrid(n,h,x,u)
real, dimension(:), intent(in) :: x !< Interface delta
real, dimension(:), intent(in) :: u !< Cell average values
integer :: i
write(*,'("i=",20i10)') (i,i=1,n+1)
write(*,'("x=",20es10.2)') (x(i),i=1,n+1)
write(*,'("i=",5x,20i10)') (i,i=1,n)
write(*,'("h=",5x,20es10.2)') (h(i),i=1,n)
write(*,'("u=",5x,20es10.2)') (u(i),i=1,n)
write(stdout,'("i=",20i10)') (i,i=1,n+1)
write(stdout,'("x=",20es10.2)') (x(i),i=1,n+1)
write(stdout,'("i=",5x,20i10)') (i,i=1,n)
write(stdout,'("h=",5x,20es10.2)') (h(i),i=1,n)
write(stdout,'("u=",5x,20es10.2)') (u(i),i=1,n)
end subroutine dumpGrid

end module MOM_remapping
30 changes: 16 additions & 14 deletions src/framework/MOM_diag_vkernels.F90
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,8 @@ module MOM_diag_vkernels

! This file is part of MOM6. See LICENSE.md for the license.

use iso_fortran_env, only : stdout=>output_unit, stderr=>error_unit

implicit none ; private

public diag_vkernels_unit_tests
Expand Down Expand Up @@ -173,8 +175,8 @@ logical function diag_vkernels_unit_tests(verbose)

v = verbose

write(6,*) '==== MOM_diag_kernels: diag_vkernels_unit_tests =========='
if (v) write(6,*) '- - - - - - - - - - interpolation tests - - - - - - - - -'
write(stdout,*) '==== MOM_diag_kernels: diag_vkernels_unit_tests =========='
if (v) write(stdout,*) '- - - - - - - - - - interpolation tests - - - - - - - - -'

fail = test_interp(v,mv,'Identity: 3 layer', &
3, (/1.,2.,3./), (/1.,2.,3.,4./), &
Expand Down Expand Up @@ -221,7 +223,7 @@ logical function diag_vkernels_unit_tests(verbose)
4, (/0.,2.,6.,0./), (/mv,1.,3.,8.,mv/) )
diag_vkernels_unit_tests = diag_vkernels_unit_tests .or. fail

if (v) write(6,*) '- - - - - - - - - - reintegration tests - - - - - - - - -'
if (v) write(stdout,*) '- - - - - - - - - - reintegration tests - - - - - - - - -'

fail = test_reintegrate(v,mv,'Identity: 3 layer', &
3, (/1.,2.,3./), (/-5.,2.,1./), &
Expand Down Expand Up @@ -273,7 +275,7 @@ logical function diag_vkernels_unit_tests(verbose)
3, (/0.,0.,0./), (/mv, mv, mv/) )
diag_vkernels_unit_tests = diag_vkernels_unit_tests .or. fail

if (.not. fail) write(*,*) 'Pass'
if (.not. fail) write(stdout,*) 'Pass'

end function diag_vkernels_unit_tests

Expand Down Expand Up @@ -302,15 +304,15 @@ logical function test_interp(verbose, missing_value, msg, nsrc, h_src, u_src, nd
if (u_dest(k)/=u_true(k)) test_interp = .true.
enddo
if (verbose .or. test_interp) then
write(6,'(2a)') ' Test: ',msg
write(6,'(a3,3(a24))') 'k','u_result','u_true','error'
write(stdout,'(2a)') ' Test: ',msg
write(stdout,'(a3,3(a24))') 'k','u_result','u_true','error'
do k=1,ndest+1
error = u_dest(k)-u_true(k)
if (error==0.) then
write(6,'(i3,3(1pe24.16))') k,u_dest(k),u_true(k),u_dest(k)-u_true(k)
write(stdout,'(i3,3(1pe24.16))') k,u_dest(k),u_true(k),u_dest(k)-u_true(k)
else
write(6,'(i3,3(1pe24.16),x,a)') k,u_dest(k),u_true(k),u_dest(k)-u_true(k),'<--- WRONG!'
write(0,'(i3,3(1pe24.16),x,a)') k,u_dest(k),u_true(k),u_dest(k)-u_true(k),'<--- WRONG!'
write(stdout,'(i3,3(1pe24.16),x,a)') k,u_dest(k),u_true(k),u_dest(k)-u_true(k),'<--- WRONG!'
write(stderr,'(i3,3(1pe24.16),x,a)') k,u_dest(k),u_true(k),u_dest(k)-u_true(k),'<--- WRONG!'
endif
enddo
endif
Expand Down Expand Up @@ -341,15 +343,15 @@ logical function test_reintegrate(verbose, missing_value, msg, nsrc, h_src, uh_s
if (uh_dest(k)/=uh_true(k)) test_reintegrate = .true.
enddo
if (verbose .or. test_reintegrate) then
write(6,'(2a)') ' Test: ',msg
write(6,'(a3,3(a24))') 'k','uh_result','uh_true','error'
write(stdout,'(2a)') ' Test: ',msg
write(stdout,'(a3,3(a24))') 'k','uh_result','uh_true','error'
do k=1,ndest
error = uh_dest(k)-uh_true(k)
if (error==0.) then
write(6,'(i3,3(1pe24.16))') k,uh_dest(k),uh_true(k),uh_dest(k)-uh_true(k)
write(stdout,'(i3,3(1pe24.16))') k,uh_dest(k),uh_true(k),uh_dest(k)-uh_true(k)
else
write(6,'(i3,3(1pe24.16),x,a)') k,uh_dest(k),uh_true(k),uh_dest(k)-uh_true(k),'<--- WRONG!'
write(0,'(i3,3(1pe24.16),x,a)') k,uh_dest(k),uh_true(k),uh_dest(k)-uh_true(k),'<--- WRONG!'
write(stdout,'(i3,3(1pe24.16),x,a)') k,uh_dest(k),uh_true(k),uh_dest(k)-uh_true(k),'<--- WRONG!'
write(stderr,'(i3,3(1pe24.16),x,a)') k,uh_dest(k),uh_true(k),uh_dest(k)-uh_true(k),'<--- WRONG!'
endif
enddo
endif
Expand Down
16 changes: 9 additions & 7 deletions src/framework/MOM_random.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,8 @@ module MOM_random
use MersenneTwister_mod, only : getRandomReal ! Generates a random number
use MersenneTwister_mod, only : getRandomPositiveInt ! Generates a random positive integer

use iso_fortran_env, only : stdout=>output_unit, stderr=>error_unit

implicit none ; private

public :: random_0d_constructor
Expand Down Expand Up @@ -205,7 +207,7 @@ logical function random_unit_tests(verbose)
HI%jdg_offset = 0

random_unit_tests = .false.
stdunit = 6
stdunit = stdout
write(stdunit,'(1x,a)') '==== MOM_random: random_unit_tests ======================='

if (verbose) write(stdunit,'(1x,"random: ",a)') '-- Time-based seeds ---------------------'
Expand Down Expand Up @@ -417,17 +419,17 @@ logical function test_fn(verbose, good, label, rvalue, ivalue)

if (present(ivalue)) then
if (.not. good) then
write(6,'(1x,a,i10,1x,a,a)') 'random: result =',ivalue,label,' <------- FAIL!'
write(0,'(1x,a,i10,1x,a,a)') 'random: result =',ivalue,label,' <------- FAIL!'
write(stdout,'(1x,a,i10,1x,a,a)') 'random: result =',ivalue,label,' <------- FAIL!'
write(stderr,'(1x,a,i10,1x,a,a)') 'random: result =',ivalue,label,' <------- FAIL!'
elseif (verbose) then
write(6,'(1x,a,i10,1x,a)') 'random: result =',ivalue,label
write(stdout,'(1x,a,i10,1x,a)') 'random: result =',ivalue,label
endif
else
if (.not. good) then
write(6,'(1x,a,1pe15.8,1x,a,a)') 'random: result =',rvalue,label,' <------- FAIL!'
write(0,'(1x,a,1pe15.8,1x,a,a)') 'random: result =',rvalue,label,' <------- FAIL!'
write(stdout,'(1x,a,1pe15.8,1x,a,a)') 'random: result =',rvalue,label,' <------- FAIL!'
write(stderr,'(1x,a,1pe15.8,1x,a,a)') 'random: result =',rvalue,label,' <------- FAIL!'
elseif (verbose) then
write(6,'(1x,a,1pe15.8,1x,a)') 'random: result =',rvalue,label
write(stdout,'(1x,a,1pe15.8,1x,a)') 'random: result =',rvalue,label
endif
endif
test_fn = .not. good
Expand Down
25 changes: 15 additions & 10 deletions src/framework/MOM_string_functions.F90
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@ module MOM_string_functions

! This file is part of MOM6. See LICENSE.md for the license.

use iso_fortran_env, only : stdout=>output_unit, stderr=>error_unit

implicit none ; private

public lowercase, uppercase
Expand Down Expand Up @@ -319,7 +321,7 @@ logical function string_functions_unit_tests(verbose)
logical :: fail, v
fail = .false.
v = verbose
write(*,*) '==== MOM_string_functions: string_functions_unit_tests ==='
write(stdout,*) '==== MOM_string_functions: string_functions_unit_tests ==='
fail = fail .or. localTestS(v,left_int(-1),'-1')
fail = fail .or. localTestS(v,left_ints(i(:)),'-1, 1, 3, 3, 0')
fail = fail .or. localTestS(v,left_real(0.),'0.0')
Expand Down Expand Up @@ -349,7 +351,7 @@ logical function string_functions_unit_tests(verbose)
fail = fail .or. localTestR(v,extract_real("1.,2.",",",2),2.)
fail = fail .or. localTestR(v,extract_real("1.,2.",",",3),0.)
fail = fail .or. localTestR(v,extract_real("1.,2.",",",4,4.),4.)
if (.not. fail) write(*,*) 'Pass'
if (.not. fail) write(stdout,*) 'Pass'
string_functions_unit_tests = fail
end function string_functions_unit_tests

Expand All @@ -361,10 +363,10 @@ logical function localTestS(verbose,str1,str2)
localTestS=.false.
if (trim(str1)/=trim(str2)) localTestS=.true.
if (localTestS .or. verbose) then
write(*,*) '>'//trim(str1)//'<'
write(stdout,*) '>'//trim(str1)//'<'
if (localTestS) then
write(*,*) trim(str1),':',trim(str2), '<-- FAIL'
write(0,*) trim(str1),':',trim(str2), '<-- FAIL'
write(stdout,*) trim(str1),':',trim(str2), '<-- FAIL'
write(stderr,*) trim(str1),':',trim(str2), '<-- FAIL'
endif
endif
end function localTestS
Expand All @@ -377,10 +379,10 @@ logical function localTestI(verbose,i1,i2)
localTestI=.false.
if (i1/=i2) localTestI=.true.
if (localTestI .or. verbose) then
write(*,*) i1,i2
write(stdout,*) i1,i2
if (localTestI) then
write(*,*) i1,'!=',i2, '<-- FAIL'
write(0,*) i1,'!=',i2, '<-- FAIL'
write(stdout,*) i1,'!=',i2, '<-- FAIL'
write(stderr,*) i1,'!=',i2, '<-- FAIL'
endif
endif
end function localTestI
Expand All @@ -393,8 +395,11 @@ logical function localTestR(verbose,r1,r2)
localTestR=.false.
if (r1/=r2) localTestR=.true.
if (localTestR .or. verbose) then
write(*,*) r1,r2
if (localTestR) write(*,*) r1,'!=',r2, '<-- FAIL'
write(stdout,*) r1,r2
if (localTestR) then
write(stdout,*) r1,'!=',r2, '<-- FAIL'
write(stderr,*) r1,'!=',r2, '<-- FAIL'
endif
endif
end function localTestR

Expand Down
10 changes: 6 additions & 4 deletions src/tracer/MOM_lateral_boundary_diffusion.F90
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,8 @@ module MOM_lateral_boundary_diffusion
use MOM_energetic_PBL, only : energetic_PBL_get_MLD, energetic_PBL_CS
use MOM_diabatic_driver, only : diabatic_CS, extract_diabatic_member

use iso_fortran_env, only : stdout=>output_unit, stderr=>error_unit

implicit none ; private

public near_boundary_unit_tests, lateral_boundary_diffusion, lateral_boundary_diffusion_init
Expand Down Expand Up @@ -987,7 +989,7 @@ logical function test_layer_fluxes(verbose, nk, test_name, F_calc, F_ans)
real, dimension(nk), intent(in) :: F_ans !< Fluxes of the unitless tracer calculated by hand [s^-1]
! Local variables
integer :: k
integer, parameter :: stdunit = 6
integer, parameter :: stdunit = stdout

test_layer_fluxes = .false.
do k=1,nk
Expand All @@ -997,8 +999,8 @@ logical function test_layer_fluxes(verbose, nk, test_name, F_calc, F_ans)
write(stdunit,10) k, F_calc(k), F_ans(k)
! ### Once these unit tests are passing, and failures are caught properly,
! we will post failure notifications to both stdout and stderr.
!write(0,*) "MOM_lateral_boundary_diffusion, UNIT TEST FAILED: ", test_name
!write(0,10) k, F_calc(k), F_ans(k)
!write(stderr,*) "MOM_lateral_boundary_diffusion, UNIT TEST FAILED: ", test_name
!write(stderr,10) k, F_calc(k), F_ans(k)
elseif (verbose) then
write(stdunit,10) k, F_calc(k), F_ans(k)
endif
Expand All @@ -1021,7 +1023,7 @@ logical function test_boundary_k_range(k_top, zeta_top, k_bot, zeta_bot, k_top_a
character(len=80) :: test_name !< Name of the unit test
logical :: verbose !< If true always print output

integer, parameter :: stdunit = 6
integer, parameter :: stdunit = stdout

test_boundary_k_range = k_top .ne. k_top_ans
test_boundary_k_range = test_boundary_k_range .or. (zeta_top .ne. zeta_top_ans)
Expand Down
Loading

0 comments on commit 3767883

Please sign in to comment.