Skip to content

Commit

Permalink
Merge pull request #539 from glemieux/glemieux-default-modules-private
Browse files Browse the repository at this point in the history
Conversion of modules from public to private by default
  • Loading branch information
rgknox authored Jun 14, 2019
2 parents 0cf63a9 + 8efc24f commit 6232bb3
Show file tree
Hide file tree
Showing 28 changed files with 1,076 additions and 1,013 deletions.
1 change: 0 additions & 1 deletion biogeochem/EDCanopyStructureMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -119,7 +119,6 @@ subroutine canopy_structure( currentSite , bc_in )
use EDParamsMod, only : ED_val_comp_excln
use EDtypesMod , only : ncwd
use EDTypesMod , only : min_patch_area
use EDTypesMod , only : val_check_ed_vars
use FatesInterfaceMod, only : bc_in_type
!
! !ARGUMENTS
Expand Down
1 change: 0 additions & 1 deletion biogeochem/EDCohortDynamicsMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,6 @@ module EDCohortDynamicsMod

use PRTGenericMod, only : prt_carbon_allom_hyp
use PRTGenericMod, only : prt_cnp_flex_allom_hyp
use PRTGenericMod, only : InitPRTVartype
use PRTGenericMod, only : prt_vartypes
use PRTGenericMod, only : all_carbon_elements
use PRTGenericMod, only : carbon12_element
Expand Down
1 change: 0 additions & 1 deletion biogeochem/EDPhysiologyMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,6 @@ module EDPhysiologyMod
use EDTypesMod , only : num_vegtemp_mem
use EDTypesMod , only : maxpft
use EDTypesMod , only : ed_site_type, ed_patch_type, ed_cohort_type
use EDTypesMod , only : dump_cohort
use EDTypesMod , only : first_leaf_aclass
use EDTypesMod , only : leaves_on
use EDTypesMod , only : leaves_off
Expand Down
10 changes: 1 addition & 9 deletions biogeophys/FatesPlantHydraulicsMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -931,7 +931,6 @@ subroutine updateSizeDepTreeHydStates(currentSite,ccohort)
!
! !USES:
use FatesUtilsMod , only : check_var_real
use EDTypesMod , only : dump_cohort
use EDTypesMod , only : AREA

! !ARGUMENTS:
Expand Down Expand Up @@ -973,11 +972,6 @@ subroutine updateSizeDepTreeHydStates(currentSite,ccohort)
ccohort_hydr%v_aroot_layer_init(j)/ccohort_hydr%v_aroot_layer(j)
ccohort_hydr%th_aroot(j) = constrain_water_contents(th_aroot_uncorr(j), small_theta_num, ft, 4)
ccohort_hydr%errh2o_growturn_aroot(j) = ccohort_hydr%th_aroot(j) - th_aroot_uncorr(j)
!call check_var_real(ccohort_hydr%errh2o_growturn_aroot(j),'ccohort_hydr%errh2o_growturn_aroot(j)',err_code)
!if ((abs(ccohort_hydr%errh2o_growturn_aroot(j)) > 1.0_r8) .or. &
! err_code == 1 .or. err_code == 10) then
! call dump_cohort(cCohort)
!end if
enddo

! Storing mass balance error
Expand Down Expand Up @@ -1428,7 +1422,6 @@ subroutine UpdateH2OVeg(nsites,sites,bc_out)
! ----------------------------------------------------------------------------------

use EDTypesMod, only : AREA
use EDTypesMod , only : dump_cohort

! Arguments
integer, intent(in) :: nsites
Expand Down Expand Up @@ -2264,8 +2257,7 @@ subroutine hydraulics_bc ( nsites, sites,bc_in,bc_out,dtime )
!s
! !USES:
use EDTypesMod , only : AREA
use FatesUtilsMod , only : check_var_real
use EDTypesMod , only : dump_cohort
use FatesUtilsMod , only : check_var_real

! ARGUMENTS:
! -----------------------------------------------------------------------------------
Expand Down
97 changes: 43 additions & 54 deletions fire/SFParamsMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7,68 +7,57 @@ module SFParamsMod
use FatesParametersInterface, only : param_string_length

implicit none
private ! Modules are private by default
save
! private - if we allow this module to be private, it does not allow the protected values below to be
! seen outside of this module.

