Skip to content

Commit

Permalink
1. Intermediate commit, to avoid losing stuff. The goal is to make th…
Browse files Browse the repository at this point in the history
…e output in ED more

    standard:
    
    a. Name conventions:
       i.   FMEAN: sub-daily means (the old AVG or MEAN variables).  AVG variables that
                   were not sub-daily means retained the old name.
       ii.  DMEAN: daily means
       iii. MMEAN: monthly mean
       iv.  MMSQU: monthly mean sum of squares 
       v.   QMEAN: mean diel
       vi.  QMSQU: mean sum of squares by hour of day
      
      2. The means are now for the native level (cohort, patch or site), plus polygon-level
         They all get a suffix: (_CO for cohorts, _PA for patches, _SI for sites, _PY for
         polygons).  Metadata are also available
      
      3. Biomass variables at polygon are split by DBH and PFT.  The total and total by 
         PFT or by DBH can be found by aggregating these variables accordingly.  They can be also
         determined using the cohort-, patch-, or site-level variables.
      
      4. BRAMS, and some R scripts aren't tested yet, but they will be soon. 

2.  Some classification variables that did not make sense to exist at the  polygon-level 
    (e.g. soil texture, soil colour) were deleted and only the site-level was kept.  

3.  Minor bug fixes in fusion, particularly with mortality.  Fast means are now part of
    the patch/cohort dynamics because they are written to the output after the 
    dynamics.
  • Loading branch information
Marcos Longo committed Nov 14, 2012
1 parent 5d9d23f commit 37188de
Show file tree
Hide file tree
Showing 59 changed files with 43,226 additions and 24,263 deletions.
18 changes: 8 additions & 10 deletions BRAMS/src/ed2/edcp_driver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -63,16 +63,6 @@ subroutine ed_coup_driver()
wtime_start = walltime(0.)
wtime1 = walltime(wtime_start)

!---------------------------------------------------------------------------------------!
! Check whether the user has indicated a need for any of the fast flux diagnostic !
! variables, these are used in conditions of ifoutput,idoutput and imoutput conditions. !
! If they are not >0, then set the logical, fast_diagnostics to false. !
!---------------------------------------------------------------------------------------!
fast_diagnostics = checkbudget .or. ifoutput /= 0 .or. idoutput /= 0 .or. &
iqoutput /= 0 .or. imoutput /= 0 .or. ioutput /= 0 .or. &
iyoutput /= 0
!---------------------------------------------------------------------------------------!




Expand All @@ -84,6 +74,14 @@ subroutine ed_coup_driver()
!---------------------------------------------------------------------------------------!


!---------------------------------------------------------------------------------------!
! If we are running EDBRAMS then we must make sure that fast diagnostic averages !
! are found when ioutput is requested. !
!---------------------------------------------------------------------------------------!
fast_diagnostics = fast_diagnostics .or. ioutput /= 0
!---------------------------------------------------------------------------------------!




!---------------------------------------------------------------------------------------!
Expand Down
23 changes: 22 additions & 1 deletion BRAMS/src/ed2/edcp_load_namelist.f90
Original file line number Diff line number Diff line change
Expand Up @@ -136,7 +136,14 @@ subroutine read_ednl(iunit,filename)
, attach_metadata & ! intent(out)
, iallom & ! intent(out)
, igrass & ! intent(out)
, min_site_area ! ! intent(out)
, min_site_area & ! intent(out)
, fast_diagnostics & ! intent(out)
, writing_dail & ! intent(out)
, writing_mont & ! intent(out)
, writing_dcyc & ! intent(out)
, writing_year & ! intent(out)
, writing_long & ! intent(out)
, writing_eorq ! ! intent(out)
use canopy_air_coms , only : icanturb & ! intent(out)
, isfclyrm & ! intent(out)
, ied_grndvap ! ! intent(out)
Expand Down Expand Up @@ -549,6 +556,20 @@ subroutine read_ednl(iunit,filename)
call copy_path_from_grid_1(ngrids,'sfilin' ,sfilin )
!---------------------------------------------------------------------------------------!



!----- Define some useful variables that control the output. ---------------------------!
writing_dail = idoutput > 0
writing_mont = imoutput > 0
writing_dcyc = iqoutput > 0
writing_year = iyoutput > 0
writing_long = writing_dail .or. writing_mont .or. writing_dcyc
writing_eorq = writing_mont .or. writing_dcyc
fast_diagnostics = ioutput /= 0 .or. ifoutput /= 0 .or. idoutput /= 0 .or. &
imoutput /= 0 .or. iqoutput /= 0 .or. itoutput /= 0
!---------------------------------------------------------------------------------------!


return
end subroutine read_ednl
!==========================================================================================!
Expand Down
360 changes: 239 additions & 121 deletions BRAMS/src/ed2/edcp_met.f90

