Skip to content

Commit

Permalink
Merge pull request #5 from bandre-ucar/file-macro-bugfix
Browse files Browse the repository at this point in the history
Fix line length issues caused by __FILE__ macro
  • Loading branch information
jinyun1tang committed May 10, 2016
2 parents 031a217 + 2909c6e commit 27329c0
Show file tree
Hide file tree
Showing 15 changed files with 59 additions and 32 deletions.
3 changes: 2 additions & 1 deletion src/betr/betr_core/BeTRTracerType.F90
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,8 @@ module BeTRTracerType
!
implicit none
private
character(len=*), parameter :: mod_filename = __FILE__
character(len=*), parameter :: mod_filename = &
__FILE__

!----------------------------------------------------
!betr tracer setup structure
Expand Down
3 changes: 2 additions & 1 deletion src/betr/betr_core/TracerParamsMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,8 @@ module TracerParamsMod
public :: calc_aerecond
public :: betr_annualupdate
!parameters
character(len=*), parameter :: filename = __FILE__
character(len=*), parameter :: filename = &
__FILE__
real(r8), parameter :: minval_diffus = 1.e-20_r8 !minimum diffusivity, m2/s
real(r8), parameter :: minval_airvol = 1.e-10_r8 !minimum air-filled volume

Expand Down
3 changes: 2 additions & 1 deletion src/betr/betr_main/BetrBGCMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,8 @@ module BetrBGCMod
real(r8), parameter :: tiny_val = 1.e-20_r8 !very small value, for tracer concentration etc.
real(r8), parameter :: dtime_min = 1._r8 !minimum time step 1 second
real(r8), parameter :: err_tol_transp = 1.e-8_r8 !error tolerance for tracer transport
character(len =*), parameter :: filename= __FILE__
character(len=*), parameter :: filename = &
__FILE__

public :: stage_tracer_transport
public :: surface_tracer_hydropath_update
Expand Down
17 changes: 10 additions & 7 deletions src/betr/betr_math/FindRootMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,9 @@ module FindRootMod
use MathfuncMod , only : is_bounded

implicit none

character(len=*), parameter :: mod_filename = &
__FILE__

contains
!-------------------------------------------------------------------------------
Expand Down Expand Up @@ -42,12 +45,12 @@ function quadrootbnd(a,b,c, xl, xr)result(x)
return
else
write(iulog,*)'no bounded solution for the given quadratic equation'
call endrun(msg=errmsg(__FILE__, __LINE__))
call endrun(msg=errmsg(mod_filename, __LINE__))
endif
endif
else
write(iulog,*)'no real solution for the given quadratic equation'
call endrun(msg=errmsg(__FILE__, __LINE__))
call endrun(msg=errmsg(mod_filename, __LINE__))
endif
return
end function quadrootbnd
Expand All @@ -73,7 +76,7 @@ function quadproot(a,b,c)result(x)
x = (-b + sqrt(delta))/2._r8
else
write(iulog,*)'no positive solution for the given quadratic equation'
call endrun(msg=errmsg(__FILE__, __LINE__))
call endrun(msg=errmsg(mod_filename, __LINE__))
endif
return
end function quadproot
Expand Down Expand Up @@ -109,7 +112,7 @@ function cubicrootbnd(a,b,c,d, xl, xr)result(x)
delta =-4._r8 * p**3._r8 - 27._r8 * q ** 2._r8
if(delta<0._r8)then
write(iulog,*)'no real solution for the given cubic equation'
call endrun(msg=errmsg(__FILE__, __LINE__))
call endrun(msg=errmsg(mod_filename, __LINE__))
else
n = sqrt(-4._r8*p/3._r8)
f = -q/2._r8 * (-p/3._r8)**(-1.5_r8)
Expand All @@ -131,7 +134,7 @@ function cubicrootbnd(a,b,c,d, xl, xr)result(x)
return
else
write(iulog,*)'no bounded solution for the given cubic equation'
call endrun(msg=errmsg(__FILE__, __LINE__))
call endrun(msg=errmsg(mod_filename, __LINE__))
endif
endif
endif
Expand Down Expand Up @@ -165,7 +168,7 @@ function cubicproot(a,b,c,d)result(x)
delta =-4._r8 * p**3._r8 - 27._r8 * q ** 2._r8
if(delta<0._r8)then
write(iulog,*)'no real solution for the given cubic equation'
call endrun(msg=errmsg(__FILE__, __LINE__))
call endrun(msg=errmsg(mod_filename, __LINE__))
else
n = sqrt(-4._r8*p/3._r8)
f = -q/2._r8 * (-p/3._r8)**(-1.5_r8)
Expand Down Expand Up @@ -393,7 +396,7 @@ end subroutine func
if((fa > 0._r8 .and. fb > 0._r8).or.(fa < 0._r8 .and. fb < 0._r8))then
write(iulog,*) 'root must be bracketed for brent'
write(iulog,*) 'a=',a,' b=',b,' fa=',fa,' fb=',fb
call endrun(msg=errmsg(__FILE__, __LINE__))
call endrun(msg=errmsg(mod_filename, __LINE__))
endif
c=b
fc=fb
Expand Down
7 changes: 5 additions & 2 deletions src/betr/betr_rxns/ReactionsFactory.F90
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,9 @@ module ReactionsFactory
use PlantSoilBGCMod , only : plant_soilbgc_type
implicit none

