module TerraHS.Algebras.Temporal.TimeFunctions where



import System.Time
import Char


-------------------------------------------
-- time functions -------------------------
-------------------------------------------

{-- | January 1, 1970, midnight, UTC, represented as a CalendarTime. --}
epoch :: CalendarTime
epoch = CalendarTime { ctYear = 1970, ctMonth = January,
                       ctDay = 1, ctHour = 0, ctMin = 0, ctSec = 0,
                       ctPicosec = 0, ctWDay = Thursday, ctYDay = 0,
                       ctTZName = "UTC", ctTZ = 0, ctIsDST = False}

{-- | Converts the specified CalendarTime (see System.Time) to 
seconds-since-epoch time.

This conversion does respect the timezone specified on the input object.
If you want a conversion from UTC, specify ctTZ = 0 and ctIsDST = False.

When called like that, the behavior is equivolent to the GNU C function
timegm().  Unlike the C library, Haskell's CalendarTime supports
timezone information, so if such information is specified, it will impact
the result.
--}

timegm :: CalendarTime -> Integer
timegm ct =
    timeDiffToSecs (diffClockTimes (toClockTime ct) (toClockTime epoch))

{-- | Converts the specified CalendarTime (see System.Time) to 
seconds-since-epoch format.

The input CalendarTime is assumed to be the time as given in your local
timezone.  All timezone and DST fields in the object are ignored.

This behavior is equivolent to the timelocal() and mktime() functions that
C programmers are accustomed to.

Please note that the behavior for this function during the hour immediately
before or after a DST switchover may produce a result with a different hour
than you expect.
--}

timelocal :: CalendarTime -> IO Integer
timelocal ct =
    do guessct <- toCalendarTime guesscl
       let newct = ct {ctTZ = ctTZ guessct}
       return $ timegm newct
    where guesscl = toClockTime ct
    
{-- | Converts the given timeDiff to the number of seconds it represents. 

Uses the same algorithm as normalizeTimeDiff in GHC. --}
timeDiffToSecs :: TimeDiff -> Integer
timeDiffToSecs td = 
    (fromIntegral $ tdSec td) +
    60 * ((fromIntegral $ tdMin td) +
          60 * ((fromIntegral $ tdHour td) +
                24 * ((fromIntegral $ tdDay td) +
                      30 * ((fromIntegral $ tdMonth td) +
                            365 * (fromIntegral $ tdYear td)))))
			    
toMonth::Int->Month
toMonth m
	|m == 1  = January
  	|m == 2 = February
  	|m == 3 = March
  	|m == 4 = April
  	|m == 5 = May
  	|m == 6 = June
  	|m == 7 = July
  	|m == 8 = August
  	|m == 9 = September
  	|m == 10 = October
  	|m == 11 = November
  	|m == 12 = December