Large diffs are not rendered by default.

38 changes: 19 additions & 19 deletions BRAMS/src/ed2/edcp_model.f90
Original file line number Diff line number Diff line change
Expand Up @@ -143,6 +143,12 @@ subroutine ed_coup_model(ifm)
, iqoutput & ! intent(in)
, itoutput & ! intent(in)
, iyoutput & ! intent(in)
, writing_dail & ! intent(in)
, writing_mont & ! intent(in)
, writing_dcyc & ! intent(in)
, writing_year & ! intent(in)
, writing_eorq & ! intent(in)
, writing_long & ! intent(in)
, frqsum & ! intent(inout)
, unitfast & ! intent(in)
, unitstate & ! intent(in)
Expand Down Expand Up @@ -194,10 +200,6 @@ subroutine ed_coup_model(ifm)
integer , external :: num_days
!----- Locally saved variables. --------------------------------------------------------!
logical , save :: first_time = .true.
logical , save :: writing_dail
logical , save :: writing_mont
logical , save :: writing_dcyc
logical , save :: writing_year
logical, dimension(maxgrds), save :: calledgrid
!---------------------------------------------------------------------------------------!

Expand All @@ -207,10 +209,6 @@ subroutine ed_coup_model(ifm)
! in a coupled model. The test can be done only once. !
!---------------------------------------------------------------------------------------!
if (first_time) then
writing_dail = idoutput > 0
writing_mont = imoutput > 0
writing_dcyc = iqoutput > 0
writing_year = iyoutput > 0
filltables = .false.
record_err = .false.
print_detailed = .false.
Expand All @@ -234,7 +232,17 @@ subroutine ed_coup_model(ifm)

!----- Radiation scheme. ---------------------------------------------------------------!
call radiate_driver(edgrid_g(ifm))



!---------------------------------------------------------------------------------------!
! At this point, all meteorologic driver data for the land surface model has been !
! updated for the current timestep. Perform the time space average for the output !
! diagnostic. !
!---------------------------------------------------------------------------------------!
call integrate_ed_fmean_met_vars(edgrid_g(ifm))
!---------------------------------------------------------------------------------------!


!----- Solve the enthalpy, water, and carbon budgets. ----------------------------------!
select case (integration_scheme)
case (0)
Expand All @@ -247,13 +255,6 @@ subroutine ed_coup_model(ifm)
call hybrid_timestep(edgrid_g(ifm))
end select

!---------------------------------------------------------------------------------------!
! Update the daily averages if daily or monthly analysis are needed. !
!---------------------------------------------------------------------------------------!
if (writing_dail .or. writing_mont .or. writing_dcyc) then
call integrate_ed_daily_output_state(edgrid_g(ifm))
end if


!---------------------------------------------------------------------------------------!
! The remainder of this subroutine is called only once, and it is done after all !
Expand Down Expand Up @@ -331,8 +332,7 @@ subroutine ed_coup_model(ifm)
! Call the model output driver. !
!------------------------------------------------------------------------------------!
call ed_output(analysis_time,new_day,dail_analy_time,mont_analy_time,dcyc_analy_time &
,annual_time,writing_dail,writing_mont,writing_dcyc,history_time &
,dcycle_time,the_end)
,annual_time,history_time,dcycle_time,the_end)
!------------------------------------------------------------------------------------!


Expand All @@ -357,7 +357,7 @@ subroutine ed_coup_model(ifm)
!------------------------------------------------------------------------------------!
if (reset_time) then
do jfm=1,ngrids
call reset_averaged_vars(edgrid_g(jfm))
call zero_ed_fmean_vars(edgrid_g(jfm))
end do
end if

Expand Down
46 changes: 44 additions & 2 deletions BRAMS/src/ed2/edcp_mpiutils.f90
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,14 @@ subroutine masterput_ednl(mainnum)
, idateh & ! intent(in)
, iallom & ! intent(in)
, igrass & ! intent(in)
, min_site_area ! ! intent(in)
, min_site_area & ! intent(in)
, fast_diagnostics & ! intent(in)
, writing_dail & ! intent(in)
, writing_mont & ! intent(in)
, writing_dcyc & ! intent(in)
, writing_year & ! intent(in)
, writing_long & ! intent(in)
, writing_eorq ! ! intent(in)
use grid_coms , only : nzg & ! intent(in)
, nzs & ! intent(in)
, ngrids & ! intent(in)
Expand Down Expand Up @@ -405,6 +412,21 @@ subroutine masterput_ednl(mainnum)
call MPI_Bcast(idetailed,1,MPI_INTEGER,mainnum,MPI_COMM_WORLD,ierr)
call MPI_Bcast(patch_keep,1,MPI_INTEGER,mainnum,MPI_COMM_WORLD,ierr)


