FMS  2025.04
Flexible Modeling System
astronomy.inc
1 !***********************************************************************
2 !* Apache License 2.0
3 !*
4 !* This file is part of the GFDL Flexible Modeling System (FMS).
5 !*
6 !* Licensed under the Apache License, Version 2.0 (the "License");
7 !* you may not use this file except in compliance with the License.
8 !* You may obtain a copy of the License at
9 !*
10 !* http://www.apache.org/licenses/LICENSE-2.0
11 !*
12 !* FMS is distributed in the hope that it will be useful, but WITHOUT
13 !* WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied;
14 !* without even the implied warranty of MERCHANTABILITY or FITNESS FOR A
15 !* PARTICULAR PURPOSE. See the License for the specific language
16 !* governing permissions and limitations under the License.
17 !***********************************************************************
18 !> @defgroup astronomy_mod astronomy_mod
19 !> @ingroup astronomy
20 !> @brief Provides astronomical variables for use
21 !! by other modules within fms. The only currently used interface is
22 !! for determination of astronomical values needed by the shortwave
23 !! radiation packages.
24 !> @author Fei Liu
25 
26 !> @addtogroup astronomy_mod
27 !> @{
28 
29 !> @brief set_orbital_parameters saves the input values of eccentricity,
30 !! obliquity and perihelion time as module variables for use by
31 !! astronomy_mod.
32 !!
33 !! @throw FATAL, "astronomy_mod module has not been initialized"
34 !! @throw FATAL, "astronomy_mod ecc must be between 0 and 0.99"
35 !! @throw FATAL, "astronomy_mod obliquity must be between -90. and 90. degrees"
36 !! @throw FATAL, "astronomy_mod perihelion must be between 0.0 and 360. degrees"
37 
38 subroutine set_orbital_parameters_(ecc_in, obliq_in, per_in)
39 
40 real(kind=fms_ast_kind_), intent(in) :: ecc_in !< Eccentricity of orbital ellipse [dimensionless]
41 real(kind=fms_ast_kind_), intent(in) :: obliq_in !< Obliquity [degrees]
42 real(kind=fms_ast_kind_), intent(in) :: per_in !< Longitude of perihelion with respect to autumnal
43  !! equinox in northern hemisphere [degrees]
44 
45 integer, parameter :: lkind = fms_ast_kind_
46 
47 !---------------------------------------------------------------------
48 ! exit if module has not been initialized.
49 !---------------------------------------------------------------------
50  if (.not. module_is_initialized) &
51  call error_mesg('astronomy_mod', 'module has not been initialized', fatal)
52 
53 !--------------------------------------------------------------------
54 ! be sure input values are within valid ranges.
55 ! QUESTION : ARE THESE THE RIGHT LIMITS ???
56 !---------------------------------------------------------------------
57 
58  if (ecc_in < 0.0_lkind .or. ecc_in > 0.99_lkind) &
59  call error_mesg('astronomy_mod', 'ecc must be between 0 and 0.99', fatal)
60  if (obliq_in < -90.0_lkind .or. real(obliq, fms_ast_kind_) > 90.0_lkind) &
61  call error_mesg('astronomy_mod', 'obliquity must be between -90. and 90. degrees', fatal)
62  if (per_in < 0.0_lkind .or. per_in > 360.0_lkind) &
63  call error_mesg('astronomy_mod', 'perihelion must be between 0.0 and 360. degrees', fatal)
64 
65 !---------------------------------------------------------------------
66 ! save input values into module variables.
67 !---------------------------------------------------------------------
68 
69  ecc = real(ecc_in, r8_kind)
70  obliq = real(obliq_in, r8_kind)
71  per = real(per_in, r8_kind)
72 
73 !---------------------------------------------------------------------
74 ! call orbit to define table of orbital angles as function of
75 ! orbital time using the input values of parameters just supplied.
76 !----------------------------------------------------------------------
77 
78  call orbit
79 
80 !----------------------------------------------------------------------
81 
82 end subroutine set_orbital_parameters_
83 
84 !> @brief get_orbital_parameters retrieves the orbital parameters for use
85 !! by another module.
86 !!
87 !! @throw FATAL, "astronomy_mod module has not been initialized"
88 
89 subroutine get_orbital_parameters_(ecc_out, obliq_out, per_out)
90 
91 !-------------------------------------------------------------------
92 ! get_orbital_parameters retrieves the orbital parameters for use
93 ! by another module.
94 !--------------------------------------------------------------------
95 
96 
97 real(kind=fms_ast_kind_), intent(out) :: ecc_out !< Eccentricity of orbital ellipse [dimensionless]
98 real(kind=fms_ast_kind_), intent(out) :: obliq_out !< Obliquity [degrees]
99 real(kind=fms_ast_kind_), intent(out) :: per_out !< Longitude of perihelion with respect to autumnal
100  !! equinox in northern hemisphere [degrees]
101 
102 !---------------------------------------------------------------------
103 ! exit if module has not been initialized.
104 !---------------------------------------------------------------------
105 
106  if (.not. module_is_initialized) &
107  call error_mesg('astronomy_mod', 'module has not been initialized', fatal)
108 
109 !--------------------------------------------------------------------
110 ! fill the output arguments with the eccentricity, obliquity and
111 ! perihelion angle.
112 !--------------------------------------------------------------------
113 
114  ecc_out = real(ecc, fms_ast_kind_)
115  obliq_out = real(obliq, fms_ast_kind_)
116  per_out = real(per, fms_ast_kind_)
117 
118 end subroutine get_orbital_parameters_
119 
120 
121 !> @brief diurnal_solar_2d returns 2d fields of cosine of zenith angle,
122 !! daylight fraction and earth-sun distance at the specified latitudes,
123 !! longitudes and time. These values may be instantaneous or averaged
124 !! over a specified time interval.
125 !!
126 !! @param [in] <lat> Latitudes of model grid points
127 !! @param [in] <lon> Longitudes of model grid points
128 !! @param [in] <gmt> Time of day at longitude 0.0; midnight = 0.0, one day = 2 * pi
129 !! @param [in] <time_since_ae> Time of year; autumnal equinox = 0.0, one year = 2 * pi
130 !! @param [out] <cosz> Cosine of solar zenith angle
131 !! @param [out] <fracday> Daylight fraction of time interval
132 !! @param [out] <rrsun> earth-sun distance (r) relative to semi-major axis of orbital ellipse (a):(a/r)**2
133 !! @param [in] <dt> OPTIONAL: time interval after gmt over which the astronomical variables are to be
134 !! averaged. this produces averaged output rather than instantaneous.
135 !! @param [in] <allow_negative_cosz> Allow negative values for cosz?
136 !! @param [out] <half_day_out> half_day_out
137 !!
138 !! @throw FATAL, "astronomy_mod time_since_ae not between 0 and 2pi"
139 !! @throw FATAL, "astronomy_mod gmt not between 0 and 2pi"
140 
141 subroutine diurnal_solar_2d_(lat, lon, gmt, time_since_ae, cosz, &
142  fracday, rrsun, dt, allow_negative_cosz, &
143  half_day_out)
144 
145 real(kind=fms_ast_kind_), dimension(:,:), intent(in) :: lat, lon
146 real(kind=fms_ast_kind_), intent(in) :: gmt, time_since_ae
147 real(kind=fms_ast_kind_), dimension(:,:), intent(out) :: cosz, fracday
148 real(kind=fms_ast_kind_), intent(out) :: rrsun
149 real(kind=fms_ast_kind_), intent(in), optional :: dt
150 logical, intent(in), optional :: allow_negative_cosz
151 real(kind=fms_ast_kind_), dimension(:,:), intent(out), optional :: half_day_out
152 
153 !---------------------------------------------------------------------
154 ! local variables
155 
156 
157 real(kind=fms_ast_kind_), dimension(size(lat,1),size(lat,2)) :: t, tt, h, aa, bb, st, stt, sh
158 real(kind=fms_ast_kind_) :: ang, dec
159 logical :: Lallow_negative
160 integer, parameter :: lkind = fms_ast_kind_
161 
162 
163 !---------------------------------------------------------------------
164 ! local variables
165 !
166 ! t time of day with respect to local noon (2 pi = 1 day)
167 ! [ radians ]
168 ! tt end of averaging period [ radians ]
169 ! h half of the daily period of daylight, centered at noon
170 ! [ radians, -pi --> pi ]
171 ! aa sin(lat) * sin(declination)
172 ! bb cos(lat) * cos(declination)
173 ! st sine of time of day
174 ! stt sine of time of day at end of averaging period
175 ! sh sine of half-day period
176 ! ang position of earth in its orbit wrt autumnal equinox
177 ! [ radians ]
178 ! dec earth's declination [ radians ]
179 !
180 !--------------------------------------------------------------------
181 
182 !--------------------------------------------------------------------
183 ! be sure the time in the annual cycle is legitimate.
184 !---------------------------------------------------------------------
185 
186  if (time_since_ae < 0.0_lkind .or. time_since_ae > real(twopi, fms_ast_kind_)) &
187  call error_mesg('astronomy_mod', 'time_since_ae not between 0 and 2pi', fatal)
188 
189 !--------------------------------------------------------------------
190 ! be sure the time at longitude = 0.0 is legitimate.
191 !---------------------------------------------------------------------
192 
193  if (gmt < 0.0_lkind .or. gmt > real(twopi, fms_ast_kind_)) &
194  call error_mesg('astronomy_mod', 'gmt not between 0 and 2pi', fatal)
195 
196 !---------------------------------------------------------------------
197 !> define the orbital angle (location in year), solar declination and
198 !! earth sun distance factor. use functions contained in this module.
199 !---------------------------------------------------------------------
200 
201  ang = angle(time_since_ae)
202  dec = declination(ang)
203  rrsun = r_inv_squared(ang)
204 
205 !---------------------------------------------------------------------
206 !> define terms needed in the cosine zenith angle equation.
207 !--------------------------------------------------------------------
208 
209  aa = sin(lat)*sin(dec)
210  bb = cos(lat)*cos(dec)
211 
212 !---------------------------------------------------------------------
213 !> define local time. force it to be between -pi and pi.
214 !--------------------------------------------------------------------
215 
216  t = gmt + lon - real(pi, fms_ast_kind_)
217  where(t >= real(pi, fms_ast_kind_)) t = t - real(twopi, fms_ast_kind_)
218  where(t < real(-pi,fms_ast_kind_)) t = t + real(twopi, fms_ast_kind_)
219 
220  lallow_negative = .false.
221  if (present(allow_negative_cosz)) then
222  if (allow_negative_cosz) lallow_negative = .true.
223  end if
224 
225 
226 !---------------------------------------------------------------------
227 !> perform a time integration to obtain cosz and fracday if desired.
228 !! output is valid over the period from t to t + dt.
229 !--------------------------------------------------------------------
230 
231  h = half_day(lat,dec)
232 
233  if ( present(half_day_out) ) then
234  half_day_out = h
235  end if
236 
237  if ( present(dt) ) then ! (perform time averaging)
238  tt = t + dt
239  st = sin(t)
240  stt = sin(tt)
241  sh = sin(h)
242  cosz = 0.0_lkind
243 
244  if (.not. lallow_negative) then
245 !-------------------------------------------------------------------
246 ! case 1: entire averaging period is before sunrise.
247 !-------------------------------------------------------------------
248 
249  where (t < -h .and. tt < -h) cosz = 0.0_lkind
250 
251 !-------------------------------------------------------------------
252 ! case 2: averaging period begins before sunrise, ends after sunrise
253 ! but before sunset
254 !-------------------------------------------------------------------
255 
256  where ( (tt+h) /= 0.0_lkind .and. t < -h .and. abs(tt) <= h) &
257  cosz = aa + bb*(stt + sh)/ (tt + h)
258 
259 !-------------------------------------------------------------------
260 ! case 3: averaging period begins before sunrise, ends after sunset,
261 ! but before the next sunrise. modify if averaging period extends
262 ! past the next day's sunrise, but if averaging period is less than
263 ! a half- day (pi) that circumstance will never occur.
264 !-------------------------------------------------------------------
265 
266  where (t < -h .and. h /= 0.0_lkind .and. h < tt) &
267  cosz = aa + bb*( sh + sh)/(h+h)
268 
269 !-------------------------------------------------------------------
270 ! case 4: averaging period begins after sunrise, ends before sunset.
271 !-------------------------------------------------------------------
272  where ( abs(t) <= h .and. abs(tt) <= h) &
273 
274  cosz = aa + bb*(stt - st)/ (tt - t)
275 
276 !-------------------------------------------------------------------
277 ! case 5: averaging period begins after sunrise, ends after sunset.
278 ! modify when averaging period extends past the next day's sunrise.
279 !-------------------------------------------------------------------
280 
281  where ((h-t) /= 0.0_lkind .and. abs(t) <= h .and. h < tt) &
282  cosz = aa + bb*(sh - st)/(h-t)
283 
284 !-------------------------------------------------------------------
285 ! case 6: averaging period begins after sunrise , ends after the
286 ! next day's sunrise. note that this includes the case when the
287 ! day length is one day (h = pi).
288 !-------------------------------------------------------------------
289 
290  where (real(twopi, fms_ast_kind_) - h < tt .and. &
291  (tt+h-real(twopi, fms_ast_kind_)) /= 0.0_lkind .and. t <= h ) &
292  cosz = (cosz*(h - t) + (aa*(tt + h - real(twopi, fms_ast_kind_)) + bb &
293  * (stt + sh))) / ((h - t) + (tt + h - real(twopi, fms_ast_kind_)))
294 
295 !-------------------------------------------------------------------
296 ! case 7: averaging period begins after sunset and ends before the
297 ! next day's sunrise
298 !-------------------------------------------------------------------
299 
300  where(h < t .and. real(twopi, fms_ast_kind_) - h >= tt) &
301  cosz = 0.0_lkind
302 
303 !-------------------------------------------------------------------
304 ! case 8: averaging period begins after sunset and ends after the
305 ! next day's sunrise but before the next day's sunset. if the
306 ! averaging period is less than a half-day (pi) the latter
307 ! circumstance will never occur.
308 !-----------------------------------------------------------------
309 
310  where (h < t .and. real(twopi, fms_ast_kind_) - h < tt)
311  cosz = aa + bb*(stt + sh) / (tt + h - real(twopi, fms_ast_kind_))
312  end where
313 
314  else
315  cosz = aa + bb*(stt - st)/ (tt - t)
316  end if
317 
318 
319 
320 !-------------------------------------------------------------------
321 ! day fraction is the fraction of the averaging period contained
322 ! within the (-h,h) period.
323 !-------------------------------------------------------------------
324 
325  where (t < -h .and. tt < -h) fracday = 0.0_lkind
326  where (t < -h .and. abs(tt) <= h) fracday = (tt + h )/dt
327  where (t < -h .and. h < tt) fracday = ( h + h )/dt
328  where (abs(t) <= h .and. abs(tt) <= h) fracday = (tt - t )/dt
329  where (abs(t) <= h .and. h < tt) fracday = ( h - t )/dt
330  where (h < t) fracday = 0.0_lkind
331  where (real(twopi, fms_ast_kind_) - h < tt) &
332  fracday = fracday + (tt + h - real(twopi, fms_ast_kind_))/dt
333 !----------------------------------------------------------------------
334 !> if instantaneous values are desired, define cosz at time t.
335 !----------------------------------------------------------------------
336  else ! (no time averaging)
337  if (.not. lallow_negative) then
338  where (abs(t) < h)
339  cosz = aa + bb*cos(t)
340  fracday = 1.0_lkind
341  elsewhere
342  cosz = 0.0_lkind
343  fracday = 0.0_lkind
344  end where
345  else
346  cosz = aa + bb*cos(t)
347  where (abs(t) < h)
348  fracday = 1.0_lkind
349  elsewhere
350  fracday = 0.0_lkind
351  end where
352  end if
353  end if
354 
355 
356 !----------------------------------------------------------------------
357 !> Check that cosz is not negative, if desired.
358 !----------------------------------------------------------------------
359 
360  if (.not. lallow_negative) then
361  cosz = max(0.0_lkind, cosz)
362  end if
363 
364 end subroutine diurnal_solar_2d_
365 
366 
367 !> @brief diurnal_solar_1d takes 1-d input fields, adds a second dimension
368 !! and calls diurnal_solar_2d. on return, the 2d fields are returned
369 !! to the original 1d fields.
370 !!
371 !! @param [in] <lat> Latitudes of model grid points
372 !! @param [in] <lon> Longitudes of model grid points
373 !! @param [in] <gmt> Time of day at longitude 0.0; midnight = 0.0, one day = 2 * pi
374 !! @param [in] <time_since_ae> Time of year; autumnal equinox = 0.0, one year = 2 * pi
375 !! @param [out] <cosz> Cosine of solar zenith angle
376 !! @param [out] <fracday> Daylight fraction of time interval
377 !! @param [out] <rrsun> earth-sun distance (r) relative to semi-major axis of orbital ellipse (a):(a/r)**2
378 !! @param [in] <dt> OPTIONAL: time interval after gmt over which the astronomical variables are to be
379 !! averaged. this produces averaged output rather than instantaneous.
380 !! @param [in] <allow_negative_cosz> Allow negative values for cosz?
381 !! @param [out] <half_day_out> half_day_out
382 
383 subroutine diurnal_solar_1d_(lat, lon, gmt, time_since_ae, cosz, &
384  fracday, rrsun, dt, allow_negative_cosz, &
385  half_day_out)
386 
387 !---------------------------------------------------------------------
388 
389 real(kind=fms_ast_kind_), dimension(:), intent(in) :: lat, lon
390 real(kind=fms_ast_kind_), intent(in) :: gmt, time_since_ae
391 real(kind=fms_ast_kind_), dimension(:), intent(out) :: cosz, fracday
392 real(kind=fms_ast_kind_), intent(out) :: rrsun
393 real(kind=fms_ast_kind_), intent(in), optional :: dt
394 logical, intent(in), optional :: allow_negative_cosz
395 real(kind=fms_ast_kind_), dimension(:), intent(out), optional :: half_day_out
396 
397 !---------------------------------------------------------------------
398 ! local variables
399 !---------------------------------------------------------------------
400 
401 real(kind=fms_ast_kind_), dimension(size(lat),1) :: lat_2d, lon_2d, cosz_2d, fracday_2d, halfday_2d
402 
403 !--------------------------------------------------------------------
404 !> define 2-d versions of input data arrays.
405 !--------------------------------------------------------------------
406 
407  lat_2d(:,1) = lat
408  lon_2d(:,1) = lon
409 
410 
411 !--------------------------------------------------------------------
412 !> call diurnal_solar_2d to calculate astronomy fields.
413 !--------------------------------------------------------------------
414 ! if (present(dt)) then
415 
416  call diurnal_solar(lat_2d, lon_2d, gmt, time_since_ae, &
417  cosz_2d, fracday_2d, rrsun, dt=dt, &
418  allow_negative_cosz=allow_negative_cosz, half_day_out=halfday_2d)
419 ! else
420 ! call diurnal_solar_2d (lat_2d, lon_2d, gmt, time_since_ae, &
421 ! cosz_2d, fracday_2d, rrsun)
422 ! endif
423 
424 !-------------------------------------------------------------------
425 !> place output fields into 1-d arguments for return to
426 !! calling routine.
427 !-------------------------------------------------------------------
428 
429  fracday = fracday_2d(:,1)
430  cosz = cosz_2d(:,1)
431  if (present(half_day_out)) then
432  half_day_out = halfday_2d(:,1)
433  end if
434 
435 end subroutine diurnal_solar_1d_
436 
437 
438 
439 !> @brief diurnal_solar_0d takes scalar input fields, makes them into 2d
440 !! arrays dimensioned (1,1), and calls diurnal_solar_2d. on return,
441 !! the 2d fields are converted back to the desired scalar output.
442 !!
443 !! @param [in] <lat> Latitudes of model grid points
444 !! @param [in] <lon> Longitudes of model grid points
445 !! @param [in] <gmt> Time of day at longitude 0.0; midnight = 0.0, one day = 2 * pi
446 !! @param [in] <time_since_ae> Time of year; autumnal equinox = 0.0, one year = 2 * pi
447 !! @param [out] <cosz> Cosine of solar zenith angle
448 !! @param [out] <fracday> Daylight fraction of time interval
449 !! @param [out] <rrsun> earth-sun distance (r) relative to semi-major axis of orbital ellipse (a):(a/r)**2
450 !! @param [in] <dt> OPTIONAL: time interval after gmt over which the astronomical variables are to be
451 !! averaged. this produces averaged output rather than instantaneous.
452 !! @param [in] <allow_negative_cosz> Allow negative values for cosz?
453 !! @param [out] <half_day_out> half_day_out
454 
455 subroutine diurnal_solar_0d_(lat, lon, gmt, time_since_ae, cosz, &
456  fracday, rrsun, dt, allow_negative_cosz, &
457  half_day_out)
458 
459 real(kind=fms_ast_kind_), intent(in) :: lat, lon, gmt, time_since_ae
460 real(kind=fms_ast_kind_), intent(out) :: cosz, fracday, rrsun
461 real(kind=fms_ast_kind_), intent(in), optional :: dt
462 logical, intent(in), optional :: allow_negative_cosz
463 real(kind=fms_ast_kind_), intent(out), optional :: half_day_out
464 
465 !--------------------------------------------------------------------
466 ! local variables:
467 !--------------------------------------------------------------------
468 
469 real(kind=fms_ast_kind_), dimension(1,1) :: lat_2d, lon_2d, cosz_2d, fracday_2d, halfday_2d
470 
471 !---------------------------------------------------------------------
472 !> create 2d arrays from the scalar input fields.
473 !---------------------------------------------------------------------
474 
475  lat_2d = lat
476  lon_2d = lon
477 
478 !--------------------------------------------------------------------
479 !> call diurnal_solar_2d to calculate astronomy fields.
480 !--------------------------------------------------------------------
481 ! if (present(dt)) then
482 
483  call diurnal_solar(lat_2d, lon_2d, gmt, time_since_ae, &
484  cosz_2d, fracday_2d, rrsun, dt=dt, &
485  allow_negative_cosz=allow_negative_cosz, half_day_out=halfday_2d)
486 ! else
487 ! call diurnal_solar_2d (lat_2d, lon_2d, gmt, time_since_ae, &
488 ! cosz_2d, fracday_2d, rrsun)
489 ! end if
490 
491 !-------------------------------------------------------------------
492 !> place output fields into scalars for return to calling routine.
493 !-------------------------------------------------------------------
494 
495  fracday = fracday_2d(1,1)
496  cosz = cosz_2d(1,1)
497  if (present(half_day_out)) then
498  half_day_out = halfday_2d(1,1)
499  end if
500 
501 end subroutine diurnal_solar_0d_
502 
503 
504 !> @brief diurnal_solar_cal_2d receives time_type inputs, converts
505 !! them to real variables and then calls diurnal_solar_2d to
506 !! compute desired astronomical variables.
507 !!
508 !! @param [in] <lat> Latitudes of model grid points
509 !! @param [in] <lon> Longitudes of model grid points
510 !! @param [in] <gmt> Time of day at longitude 0.0; midnight = 0.0, one day = 2 * pi
511 !! @param [in] <time> Time of year (time_type)
512 !! @param [out] <cosz> Cosine of solar zenith angle
513 !! @param [out] <fracday> Daylight fraction of time interval
514 !! @param [out] <rrsun> earth-sun distance (r) relative to semi-major axis of orbital ellipse (a):(a/r)**2
515 !! @param [in] <dt> OPTIONAL: time interval after gmt over which the astronomical variables are to be
516 !! averaged. this produces averaged output rather than instantaneous.
517 !! @param [in] <allow_negative_cosz> Allow negative values for cosz?
518 !! @param [out] <half_day_out> half_day_out
519 !!
520 !! @throw FATAL, "astronomy_mod radiation time step must be no longer than 12 hrs"
521 !! @throw FATAL, "astronomy_mod radiation time step must not be an integral number of days"
522 
523 subroutine diurnal_solar_cal_2d_(lat, lon, time, cosz, fracday, &
524  rrsun, dt_time, allow_negative_cosz, &
525  half_day_out)
526 
527 !-------------------------------------------------------------------
528 
529 real(kind=fms_ast_kind_), dimension(:,:), intent(in) :: lat, lon
530 type(time_type), intent(in) :: time
531 real(kind=fms_ast_kind_), dimension(:,:), intent(out) :: cosz, fracday
532 real(kind=fms_ast_kind_), intent(out) :: rrsun
533 type(time_type), intent(in), optional :: dt_time
534 logical, intent(in), optional :: allow_negative_cosz
535 real(kind=fms_ast_kind_), dimension(:,:), intent(out), optional :: half_day_out
536 
537 !---------------------------------------------------------------------
538 
539 !---------------------------------------------------------------------
540 ! local variables
541 !---------------------------------------------------------------------
542 
543 real(kind=fms_ast_kind_) :: dt
544 real(kind=fms_ast_kind_) :: gmt, time_since_ae
545 integer, parameter :: lkind = fms_ast_kind_
546 
547 !---------------------------------------------------------------------
548 !> Extract time of day (gmt) from time_type variable time with
549 !! function universal_time.
550 !---------------------------------------------------------------------
551 
552  gmt = real(universal_time(time), fms_ast_kind_)
553 
554 !---------------------------------------------------------------------
555 !> Extract the time of year (time_since_ae) from time_type variable
556 !! time using the function orbital_time.
557 !---------------------------------------------------------------------
558 
559  time_since_ae = real(orbital_time(time), fms_ast_kind_)
560 
561 !---------------------------------------------------------------------
562 !> Convert optional time_type variable dt_time (length of averaging
563 !! period) to a real variable dt with the function universal_time.
564 !---------------------------------------------------------------------
565 
566  if (present(dt_time)) then
567  dt = real(universal_time(dt_time), fms_ast_kind_)
568  if (dt > real(pi, fms_ast_kind_)) then
569  call error_mesg('astronomy_mod', 'radiation time step must be no longer than 12 hrs', fatal)
570  endif
571  if (dt == 0.0_lkind) then
572  call error_mesg('astronomy_mod', 'radiation time step must not be an integral number of days', fatal)
573  endif
574 
575 !--------------------------------------------------------------------
576 !> Call diurnal_solar_2d to calculate astronomy fields, with or
577 !! without the optional argument dt.
578 !--------------------------------------------------------------------
579 
580  call diurnal_solar(lat, lon, gmt, time_since_ae, cosz, &
581  fracday, rrsun, dt=dt, &
582  allow_negative_cosz=allow_negative_cosz, &
583  half_day_out=half_day_out)
584  else
585  call diurnal_solar(lat, lon, gmt, time_since_ae, cosz, &
586  fracday, rrsun, allow_negative_cosz=allow_negative_cosz, &
587  half_day_out=half_day_out)
588  end if
589 
590 end subroutine diurnal_solar_cal_2d_
591 
592 
593 !> @brief diurnal_solar_cal_1d receives time_type inputs, converts
594 !! them to real variables and then calls diurnal_solar_2d to
595 !! compute desired astronomical variables.
596 !!
597 !! @param [in] <lat> Latitudes of model grid points
598 !! @param [in] <lon> Longitudes of model grid points
599 !! @param [in] <gmt> Time of day at longitude 0.0; midnight = 0.0, one day = 2 * pi
600 !! @param [in] <time> Time of year (time_type)
601 !! @param [out] <cosz> Cosine of solar zenith angle
602 !! @param [out] <fracday> Daylight fraction of time interval
603 !! @param [out] <rrsun> earth-sun distance (r) relative to semi-major axis of orbital ellipse (a):(a/r)**2
604 !! @param [in] <dt> OPTIONAL: time interval after gmt over which the astronomical variables are to be
605 !! averaged. this produces averaged output rather than instantaneous.
606 !! @param [in] <allow_negative_cosz> Allow negative values for cosz?
607 !! @param [out] <half_day_out> half_day_out
608 
609 subroutine diurnal_solar_cal_1d_(lat, lon, time, cosz, fracday, &
610  rrsun, dt_time, allow_negative_cosz, &
611  half_day_out)
612 
613 !--------------------------------------------------------------------
614 
615 real(kind=fms_ast_kind_), dimension(:), intent(in) :: lat, lon
616 type(time_type), intent(in) :: time
617 real(kind=fms_ast_kind_), dimension(:), intent(out) :: cosz, fracday
618 real(kind=fms_ast_kind_), intent(out) :: rrsun
619 type(time_type), intent(in), optional :: dt_time
620 logical, intent(in), optional :: allow_negative_cosz
621 real(kind=fms_ast_kind_), dimension(:), intent(out), optional :: half_day_out
622 !--------------------------------------------------------------------
623 
624 !-------------------------------------------------------------------
625 ! local variables
626 !-------------------------------------------------------------------
627 
628 real(kind=fms_ast_kind_), dimension(size(lat),1) :: lat_2d, lon_2d, cosz_2d, &
629  fracday_2d, halfday_2d
630 
631 !--------------------------------------------------------------------
632 !> Define 2-d versions of input data arrays.
633 !--------------------------------------------------------------------
634 
635  lat_2d(:,1) = lat
636  lon_2d(:,1) = lon
637 
638 !--------------------------------------------------------------------
639 !> Call diurnal_solar_cal_2d to convert the time_types to reals and
640 !! then calculate the astronomy fields.
641 !--------------------------------------------------------------------
642 
643  if (present(dt_time)) then
644  call diurnal_solar(lat_2d, lon_2d, time, cosz_2d, &
645  fracday_2d, rrsun, dt_time=dt_time, &
646  allow_negative_cosz=allow_negative_cosz, &
647  half_day_out=halfday_2d)
648  else
649  call diurnal_solar(lat_2d, lon_2d, time, cosz_2d, &
650  fracday_2d, rrsun, allow_negative_cosz=allow_negative_cosz, &
651  half_day_out=halfday_2d)
652  end if
653 
654 !-------------------------------------------------------------------
655 !> Place output fields into 1-d arguments for return to
656 !! calling routine.
657 !-------------------------------------------------------------------
658 
659  fracday = fracday_2d(:,1)
660  cosz = cosz_2d(:,1)
661  if (present(half_day_out)) then
662  half_day_out = halfday_2d(:,1)
663  end if
664 
665 end subroutine diurnal_solar_cal_1d_
666 
667 
668 !> @brief diurnal_solar_cal_0d receives time_type inputs, converts them to real variables
669 !! and then calls diurnal_solar_2d to compute desired astronomical variables.
670 !!
671 !! @param [in] <lat> Latitudes of model grid points
672 !! @param [in] <lon> Longitudes of model grid points
673 !! @param [in] <time> Time of year (time_type)
674 !! @param [out] <cosz> Cosine of solar zenith angle
675 !! @param [out] <fracday> Daylight fraction of time interval
676 !! @param [out] <rrsun> Earth-Sun distance (r) relative to semi-major axis of orbital ellipse (a) : (a/r)**2
677 !! @param [out] <dt_time> OPTIONAL: time interval after gmt over which the astronomical variables are
678 !! to be averaged. this produces averaged output rather than instantaneous.
679 !! @param [in] <allow_negative_cosz> allow_negative_cosz
680 !! @param [out] <half_day_out> half_day_out
681 
682 subroutine diurnal_solar_cal_0d_(lat, lon, time, cosz, fracday, &
683  rrsun, dt_time, allow_negative_cosz, &
684  half_day_out)
685 
686 !---------------------------------------------------------------------
687 
688 real(kind=fms_ast_kind_), intent(in) :: lat, lon
689 type(time_type), intent(in) :: time
690 real(kind=fms_ast_kind_), intent(out) :: cosz, fracday, rrsun
691 type(time_type), intent(in), optional :: dt_time
692 logical, intent(in), optional :: allow_negative_cosz
693 real(kind=fms_ast_kind_), intent(out), optional :: half_day_out
694 
695 !---------------------------------------------------------------------
696 
697 !---------------------------------------------------------------------
698 ! local variables
699 !---------------------------------------------------------------------
700 
701 real(kind=fms_ast_kind_), dimension(1,1) :: lat_2d, lon_2d, cosz_2d, fracday_2d, halfday_2d
702 
703 !--------------------------------------------------------------------
704 !> Define 2-d versions of input data arrays.
705 !--------------------------------------------------------------------
706 
707  lat_2d = lat
708  lon_2d = lon
709 
710 !--------------------------------------------------------------------
711 !> Call diurnal_solar_cal_2d to convert the time_types to reals and
712 !! then calculate the astronomy fields.
713 !--------------------------------------------------------------------
714 
715  if (present(dt_time)) then
716  call diurnal_solar(lat_2d, lon_2d, time, cosz_2d, &
717  fracday_2d, rrsun, dt_time=dt_time, &
718  allow_negative_cosz=allow_negative_cosz, &
719  half_day_out=halfday_2d)
720  else
721  call diurnal_solar(lat_2d, lon_2d, time, cosz_2d, &
722  fracday_2d, rrsun, allow_negative_cosz=allow_negative_cosz, &
723  half_day_out=halfday_2d)
724  end if
725 
726 !-------------------------------------------------------------------
727 !> Place output fields into 1-d arguments for return to
728 !! calling routine.
729 !-------------------------------------------------------------------
730 
731  fracday = fracday_2d(1,1)
732  cosz = cosz_2d(1,1)
733  if (present(half_day_out)) then
734  half_day_out = halfday_2d(1,1)
735  end if
736 
737 end subroutine diurnal_solar_cal_0d_
738 
739 
740 !> @brief daily_mean_solar_2d computes the daily mean astronomical parameters for
741 !! the input points at latitude lat and time of year time_since_ae.
742 !!
743 !! @param [in] <lat> Latitudes of model grid points
744 !! @param [in] <time_since_ae> Time of year; autumnal equinox = 0.0, one year = 2 * pi
745 !! @param [out] <cosz> Cosine of solar zenith angle
746 !! @param [out] <h_out> 2-d array of half-day lengths at the latitudes
747 !! @param [out] <rr_out> the inverse of the square of the earth-sun distance relative
748 !! to the mean distance at angle ang in the earth's orbit.
749 !!
750 !! @throw FATAL, "astronomy_mod time_since_ae not between 0 and 2pi"
751 
752 subroutine daily_mean_solar_2d_(lat, time_since_ae, cosz, h_out, rr_out)
753 
754 !----------------------------------------------------------------------
755 real(kind=fms_ast_kind_), dimension(:,:), intent(in) :: lat
756 real(kind=fms_ast_kind_), intent(in) :: time_since_ae
757 real(kind=fms_ast_kind_), dimension(:,:), intent(out) :: cosz, h_out
758 real(kind=fms_ast_kind_), intent(out) :: rr_out
759 !----------------------------------------------------------------------
760 
761 !--------------------------------------------------------------------
762 ! local variables
763 !--------------------------------------------------------------------
764 
765 real(kind=fms_ast_kind_), dimension(size(lat,1),size(lat,2)) :: h
766 real(kind=fms_ast_kind_) :: ang, dec, rr
767 integer, parameter :: lkind = fms_ast_kind_
768 
769 !--------------------------------------------------------------------
770 ! be sure the time in the annual cycle is legitimate.
771 !---------------------------------------------------------------------
772 
773  if (time_since_ae < 0.0_lkind .or. time_since_ae > real(twopi, fms_ast_kind_)) &
774  call error_mesg('astronomy_mod', 'time_since_ae not between 0 and 2pi', fatal)
775 
776 !---------------------------------------------------------------------
777 !> Define the orbital angle (location in year), solar declination,
778 !! half-day length and earth sun distance factor. Use functions
779 !! contained in this module.
780 !---------------------------------------------------------------------
781 
782  ang = angle(time_since_ae)
783  dec = declination(ang)
784  h = half_day(lat, dec)
785  rr = r_inv_squared(ang)
786 
787 !---------------------------------------------------------------------
788 !> Where the entire day is dark, define cosz to be zero. otherwise
789 !! use the standard formula. Define the daylight fraction and earth-
790 !! sun distance.
791 !---------------------------------------------------------------------
792 
793  where (h == 0.0_lkind)
794  cosz = 0.0_lkind
795  elsewhere
796  cosz = sin(lat)*sin(dec) + cos(lat)*cos(dec)*sin(h)/h
797  end where
798  h_out = h/real(pi, fms_ast_kind_)
799  rr_out = rr
800 
801 end subroutine daily_mean_solar_2d_
802 
803 
804 !> @brief daily_mean_solar_1d takes 1-d input fields, adds a second dimension
805 !! and calls daily_mean_solar_2d. on return, the 2d fields are
806 !! returned to the original 1d fields.
807 !!
808 !! @param [in] <lat> Latitudes of model grid points
809 !! @param [in] <time_since_ae> Time of year; autumnal equinox = 0.0, one year = 2 * pi
810 !! @param [out] <cosz> Cosine of solar zenith angle
811 !! @param [out] <h_out> 2-d array of half-day lengths at the latitudes
812 !! @param [out] <rr_out> the inverse of the square of the earth-sun distance relative
813 !! to the mean distance at angle ang in the earth's orbit.
814 
815 subroutine daily_mean_solar_1d_(lat, time_since_ae, cosz, h_out, rr_out)
816 
817 !----------------------------------------------------------------------
818 real(kind=fms_ast_kind_), intent(in), dimension(:) :: lat
819 real(kind=fms_ast_kind_), intent(in) :: time_since_ae
820 real(kind=fms_ast_kind_), intent(out), dimension(size(lat(:))) :: cosz
821 real(kind=fms_ast_kind_), intent(out), dimension(size(lat(:))) :: h_out
822 real(kind=fms_ast_kind_), intent(out) :: rr_out
823 
824 !----------------------------------------------------------------------
825 
826 !----------------------------------------------------------------------
827 ! local variables
828 !----------------------------------------------------------------------
829 
830 real(kind=fms_ast_kind_), dimension(size(lat),1) :: lat_2d, cosz_2d, hout_2d
831 
832 !--------------------------------------------------------------------
833 !> define 2-d versions of input data array.
834 !--------------------------------------------------------------------
835 
836  lat_2d(:,1) = lat
837 
838 !--------------------------------------------------------------------
839 !> call daily_mean_solar_2d to calculate astronomy fields.
840 !--------------------------------------------------------------------
841 
842  call daily_mean_solar(lat_2d, time_since_ae, cosz_2d, &
843  hout_2d, rr_out)
844 
845 !-------------------------------------------------------------------
846 !> place output fields into 1-d arguments for return to
847 !! calling routine.
848 !-------------------------------------------------------------------
849 
850  h_out = hout_2d(:,1)
851  cosz = cosz_2d(:,1)
852 
853 end subroutine daily_mean_solar_1d_
854 
855 
856 !> @brief daily_mean_solar_2level takes 1-d input fields, adds a second
857 !! dimension and calls daily_mean_solar_2d. on return, the 2d fields
858 !! are returned to the original 1d fields.
859 !!
860 !! @param [in] <lat> Latitudes of model grid points
861 !! @param [in] <time_since_ae> Time of year; autumnal equinox = 0.0, one year = 2 * pi
862 !! @param [out] <cosz> Cosine of solar zenith angle
863 !! @param [out] <solar> Shortwave flux factor: cosine of zenith angle * daylight fraction /
864 !! (earth-sun distance squared)
865 
866 subroutine daily_mean_solar_2level_(lat, time_since_ae, cosz, solar)
867 
868 !----------------------------------------------------------------------
869 real(kind=fms_ast_kind_), intent(in), dimension(:) :: lat
870 real(kind=fms_ast_kind_), intent(in) :: time_since_ae
871 real(kind=fms_ast_kind_), intent(out), dimension(size(lat(:))) :: cosz, solar
872 
873 !----------------------------------------------------------------------
874 
875 !----------------------------------------------------------------------
876 ! local variables
877 !----------------------------------------------------------------------
878 
879 real(kind=fms_ast_kind_), dimension(size(lat),1) :: lat_2d, cosz_2d, hout_2d
880 real(kind=fms_ast_kind_) :: rr_out
881 
882 !--------------------------------------------------------------------
883 !> define 2-d versions of input data array.
884 !--------------------------------------------------------------------
885 
886  lat_2d(:,1) = lat
887 
888 !--------------------------------------------------------------------
889 !> call daily_mean_solar_2d to calculate astronomy fields.
890 !--------------------------------------------------------------------
891 
892  call daily_mean_solar(lat_2d, time_since_ae, cosz_2d, &
893  hout_2d, rr_out)
894 
895 !-------------------------------------------------------------------
896 !> place output fields into 1-d arguments for return to
897 !! calling routine.
898 !-------------------------------------------------------------------
899 
900  solar = cosz_2d(:,1)*hout_2d(:,1)*rr_out
901  cosz = cosz_2d(:,1)
902 
903 end subroutine daily_mean_solar_2level_
904 
905 
906 !> @brief daily_mean_solar_1d takes 1-d input fields, adds a second dimension
907 !! and calls daily_mean_solar_2d. on return, the 2d fields are
908 !! returned to the original 1d fields.
909 !!
910 !! @param [in] <lat> Latitudes of model grid points
911 !! @param [in] <time_since_ae> Time of year; autumnal equinox = 0.0, one year = 2 * pi
912 !! @param [out] <cosz> Cosine of solar zenith angle
913 !! @param [out] <h_out> 2-d array of half-day lengths at the latitudes
914 !! @param [out] <rr_out> the inverse of the square of the earth-sun distance relative to
915 !! the mean distance at angle ang in the earth's orbit.
916 
917 subroutine daily_mean_solar_0d_(lat, time_since_ae, cosz, h_out, rr_out)
918 
919 real(kind=fms_ast_kind_), intent(in) :: lat, time_since_ae
920 real(kind=fms_ast_kind_), intent(out) :: cosz, h_out, rr_out
921 
922 !--------------------------------------------------------------------
923 ! local variables
924 !--------------------------------------------------------------------
925 
926 real(kind=fms_ast_kind_), dimension(1,1) :: lat_2d, cosz_2d, hout_2d
927 
928 !--------------------------------------------------------------------
929 !> define 2-d versions of input data array.
930 !--------------------------------------------------------------------
931 
932  lat_2d = lat
933 
934 !--------------------------------------------------------------------
935 !> call daily_mean_solar_2d to calculate astronomy fields.
936 !--------------------------------------------------------------------
937 
938  call daily_mean_solar(lat_2d, time_since_ae, cosz_2d, &
939  hout_2d, rr_out)
940 
941 !-------------------------------------------------------------------
942 !> return output fields to scalars for return to calling routine.
943 !-------------------------------------------------------------------
944 
945  h_out = hout_2d(1,1)
946  cosz = cosz_2d(1,1)
947 
948 end subroutine daily_mean_solar_0d_
949 
950 
951 !> @brief daily_mean_solar_cal_2d receives time_type inputs, converts
952 !! them to real variables and then calls daily_mean_solar_2d to
953 !! compute desired astronomical variables.
954 !!
955 !! @param [in] <lat> Latitudes of model grid points
956 !! @param [in] <time> Time of year (time_type)
957 !! @param [out] <cosz> Cosine of solar zenith angle
958 !! @param [out] <fracday> Daylight fraction of time interval
959 !! @param [out] <rrsun> Earth-Sun distance (r) relative to semi-major axis of orbital ellipse (a):(a/r)**2
960 !!
961 !! @throw FATAL, "astronomy_mod time_since_ae not between 0 and 2pi"
962 
963 subroutine daily_mean_solar_cal_2d_(lat, time, cosz, fracday, rrsun)
964 
965 !-------------------------------------------------------------------
966 real(kind=fms_ast_kind_), dimension(:,:), intent(in) :: lat
967 type(time_type), intent(in) :: time
968 real(kind=fms_ast_kind_), dimension(:,:), intent(out) :: cosz, fracday
969 real(kind=fms_ast_kind_), intent(out) :: rrsun
970 !-------------------------------------------------------------------
971 
972 !-------------------------------------------------------------------
973 ! local variables
974 !-------------------------------------------------------------------
975 
976 real(kind=fms_ast_kind_) :: time_since_ae
977 integer, parameter :: lkind = fms_ast_kind_
978 
979 !--------------------------------------------------------------------
980 ! be sure the time in the annual cycle is legitimate.
981 !---------------------------------------------------------------------
982 
983  time_since_ae = real(orbital_time(time), fms_ast_kind_)
984  if (time_since_ae < 0.0_lkind .or. time_since_ae > real(twopi, fms_ast_kind_)) &
985  call error_mesg('astronomy_mod', 'time_since_ae not between 0 and 2pi', fatal)
986 
987 !--------------------------------------------------------------------
988 ! call daily_mean_solar_2d to calculate astronomy fields.
989 !--------------------------------------------------------------------
990 
991  call daily_mean_solar(lat, time_since_ae, cosz, fracday, rrsun)
992 
993 end subroutine daily_mean_solar_cal_2d_
994 
995 
996 !> @brief daily_mean_solar_cal_1d receives time_type inputs, converts
997 !! them to real, 2d variables and then calls daily_mean_solar_2d to
998 !! compute desired astronomical variables.
999 !!
1000 !! @param [in] <lat> Latitudes of model grid points
1001 !! @param [in] <time> Time of year (time_type)
1002 !! @param [out] <cosz> Cosine of solar zenith angle
1003 !! @param [out] <fracday> Daylight fraction of time interval
1004 !! @param [out] <rrsun> Earth-Sun distance (r) relative to semi-major axis of orbital ellipse (a):(a/r)**2
1005 
1006 subroutine daily_mean_solar_cal_1d_(lat, time, cosz, fracday, rrsun)
1007 
1008 real(kind=fms_ast_kind_), dimension(:), intent(in) :: lat
1009 type(time_type), intent(in) :: time
1010 real(kind=fms_ast_kind_), dimension(:), intent(out) :: cosz, fracday
1011 real(kind=fms_ast_kind_), intent(out) :: rrsun
1012 
1013 !---------------------------------------------------------------------
1014 ! local variables
1015 !---------------------------------------------------------------------
1016 
1017 real(kind=fms_ast_kind_), dimension(size(lat),1) :: lat_2d, cosz_2d, fracday_2d
1018 
1019 !--------------------------------------------------------------------
1020 !> define 2-d versions of input data array.
1021 !--------------------------------------------------------------------
1022 
1023  lat_2d(:,1) = lat
1024 
1025 !--------------------------------------------------------------------
1026 !> call daily_mean_solar_cal_2d to convert the time_types to reals and
1027 !! then calculate the astronomy fields.
1028 !--------------------------------------------------------------------
1029 
1030  call daily_mean_solar(lat_2d, time, cosz_2d, fracday_2d, rrsun)
1031 
1032 !-------------------------------------------------------------------
1033 !> place output fields into 1-d arguments for return to
1034 !! calling routine.
1035 !-------------------------------------------------------------------
1036 
1037  fracday = fracday_2d(:,1)
1038  cosz = cosz_2d(:,1)
1039 
1040 end subroutine daily_mean_solar_cal_1d_
1041 
1042 
1043 !> @brief daily_mean_solar_cal_2level receives 1d arrays and time_type input,
1044 !! converts them to real, 2d variables and then calls
1045 !! daily_mean_solar_2d to compute desired astronomical variables.
1046 !!
1047 !! @param [in] <lat> Latitudes of model grid points
1048 !! @param [in] <time> Time of year (time_type)
1049 !! @param [out] <cosz> Cosine of solar zenith angle
1050 !! @param [out] <solar> Shortwave flux factor: cosine of zenith angle * daylight fraction /
1051 !! (earth-sun distance squared)
1052 
1053 subroutine daily_mean_solar_cal_2level_(lat, time, cosz, solar)
1054 
1055 real(kind=fms_ast_kind_), dimension(:), intent(in) :: lat
1056 type(time_type), intent(in) :: time
1057 real(kind=fms_ast_kind_), dimension(:), intent(out) :: cosz, solar
1058 !---------------------------------------------------------------------
1059 ! local variables
1060 !---------------------------------------------------------------------
1061 
1062 real(kind=fms_ast_kind_), dimension(size(lat),1) :: lat_2d, cosz_2d, fracday_2d
1063 real(kind=fms_ast_kind_) :: rrsun
1064 
1065 
1066 !--------------------------------------------------------------------
1067 !> define 2-d versions of input data array.
1068 !--------------------------------------------------------------------
1069 
1070  lat_2d(:,1) = lat
1071 
1072 !--------------------------------------------------------------------
1073 !> call daily_mean_solar_cal_2d to convert the time_types to reals and
1074 !! then calculate the astronomy fields.
1075 !--------------------------------------------------------------------
1076 
1077  call daily_mean_solar(lat_2d, time, cosz_2d, fracday_2d, rrsun)
1078 
1079 !-------------------------------------------------------------------
1080 !> place output fields into 1-d arguments for return to
1081 !! calling routine.
1082 !-------------------------------------------------------------------
1083 
1084  solar = cosz_2d(:,1)*fracday_2d(:,1)*rrsun
1085  cosz = cosz_2d(:,1)
1086 
1087 end subroutine daily_mean_solar_cal_2level_
1088 
1089 
1090 !> @brief daily_mean_solar_cal_0d converts scalar input fields to real, 2d variables and
1091 !! then calls daily_mean_solar_2d to compute desired astronomical variables.
1092 !!
1093 !! @param [in] <lat> Latitudes of model grid points
1094 !! @param [in] <time> Time of year (time_type)
1095 !! @param [out] <cosz> Cosine of solar zenith angle
1096 !! @param [out] <fracday> Daylight fraction of time interval
1097 !! @param [out] <rrsun> Earth-Sun distance (r) relative to semi-major axis of orbital ellipse (a):(a/r)**2
1098 
1099 subroutine daily_mean_solar_cal_0d_(lat, time, cosz, fracday, rrsun)
1100 
1101 !--------------------------------------------------------------------
1102 real(kind=fms_ast_kind_), intent(in) :: lat
1103 type(time_type), intent(in) :: time
1104 real(kind=fms_ast_kind_), intent(out) :: cosz, fracday, rrsun
1105 !--------------------------------------------------------------------
1106 
1107 !--------------------------------------------------------------------
1108 ! local variables
1109 !--------------------------------------------------------------------
1110 
1111 real(kind=fms_ast_kind_), dimension(1,1) :: lat_2d, cosz_2d, fracday_2d
1112 
1113 !--------------------------------------------------------------------
1114 !> define 2-d versions of input data array.
1115 !--------------------------------------------------------------------
1116 
1117  lat_2d = lat
1118 
1119 !--------------------------------------------------------------------
1120 !> call daily_mean_solar_cal_2d to convert the time_types to reals and
1121 !! then calculate the astronomy fields.
1122 !--------------------------------------------------------------------
1123 
1124  call daily_mean_solar(lat_2d, time, cosz_2d, fracday_2d, rrsun)
1125 
1126 !-------------------------------------------------------------------
1127 !> place output fields into scalar arguments for return to
1128 !! calling routine.
1129 !-------------------------------------------------------------------
1130 
1131  fracday = fracday_2d(1,1)
1132  cosz = cosz_2d(1,1)
1133 
1134 end subroutine daily_mean_solar_cal_0d_
1135 
1136 
1137 !> @brief annual_mean_solar_2d returns 2d fields of annual mean values of the cosine of
1138 !! zenith angle, daylight fraction and earth-sun distance at the specified latitude.
1139 !!
1140 !! @param [in] <jst> Starting index of latitude window
1141 !! @param [in] <jnd> Ending index of latitude window
1142 !! @param [in] <lat> Latitudes of model grid points
1143 !! @param [out] <cosz> Cosine of solar zenith angle
1144 !! @param [out] <solar> Shortwave flux factor: cosine of zenith angle * daylight fraction /
1145 !! (earth-sun distance squared)
1146 !! @param [out] <fracday> Daylight fraction of time interval
1147 !! @param [out] <rrsun> Earth-Sun distance (r) relative to semi-major axis of orbital ellipse (a):(a/r)**2
1148 
1149 subroutine annual_mean_solar_2d_(js, je, lat, cosz, solar, fracday, &
1150  rrsun)
1151 
1152 !--------------------------------------------------------------------
1153 integer, intent(in) :: js, je
1154 real(kind=fms_ast_kind_), dimension(:,:), intent(in) :: lat
1155 real(kind=fms_ast_kind_), dimension(:,:), intent(out) :: solar, cosz, fracday
1156 real(kind=fms_ast_kind_), intent(out) :: rrsun
1157 !--------------------------------------------------------------------
1158 
1159 !--------------------------------------------------------------------
1160 ! local variables
1161 !--------------------------------------------------------------------
1162 
1163 real(kind=fms_ast_kind_), dimension(size(lat,1),size(lat,2)) :: s,z
1164 real(kind=fms_ast_kind_) :: t
1165 integer :: n
1166 integer, parameter :: lkind = fms_ast_kind_
1167 
1168 !--------------------------------------------------------------------
1169 ! if the calculation has not yet been done, do it here.
1170 !--------------------------------------------------------------------
1171 
1172  if (.not. annual_mean_calculated) then
1173 
1174 !----------------------------------------------------------------------
1175 !> determine annual mean values of solar flux and product of cosz
1176 !! and solar flux by integrating the annual cycle in num_angles
1177 !! orbital increments.
1178 !----------------------------------------------------------------------
1179 
1180  solar = 0.0_lkind
1181  cosz = 0.0_lkind
1182  do n =1, num_angles
1183  t = real((n-1), fms_ast_kind_)*real(twopi, fms_ast_kind_)/real(num_angles, fms_ast_kind_)
1184  call daily_mean_solar(lat,t, z, fracday, rrsun)
1185  s = z*rrsun*fracday
1186  solar = solar + s
1187  cosz = cosz + z*s
1188  end do
1189  solar = solar/real(num_angles, fms_ast_kind_)
1190  cosz = cosz/real(num_angles, fms_ast_kind_)
1191 
1192 !--------------------------------------------------------------------
1193 !> define the flux-weighted annual mean cosine of the zenith angle.
1194 !--------------------------------------------------------------------
1195 
1196  where(solar .eq. 0.0_lkind)
1197  cosz = 0.0_lkind
1198  elsewhere
1199  cosz = cosz/solar
1200  end where
1201 
1202 !-------------------------------------------------------------------
1203 !> define avg fracday such as to make the avg flux (solar) equal to
1204 !! the product of the avg cosz * avg fracday * assumed mean avg
1205 !! radius of 1.0. it is unlikely that these avg fracday and avg rr
1206 !! will ever be used.
1207 !--------------------------------------------------------------------
1208 
1209  where(solar .eq. 0.0_lkind)
1210  fracday = 0.0_lkind
1211  elsewhere
1212  fracday = solar/cosz
1213  end where
1214  rrsun = 1.00_lkind
1215 
1216 !---------------------------------------------------------------------
1217 !> save the values that have been calculated as module variables, if
1218 !! those variables are present; i.e., not the spectral 2-layer model.
1219 !---------------------------------------------------------------------
1220  if (allocated (cosz_ann)) then
1221 
1222  cosz_ann = real(cosz, r8_kind)
1223  solar_ann = real(solar, r8_kind)
1224  fracday_ann = real(fracday, r8_kind)
1225  rrsun_ann = real(rrsun, r8_kind)
1226 
1227 !--------------------------------------------------------------------
1228 !> increment the points computed counter. set flag to end execution
1229 !! once values have been calculated for all points owned by the
1230 !! processor.
1231 !--------------------------------------------------------------------
1232  num_pts = num_pts + size(lat,1)*size(lat,2)
1233  if ( num_pts == total_pts) annual_mean_calculated = .true.
1234  endif
1235 
1236 !--------------------------------------------------------------------
1237 !> if the calculation has been done, return the appropriate module
1238 !! variables.
1239 !--------------------------------------------------------------------
1240  else
1241  if (allocated (cosz_ann)) then
1242 
1243  cosz = real(cosz_ann, fms_ast_kind_)
1244  solar = real(solar_ann, fms_ast_kind_)
1245  fracday = real(fracday_ann, fms_ast_kind_)
1246  rrsun = real(rrsun_ann, fms_ast_kind_)
1247  endif
1248  endif
1249 
1250 end subroutine annual_mean_solar_2d_
1251 
1252 
1253 !> @brief annual_mean_solar_1d creates 2-d input fields from 1-d input fields and then calls
1254 !! annual_mean_solar_2d to obtain 2-d output fields which are then stored into 1-d
1255 !! fields for return to the calling subroutine.
1256 !!
1257 !! @param [in] <jst> Starting index of latitude window
1258 !! @param [in] <jnd> Ending index of latitude window
1259 !! @param [in] <lat> Latitudes of model grid points
1260 !! @param [out] <cosz> Cosine of solar zenith angle
1261 !! @param [out] <solar> Shortwave flux factor: cosine of zenith angle * daylight fraction /
1262 !! (earth-sun distance squared)
1263 !! @param [out] <fracday> Daylight fraction of time interval
1264 !! @param [out] <rrsun_out> Earth-Sun distance (r) relative to semi-major axis of orbital ellipse (a):(a/r)**2
1265 
1266 subroutine annual_mean_solar_1d_(jst, jnd, lat, cosz, solar, &
1267  fracday, rrsun_out)
1268 
1269 !---------------------------------------------------------------------
1270 integer, intent(in) :: jst, jnd
1271 real(kind=fms_ast_kind_), dimension(:), intent(in) :: lat(:)
1272 real(kind=fms_ast_kind_), dimension(:), intent(out) :: cosz, solar, fracday
1273 real(kind=fms_ast_kind_), intent(out) :: rrsun_out
1274 !---------------------------------------------------------------------
1275 
1276 !---------------------------------------------------------------------
1277 ! local variables
1278 
1279 
1280 real(kind=fms_ast_kind_), dimension(size(lat),1) :: lat_2d, solar_2d, cosz_2d, fracday_2d
1281 real(kind=fms_ast_kind_) :: rrsun
1282 
1283 !--------------------------------------------------------------------
1284 ! if the calculation has not been done, do it here.
1285 !--------------------------------------------------------------------
1286 
1287  if ( .not. annual_mean_calculated) then
1288 
1289 !--------------------------------------------------------------------
1290 !> define 2-d versions of input data array.
1291 !--------------------------------------------------------------------
1292 
1293  lat_2d(:,1) = lat
1294 
1295 !--------------------------------------------------------------------
1296 !> call annual_mean_solar_2d to calculate the astronomy fields.
1297 !--------------------------------------------------------------------
1298 
1299  call annual_mean_solar(jst, jnd, lat_2d, cosz_2d, solar_2d, fracday_2d, rrsun)
1300 
1301 !-------------------------------------------------------------------
1302 !> place output fields into 1-D arrays for return to calling routine.
1303 !-------------------------------------------------------------------
1304 
1305  fracday = fracday_2d(:,1)
1306  rrsun_out = rrsun
1307  solar = solar_2d(:,1)
1308  cosz = cosz_2d(:,1)
1309 
1310 !--------------------------------------------------------------------
1311 !> if the calculation has been done, simply return the module
1312 !! variables contain the results at the desired latitudes.
1313 !--------------------------------------------------------------------
1314 
1315  else
1316  cosz(:) = real(cosz_ann(1,jst:jnd), fms_ast_kind_)
1317  solar(:) = real(solar_ann(1,jst:jnd), fms_ast_kind_)
1318  fracday(:) = real(fracday_ann(1,jst:jnd), fms_ast_kind_)
1319  rrsun = real(rrsun_ann, fms_ast_kind_)
1320  endif
1321 
1322 end subroutine annual_mean_solar_1d_
1323 
1324 
1325 !> @brief annual_mean_solar_2level creates 2-d input fields from 1-d input fields
1326 !! and then calls annual_mean_solar_2d to obtain 2-d output fields which are
1327 !! then stored into 1-d fields for return to the calling subroutine. This
1328 !! subroutine will be called during model initialization.
1329 !!
1330 !! @throw FATAL, "astronomy_mod annual_mean_solar_2level should be called only once"
1331 
1332 subroutine annual_mean_solar_2level_(lat, cosz, solar)
1333 
1334 !---------------------------------------------------------------------
1335 real(kind=fms_ast_kind_), dimension(:), intent(in) :: lat !< Latitudes of model grid points
1336 real(kind=fms_ast_kind_), dimension(:), intent(out) :: cosz !< Cosine of solar zenith angle
1337 real(kind=fms_ast_kind_), dimension(:), intent(out) :: solar !< shortwave flux factor: cosine of zenith angle *
1338  !! daylight fraction / (earth-sun distance squared)
1339 !---------------------------------------------------------------------
1340 
1341 !---------------------------------------------------------------------
1342 ! local variables
1343 
1344 
1345 real(kind=fms_ast_kind_), dimension(size(lat),1) :: lat_2d, solar_2d, cosz_2d, fracday_2d
1346 integer :: jst, jnd
1347 real(kind=fms_ast_kind_) :: rrsun
1348 
1349 !--------------------------------------------------------------------
1350 ! if the calculation has not been done, do it here.
1351 !--------------------------------------------------------------------
1352 
1353  if ( .not. annual_mean_calculated) then
1354 
1355 !--------------------------------------------------------------------
1356 !> define 2-d versions of input data array.
1357 !--------------------------------------------------------------------
1358 
1359  lat_2d(:,1) = lat
1360  jst = 1
1361  jnd = size(lat(:))
1362 
1363 !--------------------------------------------------------------------
1364 !> call annual_mean_solar_2d to calculate the astronomy fields.
1365 !--------------------------------------------------------------------
1366 
1367  call annual_mean_solar(jst, jnd, lat_2d, cosz_2d, solar_2d, fracday_2d, rrsun)
1368 
1369 !-------------------------------------------------------------------
1370 !> place output fields into 1-D arrays for return to calling routine.
1371 !-------------------------------------------------------------------
1372 
1373  solar = solar_2d(:,1)
1374  cosz = cosz_2d(:,1)
1375 
1376 !--------------------------------------------------------------------
1377 !> if the calculation has been done, print an error message since
1378 !! this subroutine should be called only once.
1379 !--------------------------------------------------------------------
1380 
1381  else
1382  call error_mesg('astronomy_mod', 'annual_mean_solar_2level should be called only once', fatal)
1383  endif
1384  annual_mean_calculated = .true.
1385 
1386 end subroutine annual_mean_solar_2level_
1387 
1388 
1389 !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1390 !
1391 ! PRIVATE SUBROUTINES
1392 !
1393 !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1394 
1395 
1396 
1397 !> @brief r_inv_squared returns the inverse of the square of the earth-sun
1398 !! distance relative to the mean distance at angle ang in the Earth's orbit.
1399 function r_inv_squared_(ang)
1400 
1401 !--------------------------------------------------------------------
1402 real(kind=fms_ast_kind_), intent(in) :: ang !< angular position of earth in its orbit, relative to a
1403  !! value of 0.0 at the NH autumnal equinox, value between
1404  !! 0.0 and 2 * pi [radians]
1405 !--------------------------------------------------------------------
1406 
1407 !---------------------------------------------------------------------
1408 ! local variables
1409 
1410 
1411 real(kind=fms_ast_kind_) :: r_inv_squared_ !< The inverse of the square of the earth-sun distance relative
1412  !! to the mean distance [dimensionless]
1413 real(kind=fms_ast_kind_) :: r !< Earth-Sun distance relative to mean distance [dimensionless]
1414 real(kind=fms_ast_kind_) :: rad_per !< Angular position of perihelion [radians]
1415 integer, parameter :: lkind = fms_ast_kind_
1416 
1417 !--------------------------------------------------------------------
1418 !> define the earth-sun distance (r) and then return the inverse of
1419 !! its square (r_inv_squared) to the calling routine.
1420 !--------------------------------------------------------------------
1421 
1422  rad_per = real(per, fms_ast_kind_)*real(deg_to_rad, fms_ast_kind_)
1423  r = (1.0_lkind - real(ecc, fms_ast_kind_)**2)/(1.0_lkind &
1424  + real(ecc, fms_ast_kind_)*cos(ang - rad_per))
1425  r_inv_squared_ = r**(-2)
1426 
1427 
1428 end function r_inv_squared_
1429 
1430 
1431 !> @brief angle determines the position within the earth's orbit at time t
1432 !! in the year (t = 0 at NH autumnal equinox) by interpolating
1433 !! into the orbital position table.
1434 
1435 function angle_(t)
1436 
1437 !--------------------------------------------------------------------
1438 real(kind=fms_ast_kind_), intent(in) :: t !< time of year (between 0 and 2*pi; t=0 at NH autumnal equinox
1439 !--------------------------------------------------------------------
1440 
1441 !--------------------------------------------------------------------
1442 ! local variables
1443 !--------------------------------------------------------------------
1444 
1445 real(kind=fms_ast_kind_) :: angle_ !< Orbital position relative to NH autumnal equinox [radians]
1446 real(kind=fms_ast_kind_) :: norm_time !< Index into orbital table corresponding to input time [dimensionless]
1447 real(kind=fms_ast_kind_) :: x !< Fractional distance between the orbital table entries bracketing
1448  !! the input time [dimensionless]
1449 integer :: int !< Table index which is lower than actual position, but closest to it [dimensionless]
1450 integer :: int_1 !< Next table index just larger than actual orbital position [dimensionless]
1451 integer, parameter :: lkind = fms_ast_kind_
1452 
1453 !--------------------------------------------------------------------
1454 !> Define orbital tables indices bracketing current orbital time
1455 !! (int and int_1). Define table index distance between the lower
1456 !! table value (int) and the actual orbital time (x). Define orbital
1457 !! position as being x of the way between int and int_1. Renormalize
1458 !! angle to be within the range 0 to 2*pi.
1459 !--------------------------------------------------------------------
1460 
1461  norm_time = t * real(num_angles, fms_ast_kind_)/real(twopi, fms_ast_kind_)
1462  int = floor(norm_time)
1463  int = modulo(int,num_angles)
1464  int_1 = int+1
1465  x = norm_time - real(floor(norm_time), fms_ast_kind_)
1466  angle_ = (1.0_lkind - x) * real(orb_angle(int), fms_ast_kind_) &
1467  + x * real(orb_angle(int_1), fms_ast_kind_)
1468  angle_ = modulo(angle_, real(twopi, fms_ast_kind_))
1469 
1470 end function angle_
1471 
1472 
1473 !> @brief Declination returns the solar declination angle at orbital
1474 !! position ang in earth's orbit.
1475 
1476 function declination_(ang)
1477 
1478 !--------------------------------------------------------------------
1479 real(kind=fms_ast_kind_), intent(in) :: ang !< solar orbital position ang in earth's orbit
1480 
1481 !--------------------------------------------------------------------
1482 
1483 !--------------------------------------------------------------------
1484 ! local variables
1485 
1486 
1487 real(kind=fms_ast_kind_) :: declination_ !< Solar declination angle [radians]
1488 real(kind=fms_ast_kind_) :: rad_obliq !< Obliquity of the ecliptic [radians]
1489 real(kind=fms_ast_kind_) :: sin_dec !< Sine of the solar declination [dimensionless]
1490 
1491 !---------------------------------------------------------------------
1492 ! compute the solar declination.
1493 !---------------------------------------------------------------------
1494 
1495  rad_obliq = real(obliq, fms_ast_kind_)*real(deg_to_rad, fms_ast_kind_)
1496  sin_dec = - sin(rad_obliq)*sin(ang)
1497  declination_ = asin(sin_dec)
1498 
1499 end function declination_
1500 
1501 
1502 !> @brief half_day_2d returns a 2-d array of half-day lengths at the
1503 !! latitudes and declination provided.
1504 !!
1505 
1506 function half_day_2d_(latitude, dec) result(h)
1507 
1508 !---------------------------------------------------------------------
1509 real(kind=fms_ast_kind_), dimension(:,:), intent(in) :: latitude !< Latitutde of view point
1510 real(kind=fms_ast_kind_), intent(in) :: dec !< Solar declination angle at view point
1511 real(kind=fms_ast_kind_), dimension(size(latitude,1),size(latitude,2)) :: h
1512 !---------------------------------------------------------------------
1513 
1514 !---------------------------------------------------------------------
1515 ! local variables
1516 !---------------------------------------------------------------------
1517 
1518 real(kind=fms_ast_kind_), dimension (size(latitude,1),size(latitude,2)):: &
1519  cos_half_day, & !< Cosine of half-day length [dimensionless]
1520  lat !< Model latitude, adjusted so that it is never 0.5*pi or -0.5*pi
1521 real(kind=fms_ast_kind_) :: tan_dec !< tangent of solar declination [dimensionless]
1522 integer, parameter :: lkind = fms_ast_kind_
1523 real(kind=fms_ast_kind_) :: eps = 1.0e-05_lkind !< small increment
1524 
1525 
1526 !--------------------------------------------------------------------
1527 !> define tangent of the declination.
1528 !--------------------------------------------------------------------
1529 
1530  tan_dec = tan(dec)
1531 
1532 !--------------------------------------------------------------------
1533 !> adjust latitude so that its tangent will be defined.
1534 !--------------------------------------------------------------------
1535 
1536  lat = latitude
1537  where (latitude == 0.5_lkind*real(pi, fms_ast_kind_)) lat = latitude - eps
1538  where (latitude == -0.5_lkind*real(pi, fms_ast_kind_)) lat = latitude + eps
1539 
1540 !--------------------------------------------------------------------
1541 !> define the cosine of the half-day length. adjust for cases of
1542 !! all daylight or all night.
1543 !--------------------------------------------------------------------
1544 
1545  cos_half_day = -tan(lat)*tan_dec
1546  where (cos_half_day <= -1.0_lkind) h = real(pi, fms_ast_kind_)
1547  where (cos_half_day >= 1.0_lkind) h = 0.0_lkind
1548  where (cos_half_day > -1.0_lkind .and. &
1549  cos_half_day < 1.0_lkind) h = acos(cos_half_day)
1550 
1551 end function half_day_2d_
1552 
1553 
1554 !> @brief half_day_0d takes scalar input fields, makes them into 2-d fields
1555 !! dimensioned (1,1), and calls half_day_2d. On return, the 2-d
1556 !! fields are converted to the desired scalar output.
1557 !!
1558 !! @param [in] <latitude> Latitutde of view point
1559 !! @param [in] <dec> Solar declination angle at view point
1560 
1561 function half_day_0d_(latitude, dec) result(h)
1562 
1563 real(kind=fms_ast_kind_), intent(in) :: latitude, dec
1564 real(kind=fms_ast_kind_) :: h
1565 
1566 !----------------------------------------------------------------------
1567 ! local variables
1568 !----------------------------------------------------------------------
1569 
1570 real(kind=fms_ast_kind_), dimension(1,1) :: lat_2d, h_2d
1571 
1572 !---------------------------------------------------------------------
1573 ! create 2d array from the input latitude field.
1574 !---------------------------------------------------------------------
1575 
1576  lat_2d = latitude
1577 
1578 !---------------------------------------------------------------------
1579 ! call half_day with the 2d arguments to calculate half-day length.
1580 !---------------------------------------------------------------------
1581 
1582  h_2d = half_day(lat_2d, dec)
1583 
1584 !---------------------------------------------------------------------
1585 ! create scalar from 2d array.
1586 !---------------------------------------------------------------------
1587 
1588  h = h_2d(1,1)
1589 
1590 end function half_day_0d_
1591 
1592 
1593 !> @}
1594 ! close documentation grouping
subroutine daily_mean_solar_2d_(lat, time_since_ae, cosz, h_out, rr_out)
daily_mean_solar_2d computes the daily mean astronomical parameters for the input points at latitude ...
Definition: astronomy.inc:753
subroutine annual_mean_solar_2d_(js, je, lat, cosz, solar, fracday, rrsun)
annual_mean_solar_2d returns 2d fields of annual mean values of the cosine of zenith angle,...
Definition: astronomy.inc:1151
subroutine diurnal_solar_cal_0d_(lat, lon, time, cosz, fracday, rrsun, dt_time, allow_negative_cosz, half_day_out)
diurnal_solar_cal_0d receives time_type inputs, converts them to real variables and then calls diurna...
Definition: astronomy.inc:685
subroutine get_orbital_parameters_(ecc_out, obliq_out, per_out)
get_orbital_parameters retrieves the orbital parameters for use by another module.
Definition: astronomy.inc:90
subroutine diurnal_solar_0d_(lat, lon, gmt, time_since_ae, cosz, fracday, rrsun, dt, allow_negative_cosz, half_day_out)
diurnal_solar_0d takes scalar input fields, makes them into 2d arrays dimensioned (1,...
Definition: astronomy.inc:458
subroutine diurnal_solar_1d_(lat, lon, gmt, time_since_ae, cosz, fracday, rrsun, dt, allow_negative_cosz, half_day_out)
diurnal_solar_1d takes 1-d input fields, adds a second dimension and calls diurnal_solar_2d....
Definition: astronomy.inc:386
real(kind=fms_ast_kind_) function declination_(ang)
Declination returns the solar declination angle at orbital position ang in earth's orbit.
Definition: astronomy.inc:1477
subroutine daily_mean_solar_cal_2d_(lat, time, cosz, fracday, rrsun)
daily_mean_solar_cal_2d receives time_type inputs, converts them to real variables and then calls dai...
Definition: astronomy.inc:964
subroutine diurnal_solar_2d_(lat, lon, gmt, time_since_ae, cosz, fracday, rrsun, dt, allow_negative_cosz, half_day_out)
diurnal_solar_2d returns 2d fields of cosine of zenith angle, daylight fraction and earth-sun distanc...
Definition: astronomy.inc:144
subroutine daily_mean_solar_0d_(lat, time_since_ae, cosz, h_out, rr_out)
daily_mean_solar_1d takes 1-d input fields, adds a second dimension and calls daily_mean_solar_2d....
Definition: astronomy.inc:918
real(kind=fms_ast_kind_) function, dimension(size(latitude, 1), size(latitude, 2)) half_day_2d_(latitude, dec)
half_day_2d returns a 2-d array of half-day lengths at the latitudes and declination provided.
Definition: astronomy.inc:1507
real(kind=fms_ast_kind_) function r_inv_squared_(ang)
r_inv_squared returns the inverse of the square of the earth-sun distance relative to the mean distan...
Definition: astronomy.inc:1400
subroutine diurnal_solar_cal_1d_(lat, lon, time, cosz, fracday, rrsun, dt_time, allow_negative_cosz, half_day_out)
diurnal_solar_cal_1d receives time_type inputs, converts them to real variables and then calls diurna...
Definition: astronomy.inc:612
subroutine set_orbital_parameters_(ecc_in, obliq_in, per_in)
set_orbital_parameters saves the input values of eccentricity, obliquity and perihelion time as modul...
Definition: astronomy.inc:39
subroutine daily_mean_solar_cal_0d_(lat, time, cosz, fracday, rrsun)
daily_mean_solar_cal_0d converts scalar input fields to real, 2d variables and then calls daily_mean_...
Definition: astronomy.inc:1100
real(kind=fms_ast_kind_) function half_day_0d_(latitude, dec)
half_day_0d takes scalar input fields, makes them into 2-d fields dimensioned (1,1),...
Definition: astronomy.inc:1562
real(kind=fms_ast_kind_) function angle_(t)
angle determines the position within the earth's orbit at time t in the year (t = 0 at NH autumnal eq...
Definition: astronomy.inc:1436
subroutine daily_mean_solar_2level_(lat, time_since_ae, cosz, solar)
daily_mean_solar_2level takes 1-d input fields, adds a second dimension and calls daily_mean_solar_2d...
Definition: astronomy.inc:867
subroutine annual_mean_solar_1d_(jst, jnd, lat, cosz, solar, fracday, rrsun_out)
annual_mean_solar_1d creates 2-d input fields from 1-d input fields and then calls annual_mean_solar_...
Definition: astronomy.inc:1268
subroutine daily_mean_solar_cal_2level_(lat, time, cosz, solar)
daily_mean_solar_cal_2level receives 1d arrays and time_type input, converts them to real,...
Definition: astronomy.inc:1054
subroutine annual_mean_solar_2level_(lat, cosz, solar)
annual_mean_solar_2level creates 2-d input fields from 1-d input fields and then calls annual_mean_so...
Definition: astronomy.inc:1333
subroutine daily_mean_solar_1d_(lat, time_since_ae, cosz, h_out, rr_out)
daily_mean_solar_1d takes 1-d input fields, adds a second dimension and calls daily_mean_solar_2d....
Definition: astronomy.inc:816
subroutine diurnal_solar_cal_2d_(lat, lon, time, cosz, fracday, rrsun, dt_time, allow_negative_cosz, half_day_out)
diurnal_solar_cal_2d receives time_type inputs, converts them to real variables and then calls diurna...
Definition: astronomy.inc:526
subroutine daily_mean_solar_cal_1d_(lat, time, cosz, fracday, rrsun)
daily_mean_solar_cal_1d receives time_type inputs, converts them to real, 2d variables and then calls...
Definition: astronomy.inc:1007