TreeMig Code
Loading...
Searching...
No Matches
ReportNETCDF.f90
Go to the documentation of this file.
1!==============================================================================
27!===============================================================
28SUBROUTINE reportnetcdf(year, nspc)
29 use, intrinsic :: iso_fortran_env
30 use, intrinsic :: ieee_arithmetic
35
36 use netcdf, only: nf90_put_var
37
38 IMPLICIT NONE
39
40 INTEGER, INTENT(in) :: year, nspc
41 INTEGER :: ReportYear = 0
42 INTEGER :: i, rpti, yr
43 REAL :: fillval
44
45 fillval = ieee_value(fillval, ieee_quiet_nan) ! some kind of NA values
46 yr = year + simustartyear ! actual year
47 rpti = 1
48 do i=1,10 ! determine current report interval
49 if (yr >= reportintervals(i,2) .and. yr <= reportintervals(i,3) ) then
50 rpti=reportintervals(i,1)
51 exit
52 end if
53 end do
54 if (mod(year, rpti) == 0 .and. writeoutput%netcdf) then ! only if output for this year and netcdf output in general is whished
55 reportyear = reportyear+1 ! increase report year every call.
56 if(writeoutput%light) then
57 call m_check(nf90_put_var(nc_file_id, light_nc%varId, light_nc%values4D, &
58 start = (/ reportyear, 1, 1 /), count = (/ 1, maxhc+1, maxlc, maxlon, maxlat /))&
59 ,__line__, __file__)
60 light_nc%values4D = fillval
61 end if
62 if(writeoutput%biodiv) then
63 call m_check(nf90_put_var(nc_file_id, biodiv_nc%varId, biodiv_nc%values2D, &
64 start = (/ reportyear, 1, 1 /), count = (/ 1, maxlon, maxlat /))&
65 ,__line__, __file__)
66 biodiv_nc%values2D = fillval
67 end if
68 ! as example described:
69 ! The values of biomass have been put to Biomass_NC%values3D in Report.
70 ! count of them are now put to the variable Biomass_NC%varId in the file NC_FILE_ID at the position ReportYear
71 ! it is checked whether this assignment is ok (m_check)
72 ! then the variable is set to NA
73 if(writeoutput%biomass) then
74 call m_check(nf90_put_var(nc_file_id, biomass_nc%varId, biomass_nc%values3D, &
75 start = (/ reportyear, 1, 1, 1 /), count = (/ 1, nspc+1, maxlon, maxlat /))&
76 ,__line__, __file__)
77 biomass_nc%values3D = fillval
78 end if
79 if(writeoutput%number) then
80 call m_check(nf90_put_var(nc_file_id, number_nc%varId, number_nc%values3D, &
81 start = (/ reportyear, 1, 1, 1 /), count = (/ 1, nspc+1, maxlon, maxlat /))&
82 ,__line__, __file__)
83 number_nc%values3D = fillval
84 end if
85 if(writeoutput%seeds) then
86 call m_check(nf90_put_var(nc_file_id, seed_nc%varId, seed_nc%values3D, &
87 start = (/ reportyear, 1, 1, 1 /), count = (/ 1, nspc+1, maxlon, maxlat /))&
88 ,__line__, __file__)
89 seed_nc%values3D = fillval
90 end if
91 if(writeoutput%ingrowth) then
92 call m_check(nf90_put_var(nc_file_id, ingrowth_nc%varId, ingrowth_nc%values3D, &
93 start = (/ reportyear, 1, 1, 1 /), count = (/ 1, nspc+1, maxlon, maxlat /))&
94 ,__line__, __file__)
95 ingrowth_nc%values3D = fillval
96 end if
97 if(writeoutput%NPP) then
98 call m_check(nf90_put_var(nc_file_id, npp_nc%varId, npp_nc%values3D, &
99 start = (/ reportyear, 1, 1, 1 /), count = (/ 1, nspc+1, maxlon, maxlat /))&
100 ,__line__, __file__)
101 npp_nc%values3D = fillval
102 end if
103 if(writeoutput%basalArea) then
104 call m_check(nf90_put_var(nc_file_id, basalarea_nc%varId, basalarea_nc%values3D, &
105 start = (/ reportyear, 1, 1, 1 /), count = (/ 1, nspc+1, maxlon, maxlat /))&
106 ,__line__, __file__)
107 basalarea_nc%values3D = fillval
108 end if
109 if(writeoutput%antagonists) then
110 call m_check(nf90_put_var(nc_file_id, antagonist_nc%varId, antagonist_nc%values3D, &
111 start = (/ reportyear, 1, 1, 1 /), count = (/ 1, nspc+1, maxlon, maxlat /))&
112 ,__line__, __file__)
113 antagonist_nc%values3D = fillval
114 end if
115 if(writeoutput%pollen) then
116 call m_check(nf90_put_var(nc_file_id, pollen_nc%varId, pollen_nc%values3D, &
117 start = (/ reportyear, 1, 1, 1 /), count = (/ 1, nspc+1, maxlon, maxlat /))&
118 ,__line__, __file__)
119 pollen_nc%values3D = fillval
120 end if
121 if(writeoutput%lai) then
122 call m_check(nf90_put_var(nc_file_id, lai_nc%varId, lai_nc%values3D, &
123 start = (/ reportyear, 1, 1, 1 /), count = (/ 1, nspc+1, maxlon, maxlat /))&
124 ,__line__, __file__)
125 lai_nc%values3D = fillval
126 end if
127
128 if(writeoutput%hstruct) then
129 do i=1,size(heightstruct_nc)
130 call m_check(nf90_put_var(nc_file_id, heightstruct_nc(i)%varId, heightstruct_nc(i)%values3D, &
131 start = (/ reportyear, 1, 1, 1 /), count = (/ 1, nspc+1, maxlon, maxlat /))&
132 ,__line__, __file__)
133 heightstruct_nc(i)%values3D = fillval
134 end do
135 end if
136 end if
137end SUBROUTINE
subroutine m_check(status, linenumber, filename)
m_check
subroutine reportnetcdf(year, nspc)
ReportNETCDF.
integer simustartyear
Definition All_par.f90:27
integer, dimension(10, 3) reportintervals
Definition All_par.f90:29
integer, parameter maxhc
Definition All_par.f90:99
type(wroutp) writeoutput
Definition All_par.f90:143
integer, parameter maxlc
Definition All_par.f90:100
integer maxlon
Definition All_par.f90:46
integer, dimension(col2), parameter start
Definition All_par.f90:27
integer maxlat
Definition All_par.f90:45
type(ncvar) basalarea_nc
type(ncvar) ingrowth_nc
type(ncvar) antagonist_nc
type(ncvar) number_nc
type(ncvar), dimension(16) heightstruct_nc
type(ncvar) light_nc
type(ncvar) lai_nc
type(ncvar) biodiv_nc
type(ncvar) biomass_nc
type(ncvar) npp_nc
type(ncvar) pollen_nc
type(ncvar) seed_nc