!---------------------------------------------------------------------------------------!
! These variables are useful to check for which output types to allocate. !
!---------------------------------------------------------------------------------------!
call MPI_Bcast(writing_dail ,1,MPI_LOGICAL,mainnum,MPI_COMM_WORLD,ierr)
call MPI_Bcast(writing_mont ,1,MPI_LOGICAL,mainnum,MPI_COMM_WORLD,ierr)
call MPI_Bcast(writing_dcyc ,1,MPI_LOGICAL,mainnum,MPI_COMM_WORLD,ierr)
call MPI_Bcast(writing_year ,1,MPI_LOGICAL,mainnum,MPI_COMM_WORLD,ierr)
call MPI_Bcast(writing_long ,1,MPI_LOGICAL,mainnum,MPI_COMM_WORLD,ierr)
call MPI_Bcast(writing_eorq ,1,MPI_LOGICAL,mainnum,MPI_COMM_WORLD,ierr)
call MPI_Bcast(fast_diagnostics,1,MPI_LOGICAL,mainnum,MPI_COMM_WORLD,ierr)
!---------------------------------------------------------------------------------------!



return
end subroutine masterput_ednl
!==========================================================================================!
Expand Down Expand Up @@ -479,7 +501,14 @@ subroutine nodeget_ednl(master_num)
, idateh & ! intent(out)
, iallom & ! intent(out)
, igrass & ! intent(out)
, min_site_area ! ! intent(out)
, min_site_area & ! intent(out)
, fast_diagnostics & ! intent(out)
, writing_dail & ! intent(out)
, writing_mont & ! intent(out)
, writing_dcyc & ! intent(out)
, writing_year & ! intent(out)
, writing_long & ! intent(out)
, writing_eorq ! ! intent(out)
use grid_coms , only : nzg & ! intent(out)
, nzs & ! intent(out)
, ngrids & ! intent(out)
Expand Down Expand Up @@ -821,6 +850,19 @@ subroutine nodeget_ednl(master_num)
call MPI_Bcast(idetailed,1,MPI_INTEGER,master_num,MPI_COMM_WORLD,ierr)
call MPI_Bcast(patch_keep,1,MPI_INTEGER,master_num,MPI_COMM_WORLD,ierr)


!---------------------------------------------------------------------------------------!
! These variables are useful to check for which output types to allocate. !
!---------------------------------------------------------------------------------------!
call MPI_Bcast(writing_dail ,1,MPI_LOGICAL,master_num,MPI_COMM_WORLD,ierr)
call MPI_Bcast(writing_mont ,1,MPI_LOGICAL,master_num,MPI_COMM_WORLD,ierr)
call MPI_Bcast(writing_dcyc ,1,MPI_LOGICAL,master_num,MPI_COMM_WORLD,ierr)
call MPI_Bcast(writing_year ,1,MPI_LOGICAL,master_num,MPI_COMM_WORLD,ierr)
call MPI_Bcast(writing_long ,1,MPI_LOGICAL,master_num,MPI_COMM_WORLD,ierr)
call MPI_Bcast(writing_eorq ,1,MPI_LOGICAL,master_num,MPI_COMM_WORLD,ierr)
call MPI_Bcast(fast_diagnostics,1,MPI_LOGICAL,master_num,MPI_COMM_WORLD,ierr)
!---------------------------------------------------------------------------------------!

return
end subroutine nodeget_ednl
!==========================================================================================!
Expand Down
17 changes: 17 additions & 0 deletions BRAMS/src/lib/rconstants.f90
Original file line number Diff line number Diff line change
Expand Up @@ -324,6 +324,23 @@ Module rconstants



!---------------------------------------------------------------------------------------!
! Carbon-related unit conversions. !
!---------------------------------------------------------------------------------------!
real, parameter :: mol_2_umol = 1.e6 ! mol => µmol
real, parameter :: umol_2_mol = 1.e-6 ! µmol => mol
real, parameter :: umol_2_kgC = 1.20107e-8 ! µmol(CO2) => kg(C)
real, parameter :: Watts_2_Ein = 4.6e-6 ! W/m2 => mol/m²/s
real, parameter :: Ein_2_Watts = 1./Watts_2_Ein ! mol/m²/s => W/m2
real, parameter :: kgC_2_umol = 1. / umol_2_kgC ! kg(C) => µmol(CO2)
real, parameter :: kgom2_2_tonoha = 10. ! kg(C)/m² => ton(C)/ha
real, parameter :: tonoha_2_kgom2 = 0.1 ! ton(C)/ha => kg(C)/m²
real, parameter :: umols_2_kgCyr = umol_2_kgC * yr_sec ! µmol(CO2)/s => kg(C)/yr
real, parameter :: kgCday_2_umols = kgC_2_umol / day_sec ! kg(C)/day => µmol(CO2)/s
!---------------------------------------------------------------------------------------!



