TreeMig Code
Loading...
Searching...
No Matches
WriteState.f90
Go to the documentation of this file.
1!==============================================================================
32SUBROUTINE writestate(year, latStart, latEnd, lonStart, lonEnd, nspc)
33 use all_par, only: experimentid
37 ! CALL modules for TYPE definitions and +- fixed variables>---------------------------------------------------------------
39
40 IMPLICIT NONE
41 ! Local variables ---------------------------------------------------------------------------------
42 character*6:: yearChar
43
44 ! <Passed variables >--------------------------------------------------------------------------------
45 INTEGER, INTENT(in) :: year ! year of calculation
46 INTEGER, INTENT(in) :: latStart, latEnd, lonStart, lonEnd, nspc ! start and end of simulated area
47
48
49 ! <Here the SUBROUTINE starts>**********************************************************************
50 if (year >0) then
51 ! ---- Check whether this is a year for regular backup
52 if((mod(year, stateoutputdist) == 0) .and. (year /= numyrs-1)) then
53 write (logmessage, "(A,I7)") "Writing backup state for year: ", year
55 ! ---- write out alternatively between 2 backup statefiles, in case of crash during writing. Delete the other one.
56 if(mod(year/stateoutputdist, 2) == 1) then
57 call writestatefile(statebackupout_file_0, year, latstart, latend, lonstart, lonend, nspc)
58 else
59 call writestatefile(statebackupout_file_1, year, latstart, latend, lonstart, lonend, nspc)
60 end if
61 if(mod(year/stateoutputdist, 2) == 1) then
63 else
65 end if
66 end if
67 ! ---- if this is the (nearly) last year, write out an additional backup file, and delete the two others
68 if(year == numyrs-1) then
69 write (logmessage, "(A,I7)") "Writing backup state for year: ", year
71 call writestatefile(statebackupout_file, year, latstart, latend, lonstart, lonend, nspc)
74 end if
75 ! ---- If this is a year for explicitly wished output of state, write the state to the statefile with the name containing the experimentid and the year
76 if (any((year + simustartyear) == stateoutputyears)) then
77 write (logmessage, "(A,I7)") "Writing state optionally for year: ", year
79 write(yearchar,"(I6.2)") year + simustartyear
80 stateout_file%path = relativepathletter//"S/"//experimentid//"/statefile_"//trim(adjustl(yearchar))//".txt"
81 call writestatefile(stateout_file, year, latstart, latend, lonstart, lonend, nspc)
82 end if
83 end if
84end SUBROUTINE writestate
85
86! ==============================================================================
108! ===============================================================
109SUBROUTINE writestatefile(stateFile, year, latStart, latEnd, lonStart, lonEnd, nspc)
111 use loggermodule, only: logwarning
112 ! <Passed variables>--------------------------------------------------------------------------------
113 TYPE(file), INTENT(in) :: stateFile
114 INTEGER, INTENT(in) :: year, & ! year of calculation [=..]
115 latStart, latEnd, lonStart, lonEnd, nspc ! start and end of simulated area ! start and end of simulated area
116 ! <Local variables>---------------------------------------------------------------------------------
117 INTEGER :: err
118 call openfilew(statefile, err)
119 if(err /= 0) then
120 call logwarning("Could not open statefile! Skip writing")
121 return;
122 end if
123 call writestateloops(year, latstart, latend, lonstart, lonend, nspc, statefile%unit)
124 call closefile(statefile)
125end SUBROUTINE writestatefile
126! ==============================================================================
143! ===============================================================
144
146SUBROUTINE writestateloops(year, latstart, latend, lonstart, lonend, nspc, unit)
148 ! CALL modules for TYPE definitions and +- fixed variables>---------------------------------------------------------------
149
150 IMPLICIT NONE
151
152 ! <Passed variables>--------------------------------------------------------------------------------
153 INTEGER, INTENT(in) :: year, & !> year of calculation [=..]
154 latStart, latEnd, lonStart, lonEnd, nspc, unit
155
156 ! <Local variables>---------------------------------------------------------------------------------
157 INTEGER :: height
158 INTEGER :: isp, & !>!> species loop-counter
159 lat, lon, output_year
160 character(len=5) :: asChar_maxhtc
161 ! ---- converts the relative year to the real year of output then written to the statefile
162 output_year = year + simustartyear
163 ! ---- loop over the gridcells
164 looplat: do lat = latstart, latend
165 looplon: do lon = lonstart, lonend
166 if (stockability(lat, lon) .gt. 0) then
167 ! ---- loop over the species
168 do isp = 1, nspc
169 write (aschar_maxhtc, "(I5)") spec(isp)%maxhtc+1
170 ! ---- write out the state of the species in this grid cell
171 write (unit, "(A,3I10,2F18.6,I5,"//aschar_maxhtc//"F18.6)") spec(isp)%nl, output_year, lat, lon, &
172 stategrid(lat, lon)%sp(isp)%seedBank, &
173 stategrid(lat, lon)%sp(isp)%antagonist, &
174 spec(isp)%maxhtc, &
175 (stategrid(lat, lon)%sp(isp)%numin(height), height=0, spec(isp)%maxhtc)
176 end do
177 end if
178 end do looplon
179 end do looplat
180end SUBROUTINE writestateloops
subroutine writestateloops(year, latstart, latend, lonstart, lonend, nspc, unit)
WriteStateLoops.
subroutine writestate(year, latstart, latend, lonstart, lonend, nspc)
WriteState.
subroutine writestatefile(statefile, year, latstart, latend, lonstart, lonend, nspc)
WriteStateFile.
character(len=:), allocatable experimentid
Definition All_par.f90:105
integer stateoutputdist
Definition All_par.f90:31
real, dimension(:, :), allocatable stockability
Definition All_par.f90:53
integer simustartyear
Definition All_par.f90:27
type(specproperties), dimension(maxspc) spec
Definition All_par.f90:345
type(currstateincell), dimension(:, :), allocatable stategrid
Definition All_par.f90:340
integer numyrs
Definition All_par.f90:26
integer, dimension(10) stateoutputyears
Definition All_par.f90:32
character(2) relativepathletter
subroutine closefile(thefile)
closeFile
subroutine openfilew(thefile, err)
openFileW
subroutine deletefile(thefile)
deleteFile
type(file) statebackupout_file_0
type(file) stateout_file
type(file) statebackupout_file_1
type(file) statebackupout_file
LoggerModule.
subroutine logwarning(msg)
LogError
subroutine loginfo(msg)
LogInfo
character(len=1024) logmessage