60 mpp_pe, mpp_root_pe, stdlog, &
61 file_exist, write_version_number, &
63 fatal, note, warning, close_file
68 operator(-),
operator(+), &
69 operator( // ),
operator(<)
82 #include<file_version.h> 390 real,
dimension(:,:),
allocatable :: &
391 cosz_ann, & !< annual mean cos of zenith angle
422 real,
dimension(:,:),
intent(in),
optional :: latb
423 real,
dimension(:,:),
intent(in),
optional :: lonb
428 integer :: unit, ierr, io, seconds, days, jd, id
445 #ifdef INTERNAL_FILE_NML 449 if ( file_exist(
'input.nml'))
then 450 unit = open_namelist_file( )
451 ierr=1;
do while (ierr /= 0)
452 read (unit, nml=astronomy_nml, iostat=io, end=10)
455 10
call close_file (unit)
461 call write_version_number(
"ASTRONOMY_MOD", version)
462 if (mpp_pe() == mpp_root_pe() )
then 464 write (unit, nml=astronomy_nml)
470 if (
ecc < 0.0 .or.
ecc > 0.99) &
472 'ecc must be between 0 and 0.99', fatal)
475 'obliquity must be between -90 and 90 degrees', fatal)
476 if (
per < 0.0 .or.
per > 360.0) &
478 'perihelion must be between 0 and 360 degrees', fatal)
516 if (
present(latb))
then 517 jd =
size(latb,2) - 1
518 id =
size(lonb,1) - 1
541 integer,
intent(out) :: period_out
546 integer :: seconds, days
553 ' module has not been initialized', fatal)
570 type(time_type),
intent(inout) :: period_out
577 ' module has not been initialized', fatal)
592 integer,
intent(in) :: period_in
599 ' module has not been initialized', fatal)
616 type(time_type),
intent(in) :: period_in
623 ' module has not been initialized', fatal)
644 real,
intent(in) :: ecc_in
645 real,
intent(in) :: obliq_in
646 real,
intent(in) :: per_in
654 ' module has not been initialized', fatal)
660 if (ecc_in < 0.0 .or. ecc_in > 0.99) &
662 'ecc must be between 0 and 0.99', fatal)
663 if (obliq_in < -90.0 .or.
obliq > 90.0) &
665 'obliquity must be between -90. and 90. degrees', fatal)
666 if (per_in < 0.0 .or. per_in > 360.0) &
668 'perihelion must be between 0.0 and 360. degrees', fatal)
698 real,
intent(out) :: ecc_out
699 real,
intent(out) :: obliq_out
700 real,
intent(out) :: per_out
708 ' module has not been initialized', fatal)
742 second_in,minute_in,hour_in)
744 integer,
intent(in) :: day_in, month_in, year_in
745 integer,
intent(in),
optional :: second_in, minute_in, hour_in
752 ' module has not been initialized', fatal)
762 if (
present(second_in))
then 793 second_out,minute_out,hour_out)
795 integer,
intent(out) :: day_out, month_out, year_out, &
796 second_out, minute_out, hour_out
803 ' module has not been initialized', fatal)
839 fracday, rrsun, dt, allow_negative_cosz, &
842 real,
dimension(:,:),
intent(in) :: lat, lon
843 real,
intent(in) :: gmt, time_since_ae
844 real,
dimension(:,:),
intent(out) :: cosz, fracday
845 real,
intent(out) :: rrsun
846 real,
intent(in),
optional :: dt
847 logical,
intent(in),
optional :: allow_negative_cosz
848 real,
dimension(:,:),
intent(out),
optional :: half_day_out
854 real,
dimension(size(lat,1),size(lat,2)) :: t, tt, h, aa, bb, &
857 logical :: Lallow_negative
881 if (time_since_ae < 0.0 .or. time_since_ae >
twopi) &
883 'time_since_ae not between 0 and 2pi', fatal)
888 if (gmt < 0.0 .or. gmt >
twopi) &
890 'gmt not between 0 and 2pi', fatal)
896 ang =
angle(time_since_ae)
903 aa = sin(lat)*sin(dec)
904 bb = cos(lat)*cos(dec)
913 lallow_negative = .false.
914 if (
present(allow_negative_cosz))
then 915 if (allow_negative_cosz) lallow_negative = .true.
924 if (
present(half_day_out) )
then 928 if (
present(dt) )
then 935 if (.not. lallow_negative)
then 939 where (t < -h .and. tt < -h) cosz = 0.0
945 where ( (tt+h) /= 0.0 .and. t < -h .and. abs(tt) <= h) &
946 cosz = aa + bb*(stt + sh)/ (tt + h)
954 where (t < -h .and. h /= 0.0 .and. h < tt) &
955 cosz = aa + bb*( sh + sh)/(h+h)
960 where ( abs(t) <= h .and. abs(tt) <= h) &
961 cosz = aa + bb*(stt - st)/ (tt - t)
967 where ((h-t) /= 0.0 .and. abs(t) <= h .and. h < tt) &
968 cosz = aa + bb*(sh - st)/(h-t)
975 where (
twopi - h < tt .and. (tt+h-
twopi) /= 0.0 .and. t <= h ) &
976 cosz = (cosz*(h - t) + (aa*(tt + h -
twopi) + &
977 bb*(stt + sh))) / ((h - t) + (tt + h -
twopi))
983 where( h < t .and.
twopi - h >= tt ) cosz = 0.0
991 where( h < t .and.
twopi - h < tt )
992 cosz = aa + bb*(stt + sh) / (tt + h -
twopi)
996 cosz = aa + bb*(stt - st)/ (tt - t)
1005 where (t < -h .and. tt < -h) fracday = 0.0
1006 where (t < -h .and. abs(tt) <= h) fracday = (tt + h )/dt
1007 where (t < -h .and. h < tt) fracday = ( h + h )/dt
1008 where (abs(t) <= h .and. abs(tt) <= h) fracday = (tt - t )/dt
1009 where (abs(t) <= h .and. h < tt) fracday = ( h - t )/dt
1010 where ( h < t ) fracday = 0.0
1011 where (
twopi - h < tt) fracday = fracday + &
1018 if (.not. lallow_negative)
then 1020 cosz = aa + bb*cos(t)
1027 cosz = aa + bb*cos(t)
1039 if (.not. lallow_negative)
then 1040 cosz =
max(0.0, cosz)
1062 fracday, rrsun, dt, allow_negative_cosz, &
1066 real,
dimension(:),
intent(in) :: lat, lon
1067 real,
intent(in) :: gmt, time_since_ae
1068 real,
dimension(:),
intent(out) :: cosz, fracday
1069 real,
intent(out) :: rrsun
1070 real,
intent(in),
optional :: dt
1071 logical,
intent(in),
optional :: allow_negative_cosz
1072 real,
dimension(:),
intent(out),
optional :: half_day_out
1077 real,
dimension(size(lat),1) :: lat_2d, lon_2d, cosz_2d, &
1078 fracday_2d,halfday_2d
1091 cosz_2d, fracday_2d, rrsun, dt=dt, &
1092 allow_negative_cosz=allow_negative_cosz, &
1093 half_day_out=halfday_2d)
1103 fracday = fracday_2d(:,1)
1105 if (
present(half_day_out))
then 1106 half_day_out = halfday_2d(:,1)
1128 fracday, rrsun, dt, allow_negative_cosz, &
1131 real,
intent(in) :: lat, lon, gmt, time_since_ae
1132 real,
intent(out) :: cosz, fracday, rrsun
1133 real,
intent(in),
optional :: dt
1134 logical,
intent(in),
optional :: allow_negative_cosz
1135 real,
intent(out),
optional :: half_day_out
1140 real,
dimension(1,1) :: lat_2d, lon_2d, cosz_2d, fracday_2d, halfday_2d
1153 cosz_2d, fracday_2d, rrsun, dt=dt, &
1154 allow_negative_cosz=allow_negative_cosz, &
1155 half_day_out=halfday_2d)
1164 fracday = fracday_2d(1,1)
1166 if (
present(half_day_out))
then 1167 half_day_out = halfday_2d(1,1)
1192 rrsun, dt_time, allow_negative_cosz, &
1196 real,
dimension(:,:),
intent(in) :: lat, lon
1197 type(time_type),
intent(in) :: time
1198 real,
dimension(:,:),
intent(out) :: cosz, fracday
1199 real,
intent(out) :: rrsun
1200 type(time_type),
intent(in),
optional :: dt_time
1201 logical,
intent(in),
optional :: allow_negative_cosz
1202 real,
dimension(:,:),
intent(out),
optional :: half_day_out
1209 real :: gmt, time_since_ae
1227 if (
present(dt_time))
then 1231 'radiation time step must be no longer than 12 hrs', &
1236 'radiation time step must not be an integral & 1237 &number of days', fatal)
1245 fracday, rrsun, dt=dt, &
1246 allow_negative_cosz=allow_negative_cosz, &
1247 half_day_out=half_day_out)
1251 allow_negative_cosz=allow_negative_cosz, &
1252 half_day_out=half_day_out)
1274 rrsun, dt_time, allow_negative_cosz, &
1278 real,
dimension(:),
intent(in) :: lat, lon
1279 type(time_type),
intent(in) :: time
1280 real,
dimension(:),
intent(out) :: cosz, fracday
1281 real,
intent(out) :: rrsun
1282 type(time_type),
intent(in),
optional :: dt_time
1283 logical,
intent(in),
optional :: allow_negative_cosz
1284 real,
dimension(:),
intent(out),
optional :: half_day_out
1290 real,
dimension(size(lat),1) :: lat_2d, lon_2d, cosz_2d, &
1291 fracday_2d, halfday_2d
1303 if (
present(dt_time))
then 1305 fracday_2d, rrsun, dt_time=dt_time, &
1306 allow_negative_cosz=allow_negative_cosz, &
1307 half_day_out=halfday_2d)
1310 fracday_2d, rrsun, &
1311 allow_negative_cosz=allow_negative_cosz, &
1312 half_day_out=halfday_2d)
1319 fracday = fracday_2d(:,1)
1321 if (
present(half_day_out))
then 1322 half_day_out = halfday_2d(:,1)
1342 rrsun, dt_time, allow_negative_cosz, &
1346 real,
intent(in) :: lat, lon
1347 type(time_type),
intent(in) :: time
1348 real,
intent(out) :: cosz, fracday, rrsun
1349 type(time_type),
intent(in),
optional :: dt_time
1350 logical,
intent(in),
optional :: allow_negative_cosz
1351 real,
intent(out),
optional :: half_day_out
1357 real,
dimension(1,1) :: lat_2d, lon_2d, cosz_2d, fracday_2d, halfday_2d
1369 if (
present(dt_time))
then 1371 fracday_2d, rrsun, dt_time=dt_time, &
1372 allow_negative_cosz=allow_negative_cosz, &
1373 half_day_out=halfday_2d)
1376 fracday_2d, rrsun, &
1377 allow_negative_cosz=allow_negative_cosz, &
1378 half_day_out=halfday_2d)
1385 fracday= fracday_2d(1,1)
1387 if (
present(half_day_out))
then 1388 half_day_out = halfday_2d(1,1)
1408 real,
dimension(:,:),
intent(in) :: lat
1409 real,
intent(in) :: time_since_ae
1410 real,
dimension(:,:),
intent(out) :: cosz, h_out
1411 real,
intent(out) :: rr_out
1417 real,
dimension(size(lat,1),size(lat,2)) :: h
1418 real :: ang, dec, rr
1423 if (time_since_ae < 0.0 .or. time_since_ae >
twopi) &
1425 'time_since_ae not between 0 and 2pi', fatal)
1432 ang =
angle(time_since_ae)
1445 cosz = sin(lat)*sin(dec) + cos(lat)*cos(dec)*sin(h)/h
1466 real,
intent(in),
dimension(:) :: lat
1467 real,
intent(in) :: time_since_ae
1468 real,
intent(out),
dimension(size(lat(:))) :: cosz
1469 real,
intent(out),
dimension(size(lat(:))) :: h_out
1470 real,
intent(out) :: rr_out
1476 real,
dimension(size(lat),1) :: lat_2d, cosz_2d, hout_2d
1493 h_out = hout_2d(:,1)
1510 real,
intent(in),
dimension(:) :: lat
1511 real,
intent(in) :: time_since_ae
1512 real,
intent(out),
dimension(size(lat(:))) :: cosz, solar
1518 real,
dimension(size(lat),1) :: lat_2d, cosz_2d, hout_2d
1536 solar = cosz_2d(:,1)*hout_2d(:,1)*rr_out
1554 real,
intent(in) :: lat, time_since_ae
1555 real,
intent(out) :: cosz, h_out, rr_out
1560 real,
dimension(1,1) :: lat_2d, cosz_2d, hout_2d
1576 h_out = hout_2d(1,1)
1596 real,
dimension(:,:),
intent(in) :: lat
1597 type(time_type),
intent(in) :: time
1598 real,
dimension(:,:),
intent(out) :: cosz, fracday
1599 real,
intent(out) :: rrsun
1605 real :: time_since_ae
1611 if (time_since_ae < 0.0 .or. time_since_ae >
twopi) &
1613 'time_since_ae not between 0 and 2pi', fatal)
1635 real,
dimension(:),
intent(in) :: lat
1636 type(time_type),
intent(in) :: time
1637 real,
dimension(:),
intent(out) :: cosz, fracday
1638 real,
intent(out) :: rrsun
1643 real,
dimension(size(lat),1) :: lat_2d, cosz_2d, fracday_2d
1662 fracday = fracday_2d(:,1)
1678 real,
dimension(:),
intent(in) :: lat
1679 type(time_type),
intent(in) :: time
1680 real,
dimension(:),
intent(out) :: cosz, solar
1685 real,
dimension(size(lat),1) :: lat_2d, cosz_2d, fracday_2d
1705 solar = cosz_2d(:,1)*fracday_2d(:,1)*rrsun
1722 real,
intent(in) :: lat
1723 type(time_type),
intent(in) :: time
1724 real,
intent(out) :: cosz, fracday, rrsun
1730 real,
dimension(1,1) :: lat_2d, cosz_2d, fracday_2d
1748 fracday = fracday_2d(1,1)
1768 integer,
intent(in) :: js, je
1769 real,
dimension(:,:),
intent(in) :: lat
1770 real,
dimension(:,:),
intent(out) :: solar, cosz, fracday
1771 real,
intent(out) :: rrsun
1777 real,
dimension(size(lat,1),size(lat,2)) :: s,z
1818 where(solar .eq.0.0)
1821 fracday = solar/cosz
1875 integer,
intent(in) :: jst, jnd
1876 real,
dimension(:),
intent(in) :: lat(:)
1877 real,
dimension(:),
intent(out) :: cosz, solar, fracday
1878 real,
intent(out) :: rrsun_out
1884 real,
dimension(size(lat),1) :: lat_2d, solar_2d, cosz_2d, &
1902 solar_2d, fracday_2d, rrsun)
1907 fracday = fracday_2d(:,1)
1909 solar = solar_2d(:,1)
1935 real,
dimension(:),
intent(in) :: lat
1936 real,
dimension(:),
intent(out) :: cosz
1937 real,
dimension(:),
intent(out) :: solar
1944 real,
dimension(size(lat),1) :: lat_2d, solar_2d, cosz_2d, &
1965 solar_2d, fracday_2d, rrsun)
1970 solar = solar_2d(:,1)
1979 'annual_mean_solar_2level should be called only once', &
2030 real :: d1, d2, d3, d4, d5, dt, norm
2041 norm = sqrt(1.0 -
ecc**2)
2053 d5 = d1/6.0 + d2/3.0 +d3/3.0 +d4/6.0
2057 end subroutine orbit 2065 real,
intent(in) :: ang
2083 r = (1. -
ecc**2)/(1. +
ecc*cos(ang - rad_per))
2096 real,
intent(in) :: t
2116 int = floor(norm_time)
2119 x = norm_time - floor(norm_time)
2131 real,
intent(in) :: ang
2145 sin_dec = - sin(rad_obliq)*sin(ang)
2157 real,
dimension(:,:),
intent(in) :: latitude
2158 real,
intent(in) :: dec
2159 real,
dimension(size(latitude,1),size(latitude,2)) :: h
2165 real,
dimension (size(latitude,1),size(latitude,2)):: &
2166 cos_half_day, & !< Cosine of half-day length [dimensionless]
2169 real :: eps = 1.0e-05
2180 where (latitude == 0.5*
pi) lat= latitude - eps
2181 where (latitude == -0.5*
pi) lat= latitude + eps
2187 cos_half_day = -tan(lat)*tan_dec
2188 where (cos_half_day <= -1.0) h =
pi 2189 where (cos_half_day >= +1.0) h = 0.0
2190 where(cos_half_day > -1.0 .and. cos_half_day < 1.0) &
2191 h = acos(cos_half_day)
2204 real,
intent(in) :: latitude, dec
2210 real,
dimension(1,1) :: lat_2d, h_2d
2244 t =
twopi*(t - floor(t))
2261 integer :: seconds, days
2263 call get_time (time, seconds, days)
real deg_to_rad
conversion from degrees to radians
type(time_type) function, public length_of_year()
integer year_ae
Year of specified autumnal equinox.
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...
type(time_type) function, public set_date_julian(year, month, day, hour, minute, second)
subroutine set_period_integer(period_in)
set_period_integer saves as the input length of the year (an integer) in a time_type module variable...
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. on return, the 2d fields are returned to the original 1d fields.
subroutine, public astronomy_end
astronomy_end is the destructor for astronomy_mod.
type(time_type) autumnal_eq_ref
time_type variable containing specified time of reference NH autumnal equinox
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_...
subroutine, public get_ref_date_of_ae(day_out, month_out, year_out, second_out, minute_out, hour_out)
get_ref_date_of_ae retrieves the reference date of the autumnal equinox as integer variables...
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...
logical module_is_initialized
has the module been initialized ?
subroutine, public set_orbital_parameters(ecc_in, obliq_in, per_in)
set_orbital_parameters saves the input values of eccentricity, obliquity and perihelion time as modul...
integer minute_ae
Minute of specified autumnal equinox.
real, dimension(:,:), allocatable fracday_ann
annual mean daylight fraction
integer day_ae
Day of specified autumnal equinox.
real 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...
integer hour_ae
Hour of specified autumnal equinox.
integer function, public check_nml_error(IOSTAT, NML_NAME)
real function, public orbital_time(time)
Orbital time returns the time (1 year = 2*pi) since autumnal equinox.
subroutine get_period_integer(period_out)
get_period_integer returns the length of the year as an integer number of seconds.
real function, public universal_time(time)
universal_time returns the time of day at longitude = 0.0 (1 day = 2*pi)
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...
integer month_ae
Month of specified autumnal equinox.
subroutine, public set_ref_date_of_ae(day_in, month_in, year_in, second_in, minute_in, hour_in)
set_ref_date_of_ae provides a means of specifying the reference date of the NH autumnal equinox for a...
subroutine set_period_time_type(period_in)
Set_period_time_type saves the length of the year (input as a time_type variable) into a time_type mo...
integer period
Specified length of year [seconds]; must be specified to override default value given by length_of_ye...
character(len=input_str_length), dimension(:), allocatable, target, public input_nml_file
real obliq
Obliquity [degrees].
real ecc
Eccentricity of Earth's orbit [dimensionless].
real, parameter, public pi
Ratio of circle circumference to diameter [N/A].
integer num_angles
Number of intervals into which the year is divided to compute orbital positions.
subroutine, public fms_init(localcomm)
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. on return, the 2d fields are returned to the original 1d fields.
real function, private r_inv_squared(ang)
r_inv_squared returns the inverse of the square of the earth-sun distance relative to the mean distan...
subroutine, public get_orbital_parameters(ecc_out, obliq_out, per_out)
get_orbital_parameters retrieves the orbital parameters for use by another module.
real function, private declination(ang)
Declination returns the solar declination angle at orbital position ang in earth's orbit...
real function half_day_0d(latitude, dec)
half_day_0d takes scalar input fields, makes them into 2-d fields dimensioned (1,1), and calls half_day_2d. On return, the 2-d fields are converted to the desired scalar output.
real, dimension(:), allocatable orb_angle
table of orbital positions (0 to 2*pi) as a function of time used to find actual orbital position via...
subroutine, public time_manager_init()
astronomy_mod provides astronomical variables for use by other modules within fms. The only currently used interface is for determination of astronomical values needed by the shortwave radiation packages.
integer num_pts
count of grid_boxes for which annual mean astronomy values have been calculated
type(time_type) period_time_type
time_type variable containing period of one orbit
subroutine, public astronomy_init(latb, lonb)
astronomy_init is the constructor for astronomy_mod.
real, dimension(:,:), allocatable cosz_ann
annual mean cos of zenith angle
logical annual_mean_calculated
have the annual mean values been calculated?
real rrsun_ann
annual mean earth-sun distance
real seconds_per_day
seconds in a day
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 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 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...
integer total_pts
number of grid boxes owned by the processor
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 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 ...
integer second_ae
Second of specified autumnal equinox.
subroutine get_period_time_type(period_out)
get_period_time_type returns the length of the year as a time_type variable.
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...
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 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 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 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. on return, the 2d fields are returned to the original 1d fields.
real function, private angle(t)
angle determines the position within the earth's orbit at time t in the year (t = 0 at NH autumnal eq...
subroutine, public get_time(Time, seconds, days, ticks, err_msg)
subroutine, public error_mesg(routine, message, level)
real per
Longitude of perihelion with respect to autumnal equinox in NH [degrees].
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, private orbit
Orbit computes and stores a table of value of orbital angles as a function of orbital time (both the ...
subroutine, public constants_init
dummy routine.
subroutine, public get_date_julian(time, year, month, day, hour, minute, second)
real, dimension(:,:), allocatable solar_ann
annual mean solar factor