40 real(kind=fms_ast_kind_),
intent(in) :: ecc_in
41 real(kind=fms_ast_kind_),
intent(in) :: obliq_in
42 real(kind=fms_ast_kind_),
intent(in) :: per_in
45 integer,
parameter :: lkind = fms_ast_kind_
50 if (.not. module_is_initialized) &
51 call error_mesg(
'astronomy_mod',
'module has not been initialized', fatal)
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)
69 ecc = real(ecc_in, r8_kind)
70 obliq = real(obliq_in, r8_kind)
71 per = real(per_in, r8_kind)
97 real(kind=fms_ast_kind_),
intent(out) :: ecc_out
98 real(kind=fms_ast_kind_),
intent(out) :: obliq_out
99 real(kind=fms_ast_kind_),
intent(out) :: per_out
106 if (.not. module_is_initialized) &
107 call error_mesg(
'astronomy_mod',
'module has not been initialized', fatal)
114 ecc_out = real(ecc, fms_ast_kind_)
115 obliq_out = real(obliq, fms_ast_kind_)
116 per_out = real(per, fms_ast_kind_)
142 fracday, rrsun, dt, allow_negative_cosz, &
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
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_
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)
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)
201 ang = angle(time_since_ae)
202 dec = declination(ang)
203 rrsun = r_inv_squared(ang)
209 aa = sin(lat)*sin(dec)
210 bb = cos(lat)*cos(dec)
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_)
220 lallow_negative = .false.
221 if (
present(allow_negative_cosz))
then
222 if (allow_negative_cosz) lallow_negative = .true.
231 h = half_day(lat,dec)
233 if (
present(half_day_out) )
then
237 if (
present(dt) )
then
244 if (.not. lallow_negative)
then
249 where (t < -h .and. tt < -h) cosz = 0.0_lkind
256 where ( (tt+h) /= 0.0_lkind .and. t < -h .and. abs(tt) <= h) &
257 cosz = aa + bb*(stt + sh)/ (tt + h)
266 where (t < -h .and. h /= 0.0_lkind .and. h < tt) &
267 cosz = aa + bb*( sh + sh)/(h+h)
272 where ( abs(t) <= h .and. abs(tt) <= h) &
274 cosz = aa + bb*(stt - st)/ (tt - t)
281 where ((h-t) /= 0.0_lkind .and. abs(t) <= h .and. h < tt) &
282 cosz = aa + bb*(sh - st)/(h-t)
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_)))
300 where(h < t .and. real(twopi, fms_ast_kind_) - h >= tt) &
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_))
315 cosz = aa + bb*(stt - st)/ (tt - t)
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
337 if (.not. lallow_negative)
then
339 cosz = aa + bb*cos(t)
346 cosz = aa + bb*cos(t)
360 if (.not. lallow_negative)
then
361 cosz = max(0.0_lkind, cosz)
384 fracday, rrsun, dt, allow_negative_cosz, &
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
401 real(kind=fms_ast_kind_),
dimension(size(lat),1) :: lat_2d, lon_2d, cosz_2d, fracday_2d, halfday_2d
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)
429 fracday = fracday_2d(:,1)
431 if (
present(half_day_out))
then
432 half_day_out = halfday_2d(:,1)
456 fracday, rrsun, dt, allow_negative_cosz, &
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
469 real(kind=fms_ast_kind_),
dimension(1,1) :: lat_2d, lon_2d, cosz_2d, fracday_2d, halfday_2d
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)
495 fracday = fracday_2d(1,1)
497 if (
present(half_day_out))
then
498 half_day_out = halfday_2d(1,1)
524 rrsun, dt_time, allow_negative_cosz, &
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
543 real(kind=fms_ast_kind_) :: dt
544 real(kind=fms_ast_kind_) :: gmt, time_since_ae
545 integer,
parameter :: lkind = fms_ast_kind_
552 gmt = real(universal_time(time), fms_ast_kind_)
559 time_since_ae = real(orbital_time(time), fms_ast_kind_)
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)
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)
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)
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)
610 rrsun, dt_time, allow_negative_cosz, &
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
628 real(kind=fms_ast_kind_),
dimension(size(lat),1) :: lat_2d, lon_2d, cosz_2d, &
629 fracday_2d, halfday_2d
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)
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)
659 fracday = fracday_2d(:,1)
661 if (
present(half_day_out))
then
662 half_day_out = halfday_2d(:,1)
683 rrsun, dt_time, allow_negative_cosz, &
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
701 real(kind=fms_ast_kind_),
dimension(1,1) :: lat_2d, lon_2d, cosz_2d, fracday_2d, halfday_2d
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)
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)
731 fracday = fracday_2d(1,1)
733 if (
present(half_day_out))
then
734 half_day_out = halfday_2d(1,1)
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
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_
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)
782 ang = angle(time_since_ae)
783 dec = declination(ang)
784 h = half_day(lat, dec)
785 rr = r_inv_squared(ang)
793 where (h == 0.0_lkind)
796 cosz = sin(lat)*sin(dec) + cos(lat)*cos(dec)*sin(h)/h
798 h_out = h/real(pi, fms_ast_kind_)
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
830 real(kind=fms_ast_kind_),
dimension(size(lat),1) :: lat_2d, cosz_2d, hout_2d
842 call daily_mean_solar(lat_2d, time_since_ae, cosz_2d, &
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
879 real(kind=fms_ast_kind_),
dimension(size(lat),1) :: lat_2d, cosz_2d, hout_2d
880 real(kind=fms_ast_kind_) :: rr_out
892 call daily_mean_solar(lat_2d, time_since_ae, cosz_2d, &
900 solar = cosz_2d(:,1)*hout_2d(:,1)*rr_out
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
926 real(kind=fms_ast_kind_),
dimension(1,1) :: lat_2d, cosz_2d, hout_2d
938 call daily_mean_solar(lat_2d, time_since_ae, cosz_2d, &
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
976 real(kind=fms_ast_kind_) :: time_since_ae
977 integer,
parameter :: lkind = fms_ast_kind_
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)
991 call daily_mean_solar(lat, time_since_ae, cosz, fracday, rrsun)
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
1017 real(kind=fms_ast_kind_),
dimension(size(lat),1) :: lat_2d, cosz_2d, fracday_2d
1030 call daily_mean_solar(lat_2d, time, cosz_2d, fracday_2d, rrsun)
1037 fracday = fracday_2d(:,1)
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
1062 real(kind=fms_ast_kind_),
dimension(size(lat),1) :: lat_2d, cosz_2d, fracday_2d
1063 real(kind=fms_ast_kind_) :: rrsun
1077 call daily_mean_solar(lat_2d, time, cosz_2d, fracday_2d, rrsun)
1084 solar = cosz_2d(:,1)*fracday_2d(:,1)*rrsun
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
1111 real(kind=fms_ast_kind_),
dimension(1,1) :: lat_2d, cosz_2d, fracday_2d
1124 call daily_mean_solar(lat_2d, time, cosz_2d, fracday_2d, rrsun)
1131 fracday = fracday_2d(1,1)
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
1163 real(kind=fms_ast_kind_),
dimension(size(lat,1),size(lat,2)) :: s,z
1164 real(kind=fms_ast_kind_) :: t
1166 integer,
parameter :: lkind = fms_ast_kind_
1172 if (.not. annual_mean_calculated)
then
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)
1189 solar = solar/real(num_angles, fms_ast_kind_)
1190 cosz = cosz/real(num_angles, fms_ast_kind_)
1196 where(solar .eq. 0.0_lkind)
1209 where(solar .eq. 0.0_lkind)
1212 fracday = solar/cosz
1220 if (
allocated (cosz_ann))
then
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)
1232 num_pts = num_pts +
size(lat,1)*
size(lat,2)
1233 if ( num_pts == total_pts) annual_mean_calculated = .true.
1241 if (
allocated (cosz_ann))
then
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_)
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
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
1287 if ( .not. annual_mean_calculated)
then
1299 call annual_mean_solar(jst, jnd, lat_2d, cosz_2d, solar_2d, fracday_2d, rrsun)
1305 fracday = fracday_2d(:,1)
1307 solar = solar_2d(:,1)
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_)
1335 real(kind=fms_ast_kind_),
dimension(:),
intent(in) :: lat
1336 real(kind=fms_ast_kind_),
dimension(:),
intent(out) :: cosz
1337 real(kind=fms_ast_kind_),
dimension(:),
intent(out) :: solar
1345 real(kind=fms_ast_kind_),
dimension(size(lat),1) :: lat_2d, solar_2d, cosz_2d, fracday_2d
1347 real(kind=fms_ast_kind_) :: rrsun
1353 if ( .not. annual_mean_calculated)
then
1367 call annual_mean_solar(jst, jnd, lat_2d, cosz_2d, solar_2d, fracday_2d, rrsun)
1373 solar = solar_2d(:,1)
1382 call error_mesg(
'astronomy_mod',
'annual_mean_solar_2level should be called only once', fatal)
1384 annual_mean_calculated = .true.
1402 real(kind=fms_ast_kind_),
intent(in) :: ang
1413 real(kind=fms_ast_kind_) :: r
1414 real(kind=fms_ast_kind_) :: rad_per
1415 integer,
parameter :: lkind = fms_ast_kind_
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))
1438 real(kind=fms_ast_kind_),
intent(in) :: t
1445 real(kind=fms_ast_kind_) ::
angle_
1446 real(kind=fms_ast_kind_) :: norm_time
1447 real(kind=fms_ast_kind_) :: x
1451 integer,
parameter :: lkind = fms_ast_kind_
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)
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_)
1479 real(kind=fms_ast_kind_),
intent(in) :: ang
1488 real(kind=fms_ast_kind_) :: rad_obliq
1489 real(kind=fms_ast_kind_) :: sin_dec
1495 rad_obliq = real(obliq, fms_ast_kind_)*real(deg_to_rad, fms_ast_kind_)
1496 sin_dec = - sin(rad_obliq)*sin(ang)
1509 real(kind=fms_ast_kind_),
dimension(:,:),
intent(in) :: latitude
1510 real(kind=fms_ast_kind_),
intent(in) :: dec
1511 real(kind=fms_ast_kind_),
dimension(size(latitude,1),size(latitude,2)) :: h
1518 real(kind=fms_ast_kind_),
dimension (size(latitude,1),size(latitude,2)):: &
1521 real(kind=fms_ast_kind_) :: tan_dec
1522 integer,
parameter :: lkind = fms_ast_kind_
1523 real(kind=fms_ast_kind_) :: eps = 1.0e-05_lkind
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
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)
1563 real(kind=fms_ast_kind_),
intent(in) :: latitude, dec
1564 real(kind=fms_ast_kind_) :: h
1570 real(kind=fms_ast_kind_),
dimension(1,1) :: lat_2d, h_2d
1582 h_2d = half_day(lat_2d, dec)
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 ...
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,...
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...
subroutine get_orbital_parameters_(ecc_out, obliq_out, per_out)
get_orbital_parameters retrieves the orbital parameters for use by another module.
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,...
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....
real(kind=fms_ast_kind_) function declination_(ang)
Declination returns the solar declination angle at orbital position ang in earth's orbit.
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...
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...
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....
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.
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...
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...
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...
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_...
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),...
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...
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...
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_...
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,...
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...
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....
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...
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...