character(len=*), parameter :: mod_filename = &
__FILE__

private

public :: create_betr_def_application
Expand Down Expand Up @@ -66,7 +69,7 @@ function create_bgc_reaction_type(method) result(bgc_reaction)
allocate(bgc_reaction, source=bgc_reaction_h2oiso_type())
case default
write(iulog,*)subname //' ERROR: unknown method: ', method
call endrun(msg=errMsg(__FILE__, __LINE__))
call endrun(msg=errMsg(mod_filename, __LINE__))
end select
end function create_bgc_reaction_type
!-------------------------------------------------------------------------------
Expand Down Expand Up @@ -94,7 +97,7 @@ function create_plant_soilbgc_type(method)result(plant_soilbgc)
allocate(plant_soilbgc, source=plant_soilbgc_h2oiso_run_type())
case default
write(*, *)subname //' ERROR: unknown method: ', method
call endrun(msg=errMsg(__FILE__, __LINE__))
call endrun(msg=errMsg(mod_filename, __LINE__))
end select

end function create_plant_soilbgc_type
Expand Down
6 changes: 5 additions & 1 deletion src/betr/betr_util/bshr_log_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,10 @@ module bshr_log_mod
use bshr_kind_mod, only : SHR_KIND_CX

implicit none

character(len=*), parameter :: mod_filename = &
__FILE__

private

! !PUBLIC TYPES:
Expand Down Expand Up @@ -48,7 +52,7 @@ module bshr_log_mod
! !DESCRIPTION:
! Return an error message containing file & line info
! \newline
! errMsg = shr\_log\_errMsg(__FILE__, __LINE__)
! errMsg = shr\_log\_errMsg(mod_filename, __LINE__)
!
! !REVISION HISTORY:
! 2013-July-23 - Bill Sacks
Expand Down
3 changes: 2 additions & 1 deletion src/betr/betr_util/bshr_string_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1728,7 +1728,8 @@ function shr_string_listCreateField( numFields, strBase ) result ( retString )
character(*),parameter :: subName = "(shr_string_listCreateField) "
character(*),parameter :: F00 = "('(shr_string_listCreateField) ',a) "

character(*), parameter :: file_name = __FILE__
character(*), parameter :: file_name = &
__FILE__

!-------------------------------------------------------------------------------

Expand Down
3 changes: 2 additions & 1 deletion src/driver/BeTRType.F90
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,8 @@ module BetrType

private

character(len=*), parameter :: filename = __FILE__
character(len=*), parameter :: filename = &
__FILE__

type, public :: betr_type
! namelist control variables
Expand Down
4 changes: 3 additions & 1 deletion src/driver/sbetrDriverMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,9 @@ module sbetrDriverMod
private
save
public :: sbetrBGC_driver
character(len=*), parameter :: mod_filename = __FILE__

character(len=*), parameter :: mod_filename = &
__FILE__

contains

Expand Down
3 changes: 2 additions & 1 deletion src/shr/shr_string_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1723,7 +1723,8 @@ function shr_string_listCreateField( numFields, strBase ) result ( retString )
character(*),parameter :: subName = "(shr_string_listCreateField) "
character(*),parameter :: F00 = "('(shr_string_listCreateField) ',a) "

character(*), parameter :: file_name = __FILE__
character(*), parameter :: file_name = &
__FILE__

!-------------------------------------------------------------------------------

Expand Down
19 changes: 10 additions & 9 deletions src/stub_clm/CNSharedParamsMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,8 @@ module CNSharedParamsMod
use shr_kind_mod , only: r8 => shr_kind_r8
implicit none
save

character(len=*), parameter :: mod_filename = &
__FILE__
! CNParamsShareInst. PGI wants the type decl. public but the instance
! is indeed protected. A generic private statement at the start of the module
! overrides the protected functionality with PGI
Expand Down Expand Up @@ -52,43 +53,43 @@ subroutine CNParamsReadShared(ncid)
!
tString='q10_mr'
!call ncd_io(varname=trim(tString),data=tempr, flag='read', ncid=ncid, readvar=readv)
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(__FILE__, __LINE__))
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(mod_filename, __LINE__))
CNParamsShareInst%Q10=tempr

tString='minpsi_hr'
!call ncd_io(trim(tString),tempr, 'read', ncid, readvar=readv)
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(__FILE__, __LINE__))
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(mod_filename, __LINE__))
CNParamsShareInst%minpsi=tempr