!
! this is what the user can use for the actual values
!
real(r8),protected :: SF_val_fdi_a
real(r8),protected :: SF_val_fdi_b
real(r8),protected :: SF_val_fdi_alpha
real(r8),protected :: SF_val_miner_total
real(r8),protected :: SF_val_fuel_energy
real(r8),protected :: SF_val_part_dens
real(r8),protected :: SF_val_miner_damp
real(r8),protected :: SF_val_max_durat
real(r8),protected :: SF_val_durat_slope
real(r8),protected :: SF_val_drying_ratio
real(r8),protected :: SF_val_CWD_frac(NCWD)
real(r8),protected :: SF_val_max_decomp(NFSC)
real(r8),protected :: SF_val_SAV(NFSC)
real(r8),protected :: SF_val_FBD(NFSC)
real(r8),protected :: SF_val_min_moisture(NFSC)
real(r8),protected :: SF_val_mid_moisture(NFSC)
real(r8),protected :: SF_val_low_moisture_Coeff(NFSC)
real(r8),protected :: SF_val_low_moisture_Slope(NFSC)
real(r8),protected :: SF_val_mid_moisture_Coeff(NFSC)
real(r8),protected :: SF_val_mid_moisture_Slope(NFSC)

character(len=param_string_length),parameter :: SF_name_fdi_a = "fates_fire_fdi_a"
character(len=param_string_length),parameter :: SF_name_fdi_b = "fates_fire_fdi_b"
character(len=param_string_length),parameter :: SF_name_fdi_alpha = "fates_fire_fdi_alpha"
character(len=param_string_length),parameter :: SF_name_miner_total = "fates_fire_miner_total"
character(len=param_string_length),parameter :: SF_name_fuel_energy = "fates_fire_fuel_energy"
character(len=param_string_length),parameter :: SF_name_part_dens = "fates_fire_part_dens"
character(len=param_string_length),parameter :: SF_name_miner_damp = "fates_fire_miner_damp"
character(len=param_string_length),parameter :: SF_name_max_durat = "fates_fire_max_durat"
character(len=param_string_length),parameter :: SF_name_durat_slope = "fates_fire_durat_slope"
character(len=param_string_length),parameter :: SF_name_drying_ratio = "fates_fire_drying_ratio"
character(len=param_string_length),parameter :: SF_name_CWD_frac = "fates_CWD_frac"
character(len=param_string_length),parameter :: SF_name_max_decomp = "fates_max_decomp"
character(len=param_string_length),parameter :: SF_name_SAV = "fates_fire_SAV"
character(len=param_string_length),parameter :: SF_name_FBD = "fates_fire_FBD"
character(len=param_string_length),parameter :: SF_name_min_moisture = "fates_fire_min_moisture"
character(len=param_string_length),parameter :: SF_name_mid_moisture = "fates_fire_mid_moisture"
character(len=param_string_length),parameter :: SF_name_low_moisture_Coeff = "fates_fire_low_moisture_Coeff"
character(len=param_string_length),parameter :: SF_name_low_moisture_Slope = "fates_fire_low_moisture_Slope"
character(len=param_string_length),parameter :: SF_name_mid_moisture_Coeff = "fates_fire_mid_moisture_Coeff"
character(len=param_string_length),parameter :: SF_name_mid_moisture_Slope = "fates_fire_mid_moisture_Slope"
real(r8),protected, public :: SF_val_fdi_a
real(r8),protected, public :: SF_val_fdi_b
real(r8),protected, public :: SF_val_fdi_alpha
real(r8),protected, public :: SF_val_miner_total
real(r8),protected, public :: SF_val_fuel_energy
real(r8),protected, public :: SF_val_part_dens
real(r8),protected, public :: SF_val_miner_damp
real(r8),protected, public :: SF_val_max_durat
real(r8),protected, public :: SF_val_durat_slope
real(r8),protected, public :: SF_val_drying_ratio
real(r8),protected, public :: SF_val_CWD_frac(NCWD)
real(r8),protected, public :: SF_val_max_decomp(NFSC)
real(r8),protected, public :: SF_val_SAV(NFSC)
real(r8),protected, public :: SF_val_FBD(NFSC)
real(r8),protected, public :: SF_val_min_moisture(NFSC)
real(r8),protected, public :: SF_val_mid_moisture(NFSC)
real(r8),protected, public :: SF_val_low_moisture_Coeff(NFSC)
real(r8),protected, public :: SF_val_low_moisture_Slope(NFSC)
real(r8),protected, public :: SF_val_mid_moisture_Coeff(NFSC)
real(r8),protected, public :: SF_val_mid_moisture_Slope(NFSC)