!---------------------------------------------------------------------------------------!
! Double precision version of all constants used in Runge-Kutta. !
!---------------------------------------------------------------------------------------!
Expand Down
51 changes: 25 additions & 26 deletions ED/Template/Template/plot_eval_ed.r
Original file line number Diff line number Diff line change
Expand Up @@ -432,32 +432,31 @@ for (place in myplaces){
myinst = hdf5load(file=myfile,load=FALSE,verbosity=0,tidy=TRUE)
}#end if
#------------------------------------------------------------------------------#
model$atm.tmp [tt] = myinst$AVG.ATM.TMP - t00
model$atm.shv [tt] = myinst$AVG.ATM.SHV * 1000.
model$atm.prss [tt] = myinst$AVG.ATM.PRSS * 0.01
model$rain [tt] = myinst$AVG.PCPG * hr.sec
model$atm.co2 [tt] = myinst$AVG.ATM.CO2
model$atm.vels [tt] = myinst$AVG.VELS
model$rshort [tt] = myinst$AVG.RSHORT
model$rlong [tt] = myinst$AVG.RLONG
model$par [tt] = ( ( myinst$AVG.PAR.BEAM + myinst$AVG.PAR.DIFF )
* Watts.2.Ein * 1.e6)
model$hflxca [tt] = - myinst$AVG.SENSIBLE.AC
model$wflxca [tt] = - myinst$AVG.VAPOR.AC * day.sec
model$cflxca [tt] = - myinst$AVG.CARBON.AC
model$cflxst [tt] = + myinst$AVG.CARBON.ST
model$gpp [tt] = myinst$AVG.GPP * umols.2.kgCyr
model$reco [tt] = ( ( myinst$AVG.PLANT.RESP + myinst$AVG.HTROPH.RESP )
* umols.2.kgCyr )
model$nep [tt] = model$gpp[tt] - model$reco[tt]
model$nee [tt] = - model$nep[tt] * kgCyr.2.umols
model$ustar [tt] = myinst$AVG.USTAR
model$rlongup [tt] = myinst$AVG.RLONGUP
model$albedo [tt] = myinst$AVG.ALBEDO
model$rnet [tt] = ( (1. - myinst$AVG.ALBEDO) * myinst$AVG.RSHORT
+ myinst$AVG.RLONG - myinst$AVG.RLONGUP )
model$parup [tt] = myinst$AVG.PARUP * Watts.2.Ein * 1.e6
model$rshortup [tt] = myinst$AVG.RSHORTUP
model$atm.tmp [tt] = myinst$FMEAN.ATM.TEMP.PY - t00
model$atm.shv [tt] = myinst$FMEAN.ATM.SHV.PY * 1000.
model$atm.prss [tt] = myinst$FMEAN.ATM.PRSS.PY * 0.01
model$rain [tt] = myinst$FMEAN.PCPG.PY * hr.sec
model$atm.co2 [tt] = myinst$FMEAN.ATM.CO2.PY
model$atm.vels [tt] = myinst$FMEAN.ATM.VELS.PY
model$rshort [tt] = myinst$FMEAN.ATM.RSHORT.PY
model$rlong [tt] = myinst$FMEAN.ATM.RLONG.PY
model$par [tt] = myinst$FMEAN.ATM.PAR.PY * Watts.2.Ein * 1.e6
model$hflxca [tt] = - myinst$FMEAN.SENSIBLE.AC.PY
model$wflxca [tt] = - myinst$FMEAN.VAPOR.AC.PY * day.sec
model$cflxca [tt] = - myinst$FMEAN.CARBON.AC.PY
model$cflxst [tt] = + myinst$FMEAN.CARBON.ST.PY
model$gpp [tt] = myinst$FMEAN.GPP.PY
model$reco [tt] = ( myinst$FMEAN.PLRESP.PY
+ myinst$FMEAN.RH.PY )
model$nep [tt] = myinst$FMEAN.NEP.PY
model$nee [tt] = ( myinst$FMEAN.CARBON.ST.PY
- myinst$FMEAN.CARBON.AC.PY )
model$ustar [tt] = myinst$FMEAN.USTAR.PY
model$rlongup [tt] = myinst$FMEAN.RLONGUP.PY
model$albedo [tt] = myinst$FMEAN.ALBEDO.PY
model$rnet [tt] = myinst$FMEAN.RNET.PY
model$parup [tt] = myinst$FMEAN.PARUP.PY * Watts.2.Ein * 1.e6
model$rshortup [tt] = myinst$FMEAN.RSHORTUP.PY

if (tt == ntimes){
eddy.complete = TRUE
Expand Down

0 comments on commit 37188de

Please sign in to comment.