tString='cwd_fcel'
!call ncd_io(trim(tString),tempr, 'read', ncid, readvar=readv)
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(__FILE__, __LINE__))
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(mod_filename, __LINE__))
CNParamsShareInst%cwd_fcel=tempr

tString='cwd_flig'
!call ncd_io(trim(tString),tempr, 'read', ncid, readvar=readv)
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(__FILE__, __LINE__))
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(mod_filename, __LINE__))
CNParamsShareInst%cwd_flig=tempr

tString='froz_q10'
!call ncd_io(trim(tString),tempr, 'read', ncid, readvar=readv)
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(__FILE__, __LINE__))
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(mod_filename, __LINE__))
CNParamsShareInst%froz_q10=tempr

tString='decomp_depth_efolding'
!call ncd_io(trim(tString),tempr, 'read', ncid, readvar=readv)
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(__FILE__, __LINE__))
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(mod_filename, __LINE__))
CNParamsShareInst%decomp_depth_efolding=tempr

tString='mino2lim'
!call ncd_io(trim(tString),tempr, 'read', ncid, readvar=readv)
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(__FILE__, __LINE__))
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(mod_filename, __LINE__))
CNParamsShareInst%mino2lim=tempr
!CNParamsShareInst%mino2lim=0.2_r8

tString='organic_max'
!call ncd_io(trim(tString),tempr, 'read', ncid, readvar=readv)
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(__FILE__, __LINE__))
!if ( .not. readv ) call endrun(msg=trim(errCode)//trim(tString)//errMsg(mod_filename, __LINE__))
CNParamsShareInst%organic_max=tempr

end subroutine CNParamsReadShared
Expand Down
6 changes: 4 additions & 2 deletions src/stub_clm/column_varcon.F90
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,8 @@ function icemec_class_to_col_itype(icemec_class) result(col_itype)
! !LOCAL VARIABLES:

character(len=*), parameter :: subname = 'icemec_class_to_col_itype'
character(len=*), parameter :: mod_filename = __FILE__
character(len=*), parameter :: mod_filename = &
__FILE__
!-----------------------------------------------------------------------
SHR_ASSERT((1 <= icemec_class .and. icemec_class <= maxpatch_glcmec), errMsg(mod_filename, __LINE__))

Expand All @@ -75,7 +76,8 @@ function col_itype_to_icemec_class(col_itype) result(icemec_class)
! !LOCAL VARIABLES:

character(len=*), parameter :: subname = 'col_itype_to_icemec_class'
character(len=*), parameter :: mod_filename = __FILE__
character(len=*), parameter :: mod_filename = 'column_varcon.F90'

!-----------------------------------------------------------------------

icemec_class = col_itype - istice_mec*100
Expand Down
8 changes: 6 additions & 2 deletions src/stub_clm/ncdio_pio.F90
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,10 @@ module ncdio_pio
use clm_varctl , only : single_column, iulog
use spmdMod , only : masterproc
implicit none

character(len=*), parameter :: mod_filename = &
__FILE__

private
save

Expand Down Expand Up @@ -245,7 +249,7 @@ subroutine check_dim(ncid, dimname, value)
write (iulog,*) 'CHECK_DIM error: mismatch of input dimension ',dimlen, &
' with expected value ',value,' for variable ', trim(dimname)

call shr_sys_abort(errMsg(__FILE__,__LINE__))
call shr_sys_abort(errMsg(mod_filename,__LINE__))
end if

end subroutine check_dim
Expand Down Expand Up @@ -1348,7 +1352,7 @@ subroutine ncd_inqfdims(ncid, isgrid2d, ni, nj, ns)

if (ni == 0 .or. nj == 0) then
write(iulog,*) trim(subname),' ERROR: ni,nj = ',ni,nj,' cannot be zero '
call shr_sys_abort(errMsg(__FILE__, __LINE__))
call shr_sys_abort(errMsg(mod_filename, __LINE__))
end if

if (nj == 1) then
Expand Down
3 changes: 2 additions & 1 deletion src/stub_clm/soilorder_varcon.F90
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,8 @@ module soilorder_varcon
real(r8), pointer :: k_s3_biochem(:)
real(r8), pointer :: k_s4_biochem(:)

character(len=*), parameter :: mod_filename = __FILE__
character(len=*), parameter :: mod_filename = &
__FILE__


! !PUBLIC MEMBER FUNCTIONS:
Expand Down
3 changes: 2 additions & 1 deletion src/stub_clm/subgridAveMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,8 @@ module subgridAveMod
private :: build_scale_l2g
private :: create_scale_l2g_lookup

character(len=*), parameter :: mod_filename = __FILE__
character(len=*), parameter :: mod_filename = &
__FILE__

! WJS (10-14-11): TODO:
!
Expand Down

0 comments on commit 27329c0

Please sign in to comment.