TreeMig Code
Loading...
Searching...
No Matches
FileListModule.f90
Go to the documentation of this file.
1 ! uses preprocessor
2!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
3!==============================================================================
4! Module FileListModule
5! *****************************************
6! contains
7! File declarations
8! subroutine ReadControlParsAndInitFiles
9!==============================================================================
12!==============================================================================
13! Type Declarations
14! *****************
15! for different text and netcdf files. The types are defined in FileHandlingModule
16!
17! USE FileHandlingModule
18!==============================================================================
19 character(len=:), allocatable :: resultpath, resultpath_h, statepath; ! defined in read control pars
20 TYPE(file) :: log_file
41 TYPE(file) :: laioutfile
54
56
57 TYPE ncvar
58 character(len=:), allocatable :: name
59 character(len=:), allocatable :: attr_unit
60 INTEGER :: varid = -1
61 REAL , allocatable :: values2d(:,:)
62 REAL , allocatable :: values3d(:,:,:)
63 REAL , allocatable :: values4d(:,:,:,:)
64 end TYPE
65 INTEGER :: nc_file_id
66 character(len=:), allocatable :: nc_file_name
70 TYPE(ncvar) :: seed_nc
72 TYPE(ncvar) :: npp_nc
76 TYPE(ncvar) :: lai_nc
77 TYPE(ncvar) :: light_nc
79contains
80
81!==============================================================================
129!==============================================================================
131 use loggermodule
134 IMPLICIT NONE
135 character(len=128) :: controlFileName
136 character(len=128) :: workingDir
137 character(len=:), allocatable :: FileOutID, FileOutID2
138 INTEGER :: i
139 LOGICAL :: exists
140 character(len=2) :: structID
141!---- prepares the logfile and also the logging on the console
142 log_file = file(10,"logfile.txt")
143 call initlogger(log_file);
144 call loginfo("Starting TreeMig v2.0")
145 call loginfo("Initializing files...")
146!---- prepares reading of the control file
147!---- gets from the command line (console) the control filename (1st argument) and the working directory (2nd argument)
148 call get_command_argument(1, controlfilename) ! get the name of the control file from command line
149 call get_command_argument(2, workingdir)
150 if (trim(workingdir) /= '') then ! if a working directory is indicated set it
151 call chdir(workingdir)
152 end if
153
154 if (trim(controlfilename) == '') then ! if no name for control file is given request one
155 do
156 write(*,*) 'Please enter control-file name:'
157 read(*,*) controlfilename
158 INQUIRE(file=relativepathletter//"C"//pathletter//trim(controlfilename), exist=exists)
159 if(exists) then
160 exit
161 else
162 write(*,*) 'Control-file not found:'//relativepathletter//"C"//pathletter//trim(controlfilename)
163 end if
164 end do
165 end if
166
167!---- read control pars file, parts of the information is needed for defining the other files!
168 controlpars_file = file(11,relativepathletter//"C"//pathletter//trim(controlfilename))
169 controlparsout_file = file(12,null()) ! path defined in ReadControlPars()
170 call readcontrolpars() !
171
172!---- define (unit, path, name) other input files
173 statein_file = file(71, relativepathletter//"InitialValues.txt")
174 dispersalkernel_file = file(100,relativepathletter//"dispKern.txt")
175 dispersalkernelnew_file = file(110,relativepathletter//"newdispkernels.txt")
181
182!---- define (unit, path, name) output files
183 fileoutid = experimentid//"_"
184 stateout_file = file(72,statepath//"statefile_0000.txt")
185 statebackupout_file = file(73,statepath//"statefile_backup.txt")
186 statebackupout_file_0 = file(74,statepath//"statefile_backup_0.txt")
187 statebackupout_file_1 = file(75,statepath//"statefile_backup_1.txt")
188
189 immigrationout_file = file(200, resultpath//fileoutid//"immigration"//".pars")
190 speciesout_file = file(201, resultpath//fileoutid//"species"//".pars")
191
192 biompertreehcloutfile = file(220, resultpath_h//fileoutid2//"bioPerTreeHCL"//".txt")
193 laipertreehcloutfile = file(221, resultpath_h//fileoutid2//"laiPerTreeHCL"//".txt")
194 dbhpertreehcloutfile = file(222, resultpath_h//fileoutid2//"dbhPerTreeHCL"//".txt")
195 seedprodfractpertreehcloutfile = file(223, resultpath_h//fileoutid2//"seedProdPerTreeHCL"//".txt")
196 heightperhcloutfile = file(224, resultpath_h//fileoutid2//"heights"//".txt")
197 lightdistrperhcloutfile = file(225, resultpath_h//fileoutid2//"lightDistr"//".txt")
198 lightandleafareaperlightclass = file(226, resultpath //"lightLAI_LCL"//".txt")
199
200 biomassoutfile = file(300, resultpath//'Biomass'//'.txt')
201 numberoutfile = file(301, resultpath//'Number'//'.txt')
202 seedoutfile = file(302, resultpath//'Seeds'//'.txt')
203 antaoutfile = file(303, resultpath//'Antagonists'//'.txt')
204 pollenoutfile = file(304, resultpath//'Pollen'//'.txt') !pollen
205 nppoutfile = file(305, resultpath//'NPP'//'.txt') !NPP
206 biodivoutfile = file(306, resultpath//'Biodiversity'//'.txt') !biodiv
207 laioutfile = file(307, resultpath//'LAI'//'.txt') !LAI
208 basareaoutfile = file(308, resultpath//'BA'//'.txt') !basal area
209 ingrowthoutfile = file(309, resultpath//'InGr'//'.txt') !ingrowth
210
211 do i=0,15
212 write(structid,"(I2.2)") i
213 heightstructoutfiles(i+1) = file(400+i, resultpath_h//'HeightStruct_'//structid//'.txt')
214 end do
215
216!---- Define (unit, path, name) netcdf output file and netcdf variables
217
218 nc_file_name = resultpath //fileoutid//'OUT'//'.nc'
219
220 biodiv_nc = ncvar("Biodiversity" , "1")
221 biomass_nc = ncvar("Biomass" , "t/ha")
222 number_nc = ncvar("Number" , "1")
223 seed_nc = ncvar("seedBank" , "1")
224 ingrowth_nc = ncvar("Ingrowth" , "1")
225 npp_nc = ncvar("NPP" , "t/ha") ! net primary productivity
226 basalarea_nc = ncvar("BasalArea" , "m^2/h")
227 antagonist_nc = ncvar("Antagonist" , "1")
228 pollen_nc = ncvar("Pollen" , "percent") ! pollen percent
229 lai_nc = ncvar("LAI" , "m^2/m^2") !"leaf_area_index",
230 light_nc = ncvar("LightDistr" , "1") !"light distribution",
231 do i=0,15
232 write(structid,"(I2.2)") i
233 heightstruct_nc(i+1) = ncvar("HeightStruct_"//structid, "t/ha")
234 end do
235 end SUBROUTINE readcontrolparsandinitfiles
236 !==============================================================================
237
238end module filelistmodule
239!==============================================================================
240
241
subroutine readcontrolpars()
ReadControlPars
character(len=:), allocatable experimentid
Definition All_par.f90:105
character(len=:), allocatable landcoverfilterfilename
Definition All_par.f90:104
character(len=:), allocatable bioclimfilename
Definition All_par.f90:103
character(len=:), allocatable specfilename
Definition All_par.f90:101
character(len=:), allocatable stockareafilename
Definition All_par.f90:104
character(len=:), allocatable immifilename
Definition All_par.f90:102
character(2) relativepathletter
subroutine closefile(thefile)
closeFile
subroutine openfiler(thefile, err)
openFileR
type(ncvar) basalarea_nc
type(file) nppoutfile
type(file) biodivoutfile
type(ncvar) ingrowth_nc
type(file) statebackupout_file_0
type(ncvar) antagonist_nc
type(file) log_file
type(file) stockarea_file
type(ncvar) number_nc
type(ncvar), dimension(16) heightstruct_nc
type(ncvar) light_nc
type(file) numberoutfile
subroutine readcontrolparsandinitfiles()
ReadControlParsAndInitFiles
type(file) statein_file
type(file) stateout_file
type(file) dispersalkernelnew_file
type(file) landcoverfilter_file
type(file) lightdistrperhcloutfile
type(ncvar) lai_nc
type(file) biomassoutfile
type(file) immigrationout_file
type(file) pollenoutfile
character(len=:), allocatable statepath
type(file) bioclimate_file
type(file) heightperhcloutfile
type(file) ingrowthoutfile
type(file) dispersalkernel_file
type(file) seedprodfractpertreehcloutfile
type(file) seedoutfile
character(len=:), allocatable resultpath
type(file) controlpars_file
type(ncvar) biodiv_nc
type(ncvar) biomass_nc
character(len=:), allocatable nc_file_name
type(file), dimension(16) heightstructoutfiles
type(file) statebackupout_file_1
type(file) immigration_file
type(file) antaoutfile
type(file) lightandleafareaperlightclass
type(file) laioutfile
character(len=:), allocatable resultpath_h
type(file) biompertreehcloutfile
type(ncvar) npp_nc
type(file) statebackupout_file
type(file) controlparsout_file
type(file) laipertreehcloutfile
type(file) speciesout_file
type(ncvar) pollen_nc
type(file) species_file
type(ncvar) seed_nc
type(file) basareaoutfile
type(file) dbhpertreehcloutfile
LoggerModule.
subroutine loginfo(msg)
LogInfo
subroutine initlogger(log_file)
InitLogger