character(len=param_string_length),parameter, public :: SF_name_fdi_a = "fates_fire_fdi_a"
character(len=param_string_length),parameter, public :: SF_name_fdi_b = "fates_fire_fdi_b"
character(len=param_string_length),parameter, public :: SF_name_fdi_alpha = "fates_fire_fdi_alpha"
character(len=param_string_length),parameter, public :: SF_name_miner_total = "fates_fire_miner_total"
character(len=param_string_length),parameter, public :: SF_name_fuel_energy = "fates_fire_fuel_energy"
character(len=param_string_length),parameter, public :: SF_name_part_dens = "fates_fire_part_dens"
character(len=param_string_length),parameter, public :: SF_name_miner_damp = "fates_fire_miner_damp"
character(len=param_string_length),parameter, public :: SF_name_max_durat = "fates_fire_max_durat"
character(len=param_string_length),parameter, public :: SF_name_durat_slope = "fates_fire_durat_slope"
character(len=param_string_length),parameter, public :: SF_name_drying_ratio = "fates_fire_drying_ratio"
character(len=param_string_length),parameter, public :: SF_name_CWD_frac = "fates_CWD_frac"
character(len=param_string_length),parameter, public :: SF_name_max_decomp = "fates_max_decomp"
character(len=param_string_length),parameter, public :: SF_name_SAV = "fates_fire_SAV"
character(len=param_string_length),parameter, public :: SF_name_FBD = "fates_fire_FBD"
character(len=param_string_length),parameter, public :: SF_name_min_moisture = "fates_fire_min_moisture"
character(len=param_string_length),parameter, public :: SF_name_mid_moisture = "fates_fire_mid_moisture"
character(len=param_string_length),parameter, public :: SF_name_low_moisture_Coeff = "fates_fire_low_moisture_Coeff"
character(len=param_string_length),parameter, public :: SF_name_low_moisture_Slope = "fates_fire_low_moisture_Slope"
character(len=param_string_length),parameter, public :: SF_name_mid_moisture_Coeff = "fates_fire_mid_moisture_Coeff"
character(len=param_string_length),parameter, public :: SF_name_mid_moisture_Slope = "fates_fire_mid_moisture_Slope"

public :: SpitFireRegisterParams
public :: SpitFireReceiveParams

private :: SpitFireParamsInit
private :: SpitFireRegisterScalars
private :: SpitFireReceiveScalars

private :: SpitFireRegisterNCWD
private :: SpitFireReceiveNCWD

private :: SpitFireRegisterNFSC
private :: SpitFireReceiveNFSC


contains
!-----------------------------------------------------------------------
subroutine SpitFireParamsInit()
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,6 @@ module FatesCohortWrapMod

use EDPftvarcon, only : EDPftvarcon_inst

use PRTGenericMod, only : InitPRTVartype
use PRTGenericMod, only : prt_vartypes
use PRTGenericMod, only : leaf_organ
use PRTGenericMod, only : all_carbon_elements
Expand Down Expand Up @@ -74,12 +73,10 @@ module FatesCohortWrapMod
use FatesGlobals , only : fates_log
use shr_log_mod , only : errMsg => shr_log_errMsg



implicit none
private ! Modules are private by default


type ed_cohort_type
type, public :: ed_cohort_type

integer :: pft ! pft number
integer :: parteh_model ! The PARTEH allocation hypothesis used
Expand Down Expand Up @@ -109,10 +106,17 @@ module FatesCohortWrapMod

! Global Instances

type(ed_cohort_type), pointer :: cohort_array(:)
integer :: numcohort
type(ed_cohort_type), pointer, public :: cohort_array(:)
integer, public :: numcohort

character(len=*), parameter, private :: sourcefile = __FILE__

! Make necessary procedures public
public :: CohortInitAlloc
public :: CohortPySet
public :: WrapDailyPRT
public :: WrapQueryVars
public :: WrapQueryDiagnostics

