PROGRAM WeatherCalc !--------------------------------------------------------------------------- ! This program calculates the heat index, hurricane scale, potential temp ! temperature conversion between farhenheit and celsius, wind chill, ! windspeed conversion between knots and mph. Variables are: ! ! Author: Meteorologist Andy Kren ! Date: May 3rd, 2008 !--------------------------------------------------------------------------- IMPLICIT NONE REAL :: TempH, RH, Heat_Index, ptemp, Celsius, p0, p1, Maxtemp, Kelvin, Celsius2, TempF, TempC, Fahrenheit REAL :: WindChill, WindSpeed, Knots, Mph, WindSpeed_mph, WindSpeed_knots, Temperature, dpf, Tc, Tdc, E, Es INTEGER :: Knots_or_Mph CHARACTER :: ForCresponse, Response, FinalChoice PRINT * PRINT *, "Weather Calculator" PRINT *, " By: Andy Kren " PRINT *, "------------------" DO ! Ask user what he wants to calculate PRINT *, "Enter 1-6 corresponding to what you want to calculate:" PRINT * PRINT *, "1. Potential Temperature" PRINT *, "2. Temperature Conversion" PRINT *, "3. Wind Speed Conversion" PRINT *, "4. Wind Chill" PRINT *, "5. Heat Index" PRINT *, "6. Hurricane Scale" PRINT * READ *, Response DO IF (Response == "1") THEN PRINT * PRINT *, "Enter the level (mb) at which you wish to determine Theta:" READ *, p1 PRINT *, "Enter the surface pressure (i.e. around 1030mb or less):" READ *, p0 PRINT *, "Enter the temperature in Celsius at level to mix down:" READ *, Celsius !convert temperature to kelvin Kelvin = Celsius + 273 ! calculate potential temperature ptemp = (Kelvin)*((p0 / p1)**(.286)) ! convert potential temp to fahrenheit Celsius2 = ptemp - 273 Maxtemp = (1.8 * Celsius2) + 32 PRINT *, "The Max Temperature (or Potential Temp) = ", MaxTemp EXIT ELSE IF (Response == "2") THEN PRINT * PRINT *, "Enter (1) to convert from F to C or (2) for vice versa:" READ *, ForCresponse IF (ForCresponse == "1") THEN PRINT *, "Enter the Fahrenheit Temperature" READ *, TempF ! Calculate the Celsius temp. Celsius = (0.555555556) * (TempF - 32) ! Print out celsius temp 100 FORMAT (1X, A28, F10.2) PRINT 100, "The Celsius Temperature is:", Celsius ELSE IF (ForCresponse == "2") THEN PRINT *, "Enter the Celsius Temperature" READ *, TempC ! Calculate the Fahrenheit Fahrenheit = (1.8 * TempC) + 32 ! Print out Fahrenheit temp 110 FORMAT (1X, A31, F10.2) PRINT 110, "The Fahrenheit Temperature is:", Fahrenheit ELSE PRINT *, "THAT IS NOT A VALID RESPONSE. RE-RUN PROGRAM." STOP END IF EXIT ELSE IF (Response == "3") THEN PRINT * PRINT *, "Enter a (1) to convert from knots to mph or (2) for vice versa:" READ *, Knots_or_Mph IF (Knots_or_Mph == 1) THEN ! calculate the knots to mph conversion and ask if wants to reconvert PRINT *, "Enter the wind speed in knots:" READ *, Knots WindSpeed_mph = Knots * 1.15 130 FORMAT(1X, A24, F12.1, T39, A3) PRINT 130, "The Wind Speed in MPH = ", WindSpeed_mph, "mph" PRINT * ELSE IF (Knots_or_Mph == 2) THEN ! calculate the mph to knots conversion and ask if wants to reconvert PRINT *, "Enter the wind speed in mph:" READ *, Mph WindSpeed_knots = Mph / (1.15) 140 FORMAT(1X, A26, F12.1, T41, A5) PRINT 140, "The Wind Speed in Knots = ", WindSpeed_knots, "knots" ELSE PRINT *, "***Enter a valid number (1) or (2)***" STOP END IF EXIT ELSE IF (Response == "4") THEN PRINT * PRINT *, "Enter the Surface Temperature (degrees F)" READ *, Temperature PRINT *, "Enter the Wind Speed (mph)" READ *, WindSpeed IF (WindSpeed < 0) STOP "*Re-run program. Wind speed not negative*" WindChill = 35.74 + (0.6215 * Temperature) - (35.75 * (WindSpeed**& &0.16)) + (0.4275 * Temperature * (WindSpeed ** 0.16)) 200 FORMAT(1X, A, 1X, F10.1) IF (WindChill > 40) THEN PRINT 200, "The Wind Chill is:", WindChill PRINT *, " This weather is no problem!" ELSE IF (WindChill > 20) THEN PRINT 200, "The Wind Chill is:", WindChill PRINT * PRINT *, " That's Chilly!" ELSE IF (WindChill > 10) THEN PRINT 200, "The Wind Chill is:", WindChill PRINT * PRINT *, " Pretty Nippy Outside!" ELSE IF (WindChill > 0) THEN PRINT 200, "The Wind Chill is:", WindChill PRINT * PRINT *, " That's Pretty Cold my Friend!!" ELSE IF (WindChill < 0) THEN PRINT 200, "The Wind Chill is:", WindChill PRINT * PRINT *, " Bitterly Freezing Cold!!!" END IF PRINT * EXIT ELSE IF (Response == "5") THEN DO PRINT * PRINT *, "Enter the air Temperature (Fahrenheit >= 80): " READ *, TempH IF (TempH >= 80) EXIT END DO PRINT *, "Enter the Dewpoint Temperature in Fahrenheit: " READ *, dpf ! convert temp and dewpoint to celsius Tc = (0.555555556) * (TempH - 32) Tdc = (0.555555556) * (dpf - 32) ! calculate vapor pressure and saturation vapor pressure (E, Es) E = 6.11 * (10.0**((7.5*Tdc)/(237.7+Tdc))) Es = 6.11 * (10.0**((7.5*Tc)/(237.7+Tc))) ! calulate RH to be used in finding the heat index: RH = (E / Es) * 100 ! calculate heat index Heat_Index = (-42.379) + (2.04901523 * TempH) + (10.14333127 * RH) & &- (0.22475541 * TempH * RH) - (6.83783e-3 * (TempH ** 2)) & &- (5.481717e-2 * (RH ** 2)) + (1.22874e-3 * (TempH ** 2) * RH) & &+ (8.5282e-4 * TempH * (RH ** 2)) - (1.99e-6 * (TempH ** 2) * (RH ** 2)) ! print out results PRINT * PRINT 190, "----------------------------------------" PRINT 170, "For your given Temp: ", TempH PRINT 240, "For your given Dewpoint: ", dpf PRINT * PRINT 180, "Heat Index = ", Heat_Index PRINT 230, "Relative Humidity = ", RH, "%" PRINT 190, "----------------------------------------" PRINT * 170 FORMAT(1X, A21, F6.2) 240 FORMAT(1X, A25, F6.2) 180 FORMAT(1X, A13, F6.1) 190 FORMAT(1X, A40) 230 FORMAT(1X, A20, F6.2, A1) EXIT ELSE IF (Response == "6") THEN PRINT * PRINT *, "Saffir Simpson Hurricane Scale" PRINT *, "------------------------------" PRINT * PRINT *, "Enter the Wind Speed of the Storm (mph):" READ *, WindSpeed ! Determine the category of the storm IF (WindSpeed <= 0) THEN PRINT *, "Storm cannot have a 0 or negative wind-RE-RUN PROGRAM" STOP ELSE IF (WindSpeed < 38) THEN PRINT * PRINT *, "This disturbance is too weak! No organized storm." ELSE IF (WindSpeed == 38) THEN PRINT * PRINT *, "A Tropical Depression" ELSE IF (WindSpeed >= 39.AND.WindSpeed <= 73) THEN PRINT * PRINT *, "A Tropical Storm" ELSE IF (WindSpeed >= 74.AND.WindSpeed <= 95) THEN PRINT * PRINT *, "A Category 1 Hurricane" ELSE IF (WindSpeed >= 96.AND.WindSpeed <= 110) THEN PRINT * PRINT *, "A Category 2 Hurricane" ELSE IF (Windspeed >= 111.AND.WindSpeed <= 130) THEN PRINT * PRINT *, "A Category 3 Hurricane" ELSE IF (WindSpeed >= 131.AND.WindSpeed <= 155) THEN PRINT * PRINT *, "A Category 4 Hurricane" ELSE PRINT * PRINT *, "A Category 5 Hurricane" END IF EXIT ELSE PRINT *, "Enter a Valid Integer between 1 and 6, and re-run program" EXIT END IF END DO ! ask user if he wants to re-calcluate another quantity PRINT * PRINT *, "Do you want to Calculate another thing? (Y or N)?" READ *, FinalChoice IF (FinalChoice == "N".OR.FinalChoice == "n") THEN EXIT END IF END DO END PROGRAM WeatherCalc