PROGRAM grow !--------------------------------------------------- ! Program to calculate the nubmer of growing ! degree days experienced on a particular ! day based on the high and low temperatures ! (fahrenheit) entered by the user. ! ! Identifiers used are: ! maxT : Maximum daily recorded temperature (F) ! minT : Minimum daily recorded temperature (F) ! aveT : average daily temperature (F) ! calculated from maxT and minT ! baseT : 50 degrees F ! gdd : number of growing degree days ! ! Input : Maximum and minimum recorded ! temperatures (F) for the day ! Constant: Base temperature (F) !--------------------------------------------------- IMPLICIT NONE REAL :: maxT, minT real :: gdd !Obtain values for maxT and minT PRINT *, "Enter Maximum Temperature and" // & " Minimum Temperature (degrees F)" PRINT *, "Separated by a comma or space." READ *, maxT, minT !Call function to calculate the number of growing degree days. gdd = grow_days(maxT,minT) !Display growing degree days PRINT *, "Number of growing degree days & is", gdd CONTAINS function grow_days(max_temp,min_temp) real :: grow_days, aveT real, intent(in) :: max_temp, min_temp real :: max_calc, min_calc real, parameter :: baseT = 50 max_calc = max_temp min_calc = min_temp !Set value of max_temp between 50F and 86F IF (max_calc > 86) THEN max_calc = 86 ELSE IF (max_calc < 50) THEN max_calc = 50 ENDIF !Set value of min_temp between 50F and 86F IF (min_calc < 50) THEN min_calc = 50 ELSE IF (min_calc > 86) THEN min_calc = 86 ENDIF !Calculate daily average temperature aveT = calc_average(max_calc,min_calc) !Calculate growing degree days grow_days = aveT - baseT !Make sure grow_days is non-negative IF (grow_days < 0) THEN grow_days = 0 ENDIF end function grow_days function calc_average(Tmax, Tmin) real:: calc_average, Tmax, Tmin calc_average = (Tmax + Tmin) / 2.0 end function calc_average END PROGRAM grow