contains

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -22,9 +22,14 @@ module FatesPARTEHWrapMod
use iso_c_binding, only : c_char

implicit none
private

character(len=*), parameter, private :: sourcefile = __FILE__

! Make necessary procedures public

public :: SPMapPyset

contains


Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,10 @@ module EDPftvarcon
use iso_c_binding, only : i4 => c_int
use iso_c_binding, only : c_char

integer,parameter :: SHR_KIND_CS = 80 ! short char
implicit none
private ! Modules are private by default

integer,parameter,public :: SHR_KIND_CS = 80 ! short char

type, public :: EDPftvarcon_inst_type

Expand Down Expand Up @@ -106,24 +109,27 @@ module EDPftvarcon

end type EDPftvarcon_inst_type

type pftptr_var
type, public :: pftptr_var
real(r8), dimension(:), pointer :: rp_1d
real(r8), dimension(:,:), pointer :: rp_2d
character(len=shr_kind_cs) :: var_name
end type pftptr_var

type EDPftvarcon_ptr_type
type, public :: EDPftvarcon_ptr_type
type(pftptr_var), allocatable :: var(:)
end type EDPftvarcon_ptr_type

type(EDPftvarcon_inst_type), public :: EDPftvarcon_inst ! ED ecophysiological constants structure
type(EDPftvarcon_ptr_type), public :: EDPftvarcon_ptr ! Pointer structure for obj-oriented id

integer :: numparm ! Number of different PFT parameters
integer :: num_pft ! Number of PFTs
integer :: num_organs ! Number of organs

integer, public :: numparm ! Number of different PFT parameters
integer, public :: num_pft ! Number of PFTs
integer, public :: num_organs ! Number of organs

! Make necessary procedures public
public :: EDPftvarconPySet
public :: EDPftvarconAlloc

contains


Expand Down
60 changes: 40 additions & 20 deletions functional_unit_testing/parteh/f_wrapper_modules/FatesWrapMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,51 +9,71 @@ module EDTypesMod
use iso_c_binding, only: fates_r8 => c_double
use iso_c_binding, only: fates_int => c_int

integer(fates_int), parameter :: nlevleaf = 40
real(fates_r8), parameter :: dinc_ed = 1.0_fates_r8
integer(fates_int), parameter :: nclmax = 4
implicit none
private

integer(fates_int), parameter, public :: nlevleaf = 40
real(fates_r8), parameter, public :: dinc_ed = 1.0_fates_r8
integer(fates_int), parameter, public :: nclmax = 4

end module EDTypesMod


module shr_log_mod

use iso_c_binding, only : c_char
use iso_c_binding, only : c_int
use iso_c_binding, only : c_char
use iso_c_binding, only : c_int

implicit none
private

! Make necessary producers public
public :: shr_log_errMsg

contains
contains

function shr_log_errMsg(source, line) result(ans)
function shr_log_errMsg(source, line) result(ans)
character(kind=c_char,len=*), intent(in) :: source
integer(c_int), intent(in) :: line
character(kind=c_char,len=128) :: ans

ans = "source: " // trim(source) // " line: "
end function shr_log_errMsg
end function shr_log_errMsg

end module shr_log_mod

module FatesInterfaceMod

use iso_c_binding, only: fates_r8 => c_double
real(fates_r8), parameter :: hlm_freq_day = 1.0_fates_r8/365.0_fates_r8

implicit none
private

real(fates_r8), parameter, public :: hlm_freq_day = 1.0_fates_r8/365.0_fates_r8

end module FatesInterfaceMod


module FatesGlobals

contains

integer function fates_log()
fates_log = 6 ! usually stdout
end function fates_log

subroutine fates_endrun(msg)
implicit none
private

! Make necessary producers public
public :: fates_log
public :: fates_endrun

contains

integer function fates_log()
fates_log = 6 ! usually stdout
end function fates_log

implicit none
character(len=*), intent(in) :: msg ! string to be printed
stop
end subroutine fates_endrun
subroutine fates_endrun(msg)

implicit none
character(len=*), intent(in) :: msg ! string to be printed
stop
end subroutine fates_endrun

end module FatesGlobals
Loading

0 comments on commit 6232bb3

Please sign in to comment.