FV3 Bundle
stock_constants.F90
Go to the documentation of this file.
1 !***********************************************************************
2 !* GNU Lesser General Public License
3 !*
4 !* This file is part of the GFDL Flexible Modeling System (FMS).
5 !*
6 !* FMS is free software: you can redistribute it and/or modify it under
7 !* the terms of the GNU Lesser General Public License as published by
8 !* the Free Software Foundation, either version 3 of the License, or (at
9 !* your option) any later version.
10 !*
11 !* FMS is distributed in the hope that it will be useful, but WITHOUT
12 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
13 !* FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
14 !* for more details.
15 !*
16 !* You should have received a copy of the GNU Lesser General Public
17 !* License along with FMS. If not, see <http://www.gnu.org/licenses/>.
18 !***********************************************************************
19 
21 
22  use mpp_mod, only : mpp_pe, mpp_root_pe, mpp_sum
23  use fms_mod, only : write_version_number
25  use time_manager_mod, only : operator(+), operator(-)
27 
28  implicit none
29 
30  ! Include variable "version" to be written to log file.
31 #include<file_version.h>
32 
33  integer,public, parameter :: nelems=3
34  integer, parameter :: nelems_report=3
35  integer,public, parameter :: istock_water=1, istock_heat=2, istock_salt=3
36  integer,public, parameter :: istock_top=1, istock_bottom=2, istock_side=3
37  integer,public :: stocks_file
38  ! Stock related stuff
39  ! Shallow (no constructor) data structures holding the starting stock values (per PE) and
40  ! flux integrated increments at present time.
41 
42  integer, parameter :: nsides = 3 ! top, bottom, side
43 
44  type stock_type ! per PE values
45  real :: q_start = 0.0 ! total stocks at start time
46  real :: q_now = 0.0 ! total stocks at time t
47 
48  ! The dq's below are the stocks increments at the present time
49  ! delta_t * surf integr of flux
50  ! one for each side (ISTOCK_TOP, ISTOCK_BOTTOM, ISTOCK_SIDE)
51  real :: dq(nsides) = 0.0 ! stock increments at present time on the Ice grid
52  real :: dq_in(nsides) = 0.0 ! stock increments at present time on the Ocean grid
53  end type stock_type
54 
55  type(stock_type), save, dimension(NELEMS) :: atm_stock, ocn_stock, lnd_stock, ice_stock
56  type(time_type), save :: init_time
57 
58  public stocks_report
59  public stocks_report_init
61 
62  integer,private, parameter :: ncomps=4
63  integer,private, parameter :: istock_atm=1,istock_lnd=2,istock_ice=3,istock_ocn=4
64  character(len=3) , parameter, dimension(NCOMPS) :: comp_names=(/'ATM', 'LND', 'ICE', 'OCN'/)
65 
66 
67  character(len=5) , parameter, dimension(NELEMS) :: stock_names=(/'water', 'heat ', 'salt '/)
68  character(len=12), parameter, dimension(NELEMS) :: stock_units=(/'[Kg] ','[Joules]','[Kg] '/)
69 
70 
71 contains
72 
73 
74  subroutine stocks_report_init(Time)
75  type(time_type) , intent(in) :: time
76 
77  character(len=80) :: formatstring,space
78  integer :: i,s
79  real, dimension(NELEMS) :: val_atm, val_lnd, val_ice, val_ocn
80 
81  ! Write the version of this file to the log file
82  call write_version_number('STOCK_CONSTANTS_MOD', version)
83 
84  do i = 1, nelems_report
85  val_atm(i) = atm_stock(i)%q_start
86  val_lnd(i) = lnd_stock(i)%q_start
87  val_ice(i) = ice_stock(i)%q_start
88  val_ocn(i) = ocn_stock(i)%q_start
89  call mpp_sum(val_atm(i))
90  call mpp_sum(val_lnd(i))
91  call mpp_sum(val_ice(i))
92  call mpp_sum(val_ocn(i))
93  enddo
94 
95 
96 
97  if(mpp_pe() == mpp_root_pe()) then
98 ! earth_area = 4.*PI*Radius**2
99 
100  write(stocks_file,*) '================Stocks Report Guide====================================='
101  write(stocks_file,*) ' '
102  write(stocks_file,*) 'S(t) = Total amount of a tracer in the component model at time t.'
103  write(stocks_file,*) ' Calculated via the component model itself.'
104  write(stocks_file,*) ' '
105  write(stocks_file,*) 'F(t) = Cumulative input of a tracer to the component model at time t.'
106  write(stocks_file,*) ' Calculated via interchange of fluxes with other component models.'
107  write(stocks_file,*) ' '
108  write(stocks_file,*) 'S(t) - S(0) = Cumulative increase of the component stocks at time t'
109  write(stocks_file,*) ' Calculated by the component itself.'
110  write(stocks_file,*) ' '
111  write(stocks_file,*) 'In a conserving component F(t)=S(t)-S(0) to within numerical accuracy.'
112  write(stocks_file,*) ' '
113  write(stocks_file,*) 'Component Model refers to one of OCN, ATM, LND or ICE'
114  write(stocks_file,*) ''
115  write(stocks_file,*) 'NOTE: When use_lag_fluxes=.true. is used in coupler, the ocean stocks '
116  write(stocks_file,*) ' calculations are in error by an order which scales as the inverse'
117  write(stocks_file,*) ' of the number of time steps.'
118  write(stocks_file,*) ' '
119  write(stocks_file,*) '======================================================================='
120 
121 
122  write(stocks_file,*) '======================Initial Stock S(0)==============================='
123 !The following produces formatString='(5x,a,a,12x,a,a, 9x)' but is general to handle more elements
124  formatstring= '(5x'
125  do i=1,nelems_report
126  s = 25-len_trim(stock_names(i))-len_trim(stock_units(i))
127  write(space,'(i2)') s
128  formatstring= trim(formatstring)//',a,a,'//trim(space)
129  formatstring= trim(formatstring)//trim('x')
130  enddo
131  formatstring= trim(formatstring)//')'
132 
133  write(stocks_file,formatstring) (trim(stock_names(i)),trim(stock_units(i)), i=1,nelems_report)
134 
135 !The following produces formatString=' (a,x,es22.15,3x,es22.15,3x)' but is general to handle more elements
136  formatstring= '(a,x'
137  do i=1,nelems_report
138  write(space,'(i2)') s
139  formatstring= trim(formatstring)//',es22.15,3x'
140  enddo
141  formatstring= trim(formatstring)//')'
142 
143 
144  write(stocks_file,formatstring) 'ATM', (val_atm(i), i=1,nelems_report)
145  write(stocks_file,formatstring) 'LND', (val_lnd(i), i=1,nelems_report)
146  write(stocks_file,formatstring) 'ICE', (val_ice(i), i=1,nelems_report)
147  write(stocks_file,formatstring) 'OCN', (val_ocn(i), i=1,nelems_report)
148 
149  write(stocks_file,*) '========================================================================'
150  write(stocks_file,'(a)' ) ' '!blank line
151 
152  end if
153 
154  call stocks_set_init_time(time)
155 
156  end subroutine stocks_report_init
157 
158 
159  subroutine stocks_report(Time)
160  type(time_type) , intent(in) :: time
161 
162  type(time_type) :: timesincestart
163  type(stock_type) :: stck
164  real, dimension(NCOMPS) :: f_value, f_ice_grid, f_ocn_grid, f_ocn_btf, q_start, q_now,c_value
165  character(len=80) :: formatstring
166  integer :: iday0, isec0, iday, isec, hours
167  real :: days
168  integer :: diagid , comp,elem,i
169  integer, parameter :: initid = -2 ! initial value for diag IDs. Must not be equal to the value
170  ! that register_diag_field returns when it can't register the filed -- otherwise the registration
171  ! is attempted every time this subroutine is called
172 
173  integer, dimension(NCOMPS,NELEMS), save :: f_valuediagid = initid
174  integer, dimension(NCOMPS,NELEMS), save :: c_valuediagid = initid
175  integer, dimension(NCOMPS,NELEMS), save :: fmc_valuediagid = initid
176  integer, dimension(NCOMPS,NELEMS), save :: f_lostdiagid = initid
177 
178  real :: diagfield
179  logical :: used
180  character(len=30) :: field_name, units
181 
182  if(mpp_pe()==mpp_root_pe()) then
183  call get_time(init_time, isec0, iday0)
184  call get_time(time, isec, iday)
185 
186  hours = iday*24 + isec/3600 - iday0*24 - isec0/3600
187  days = hours/24.
188  write(stocks_file,*) '==============================================='
189  write(stocks_file,'(a,f12.3)') 't = TimeSinceStart[days]= ',days
190  write(stocks_file,*) '==============================================='
191  endif
192 
193  do elem = 1,nelems_report
194 
195  do comp = 1,ncomps
196 
197  if(comp == istock_atm) stck = atm_stock(elem)
198  if(comp == istock_lnd) stck = lnd_stock(elem)
199  if(comp == istock_ice) stck = ice_stock(elem)
200  if(comp == istock_ocn) stck = ocn_stock(elem)
201 
202 
203  f_ice_grid(comp) = sum(stck%dq)
204  f_ocn_grid(comp) = sum(stck%dq_IN)
205  f_ocn_btf(comp) = stck%dq_IN( istock_bottom )
206 
207  q_start(comp) = stck%q_start
208  q_now(comp) = stck%q_now
209 
210  call mpp_sum(f_ice_grid(comp))
211  call mpp_sum(f_ocn_grid(comp))
212  call mpp_sum(f_ocn_btf(comp))
213  call mpp_sum(q_start(comp))
214  call mpp_sum(q_now(comp))
215 
216  c_value(comp) = q_now(comp) - q_start(comp)
217 
218  if(mpp_pe() == mpp_root_pe()) then
219 
220  if(f_valuediagid(comp,elem) == initid) then
221  field_name = trim(comp_names(comp)) // trim(stock_names(elem))
222  field_name = trim(field_name) // 'StocksChange_Flux'
223  units = trim(stock_units(elem))
224  f_valuediagid(comp,elem) = register_diag_field('stock_print', field_name, time, &
225  units=units)
226  endif
227 
228  if(c_valuediagid(comp,elem) == initid) then
229  field_name = trim(comp_names(comp)) // trim(stock_names(elem))
230  field_name = trim(field_name) // 'StocksChange_Comp'
231  units = trim(stock_units(elem))
232  c_valuediagid(comp,elem) = register_diag_field('stock_print', field_name, time, &
233  units=units)
234  endif
235 
236  if(fmc_valuediagid(comp,elem) == initid) then
237  field_name = trim(comp_names(comp)) // trim(stock_names(elem))
238  field_name = trim(field_name) // 'StocksChange_Diff'
239  units = trim(stock_units(elem))
240  fmc_valuediagid(comp,elem) = register_diag_field('stock_print', field_name, time, &
241  units=units)
242  endif
243 
244  f_value(comp) = f_ice_grid(comp)
245 
246  if(comp == istock_ocn) then
247 
248  f_value(comp) = f_ocn_grid(comp)
249 
250  if(f_lostdiagid(comp,elem) == initid) then
251  field_name = trim(comp_names(comp)) // trim(stock_names(elem))
252  field_name = trim(field_name) // 'StocksExchangeLost'
253  units = trim(stock_units(elem))
254  f_lostdiagid(comp,elem) = register_diag_field('stock_print', field_name, time, &
255  units=units)
256  endif
257 
258  diagid=f_lostdiagid(comp,elem)
259  diagfield = f_ice_grid(comp) - f_ocn_grid(comp)
260  if (diagid > 0) used = send_data(diagid, diagfield, time)
261 
262  endif
263 
264 
265  diagid=f_valuediagid(comp,elem)
266  diagfield = f_value(comp)
267  if (diagid > 0) used = send_data(diagid, diagfield, time)
268  diagid=c_valuediagid(comp,elem)
269  diagfield = c_value(comp)
270  if (diagid > 0) used = send_data(diagid, diagfield, time)
271  diagid=fmc_valuediagid(comp,elem)
272  diagfield = f_value(comp)-c_value(comp)
273  if (diagid > 0) used = send_data(diagid, diagfield, time)
274 
275 
276  ! formatString = '(a,a,a,i16,2x,es22.15,2x,es22.15,2x,es22.15,2x,es22.15,2x,es22.15,2x,es22.15)'
277  !
278  ! write(stocks_file,formatString) trim(COMP_NAMES(comp)),STOCK_NAMES(elem),STOCK_UNITS(elem) &
279  ! ,hours, q_now, q_now-q_start, f_value, f_value - (q_now - q_start), (f_value - (q_now - q_start))/q_start
280 
281 
282  endif
283  enddo
284 
285 
286  if(mpp_pe()==mpp_root_pe()) then
287 ! write(stocks_file,'(a)' ) ' '!blank line
288 ! write(stocks_file,'(a,f12.3)') 't = TimeSinceStart[days]= ',days
289 ! write(stocks_file,'(a)' ) ' '!blank line
290 ! write(stocks_file,'(a,30x,a,20x,a,20x,a,20x,a)') 'Component ','ATM','LND','ICE','OCN'
291 ! write(stocks_file,'(55x,a,20x,a,20x,a,20x,a)') 'ATM','LND','ICE','OCN'
292 ! write(stocks_file,'(a,f12.3,12x,a,20x,a,20x,a,20x,a)') 't = TimeSinceStart[days]= ',days,'ATM','LND','ICE','OCN'
293 
294  write(stocks_file,'(a,a,40x,a,20x,a,20x,a,20x,a)') 'Stocks of ',trim(stock_names(elem)),'ATM','LND','ICE','OCN'
295  formatstring = '(a,a,2x,es22.15,2x,es22.15,2x,es22.15,2x,es22.15)'
296 
297  write(stocks_file,formatstring) 'Total =S(t) ',stock_units(elem),&
298  ( q_now(i), i=1,ncomps)
299  write(stocks_file,formatstring) 'Change=S(t)-S(0) ',stock_units(elem),&
300  ( q_now(i)-q_start(i), i=1,ncomps)
301  write(stocks_file,formatstring) 'Input =F(t) ',stock_units(elem),&
302  ( f_value(i), i=1,ncomps)
303  write(stocks_file,formatstring) 'Diff =F(t) - (S(t)-S(0)) ',stock_units(elem),&
304  ( f_value(i) - c_value(i), i=1,ncomps)
305  write(stocks_file,formatstring) 'Error =Diff/S(0) ','[NonDim] ', &
306  ((f_value(i) - c_value(i))/(1+q_start(i)), i=1,ncomps) !added 1 to avoid div by zero. Assuming q_start large
307 
308  write(stocks_file,'(a)' ) ' '!blank line
309  formatstring = '(a,a,a,6x,es22.15)'
310  write(stocks_file,formatstring) 'Lost Stocks in the exchange between Ice and Ocean ',trim(stock_names(elem)),trim(stock_units(elem)), &
311  f_ice_grid(istock_ocn) - f_ocn_grid(istock_ocn) + f_ocn_btf(istock_ocn)
312 
313  write(stocks_file,'(a)') ' ' !blank line
314  write(stocks_file,'(a)') ' ' !blank line
315 
316  endif
317  enddo
318 
319  end subroutine stocks_report
320 
321  subroutine stocks_set_init_time(Time)
322  type(time_type) , intent(in) :: time
323  init_time = time
324 
325  end subroutine stocks_set_init_time
326 
327 end module stock_constants_mod
Definition: fms.F90:20
integer, parameter nelems_report
character(len=3), dimension(ncomps), parameter comp_names
integer, parameter, public istock_salt
integer, parameter, public istock_heat
integer, parameter, public istock_bottom
integer, parameter, private istock_atm
character(len=12), dimension(nelems), parameter stock_units
Definition: mpp.F90:39
integer, parameter, public istock_top
integer, parameter, public nelems
integer, parameter, public istock_side
integer, parameter nsides
integer, public stocks_file
type(stock_type), dimension(nelems), save ice_stock
integer, parameter, private istock_ocn
character(len=5), dimension(nelems), parameter stock_names
integer, parameter, private istock_lnd
integer, parameter, private istock_ice
integer, parameter, public istock_water
subroutine, public stocks_report_init(Time)
integer, parameter, private ncomps
type(stock_type), dimension(nelems), save ocn_stock
type(stock_type), dimension(nelems), save lnd_stock
subroutine, public stocks_report(Time)
type(stock_type), dimension(nelems), save atm_stock
subroutine, public get_time(Time, seconds, days, ticks, err_msg)
subroutine, public stocks_set_init_time(Time)
type(time_type), save init_time