Skip to content

Commit e330af8

Browse files
committed
computationall irrelevant: refined formatting of outputs
1 parent 5d701c5 commit e330af8

File tree

2 files changed

+22
-13
lines changed

2 files changed

+22
-13
lines changed

src/General/utils_h.f90

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -116,16 +116,21 @@ function locase(string) result(lower) !convert to lower case
116116
end do
117117
end function locase
118118

119-
function fmt_str(max_val, fieldwidth, decimals) result(fstr) !generate format string
119+
function fmt_str(max_val, decimals, fieldwidth) result(fstr) !generate format string
120120
real, intent(in) :: max_val
121-
integer, optional :: fieldwidth, decimals
121+
integer, optional, INTENT(IN) :: fieldwidth, decimals
122122
character(len=5) :: fstr
123-
integer :: digits, fw_req, fw=11, dec=3
124-
if (present(fieldwidth)) fw=fieldwidth !if specified, override defaults
123+
integer :: digits, fw_req
124+
integer :: fw=11, dec=3
125+
dec=3 !default values (sometimes, the assignment above doesn't seem to work)
126+
fw=11
127+
125128
if (present(decimals)) dec=decimals
129+
if (present(fieldwidth)) fw=fieldwidth !if specified, override defaults
126130

127131
digits=ceiling(log10(max(1.0,max_val)))+1 !Till: number of pre-decimal digits required
128132
fw_req=max(6, digits+1+dec) !total fieldwidth required
133+
!fw_req = 0 !use 'f0' notation for automatic formatting of pre-decimal digits
129134

130135
if (fw_req <= fw) then
131136
write(fstr,'(a,i0,a,i0)') 'f',fw_req,'.',dec !generate format string

src/Hillslope/hymo_all.f90

Lines changed: 13 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1290,7 +1290,7 @@ SUBROUTINE hymo_all(STATUS)
12901290
CALL write_subdaily_output_TC(f_snowWaterEquiv,'snowWaterEquiv.out', snowWaterEquiv)
12911291
CALL write_subdaily_output_TC(f_snowAlbedo,'snowAlbedo.out', snowAlbedo)
12921292
CALL write_subdaily_output_TC(f_snowCover,'snowCover.out', snowCover)
1293-
CALL write_subdaily_output_TC(f_snowTemp,'snowTemp.out', snowTemp)
1293+
CALL write_subdaily_output_TC(f_snowTemp,'snowTemp.out', snowTemp, 1)
12941294
CALL write_subdaily_output_TC(f_surfTemp,'surfTemp.out', surfTemp)
12951295
CALL write_subdaily_output_TC(f_liquFrac,'liquFrac.out', liquFrac)
12961296
CALL write_subdaily_output_TC(f_fluxPrec,'fluxPrec.out', fluxPrec)
@@ -1498,19 +1498,19 @@ SUBROUTINE open_subdaily_output_TC(f_flag,file_name,headerline)
14981498
END SUBROUTINE open_subdaily_output_TC
14991499

15001500

1501-
SUBROUTINE write_output(f_flag,file_name,value_array,spec_decimals)
1501+
SUBROUTINE write_output(f_flag, file_name, value_array, decimals)
15021502
! Output daily values of given array
15031503
use utils_h
15041504
IMPLICIT NONE
15051505
LOGICAL, INTENT(IN) :: f_flag
15061506
CHARACTER(len=*), INTENT(IN) :: file_name
15071507
REAL, INTENT(IN) :: value_array(:,:)
1508-
INTEGER, optional :: spec_decimals
1508+
INTEGER, optional :: decimals
15091509

15101510
IF (f_flag) THEN !if output file is enabled
15111511
OPEN(11,FILE=pfadn(1:pfadi)//file_name, STATUS='old',POSITION='append')
15121512

1513-
write(fmtstr,'(a,i0,a,a,a)') '(i0,a,i0,',subasin,'(a,',fmt_str(maxval(value_array)),'))' !generate format string
1513+
write(fmtstr,'(a,i0,a,a,a)') '(i0,a,i0,',subasin,'(a,',fmt_str(maxval(abs(value_array)), decimals),'))' !generate format string
15141514

15151515
DO d=1,dayyear
15161516
write(11,trim(fmtstr))t,char(9),d,(char(9),value_array(d,i),i=1,subasin)
@@ -1520,18 +1520,20 @@ SUBROUTINE write_output(f_flag,file_name,value_array,spec_decimals)
15201520
END IF
15211521
END SUBROUTINE write_output
15221522

1523-
SUBROUTINE write_subdaily_output(f_flag,file_name,value_array)
1523+
SUBROUTINE write_subdaily_output(f_flag,file_name,value_array, decimals)
15241524
! Output subdaily values of given array
15251525
use utils_h
15261526
IMPLICIT NONE
15271527
LOGICAL, INTENT(IN) :: f_flag
15281528
CHARACTER(len=*), INTENT(IN) :: file_name
1529-
REAL, POINTER :: value_array(:,:,:)
1529+
REAL, POINTER, INTENT(IN) :: value_array(:,:,:)
1530+
integer, optional, INTENT(IN) :: decimals
15301531

15311532
IF (f_flag) THEN !if output file is enabled
15321533
OPEN(11,FILE=pfadn(1:pfadi)//file_name, STATUS='old',POSITION='append')
15331534

1534-
write(fmtstr,'(a,i0,a,a,a)') '(i0,a,i0,a,i0,',subasin,'(a,',fmt_str(maxval(value_array)),'))' !generate format string
1535+
write(fmtstr,'(a,i0,a,a,a)') '(i0,a,i0,a,i0,',subasin,'(a,',fmt_str(maxval(abs(value_array)), decimals),'))' !generate format string
1536+
!write(fmtstr,'(a,i0,a,a,a)') '(i0,a,i0,a,i0,',subasin,'(a,','f0.8','))' !generate format string
15351537

15361538
DO d=1,dayyear
15371539
DO j=1,nt
@@ -1542,20 +1544,22 @@ SUBROUTINE write_subdaily_output(f_flag,file_name,value_array)
15421544
END IF
15431545
END SUBROUTINE write_subdaily_output
15441546

1545-
SUBROUTINE write_subdaily_output_TC(f_flag,file_name,value_array)
1547+
SUBROUTINE write_subdaily_output_TC(f_flag,file_name,value_array, decimals)
15461548
! Output subdaily values of given array on TC-scale
15471549
use utils_h
15481550
IMPLICIT NONE
15491551
LOGICAL, INTENT(IN) :: f_flag
15501552
CHARACTER(len=*), INTENT(IN) :: file_name
1551-
REAL, POINTER :: value_array(:,:,:)
1553+
REAL, POINTER, INTENT(IN) :: value_array(:,:,:)
1554+
integer, optional, INTENT(IN) :: decimals
15521555
INTEGER :: sb_counter, lu_counter, tc_counter, i_lu
15531556

15541557
IF (f_flag) THEN !if output file is enabled
15551558
OPEN(11,FILE=pfadn(1:pfadi)//file_name, STATUS='old',POSITION='append')
15561559

15571560
!fmtstr ='(6(i0,a),'//fmt_str(maxval(value_array)*10)//')' !generate format string
15581561
fmtstr ='(6(i0,a),E12.5)' !generate format string
1562+
write(fmtstr,'(a,a,a)') '(6(i0,a),', fmt_str(maxval(abs(value_array)), decimals),')' !generate format string
15591563

15601564
DO d=1,dayyear
15611565
DO j=1,nt

0 commit comments

Comments
 (0)