--- /dev/null
+module Data.Time.Asctime
+    ( format
+    , parse
+    )
+    where
+
+import qualified Text.Parsec as P
+
+import Data.Time
+import Data.Time.Calendar.WeekDate
+import Data.Time.HTTP.Common
+import Data.Time.Asctime.Parsec
+
+{-
+  Wdy Mon DD HH:MM:SS YYYY
+-}
+
+format :: LocalTime -> String
+format localTime
+    = let (year, month, day) = toGregorian (localDay localTime)
+          (_, _, week)       = toWeekDate  (localDay localTime)
+          timeOfDay          = localTimeOfDay localTime
+      in
+        concat [ shortWeekDayName week
+               , ", "
+               , shortMonthName month
+               , " "
+               , show2 day
+               , " "
+               , show2 (todHour timeOfDay)
+               , ":"
+               , show2 (todMin timeOfDay)
+               , ":"
+               , show2 (floor (todSec timeOfDay))
+               , " "
+               , show4 year
+               ]
+
+parse :: String -> Maybe LocalTime
+parse src = case P.parse p "" src of
+              Right zt -> Just zt
+              Left  _  -> Nothing
+    where
+      p = do zt <- asctime
+             _  <- P.eof
+             return zt
 
--- /dev/null
+{-# LANGUAGE FlexibleContexts #-}
+module Data.Time.Asctime.Parsec
+    ( asctime
+    )
+    where
+
+import Control.Monad
+import Data.Fixed
+import Data.Time
+import Data.Time.Calendar.WeekDate
+import Data.Time.HTTP.Common
+import Text.Parsec
+
+
+asctime :: Stream s m Char => ParsecT s u m LocalTime
+asctime = do weekDay <- shortWeekDayNameP
+             _       <- string ", "
+             month   <- shortMonthNameP
+             _       <- char ' '
+             day     <- read2
+             _       <- char ' '
+             hour    <- read2
+             _       <- char ':'
+             minute  <- read2
+             _       <- char ':'
+             second  <- read2
+             _       <- char ' '
+             year    <- read4
+
+             gregDay <- assertGregorianDateIsGood year month day
+             _       <- assertWeekDayIsGood weekDay gregDay
+             tod     <- assertTimeOfDayIsGood hour minute second
+
+             return (LocalTime gregDay tod)
 
           _     <- char ' '
           year  <- read4
           _     <- char ' '
-          assertGregorianDateIsGood (toInteger year) month day
+          assertGregorianDateIsGood year month day
 
                    <|>
                    liftM (+ 1900) read2
           _     <- char ' '
-          assertGregorianDateIsGood (toInteger year) month day
+          assertGregorianDateIsGood year month day
 
 time :: Stream s m Char => ParsecT s u m (TimeOfDay, TimeZone)
 time = do tod <- hour
 
           _     <- char ' '
           year  <- liftM (+ 1900) read2
           _     <- char ' '
-          assertGregorianDateIsGood (toInteger year) month day
+          assertGregorianDateIsGood year month day
 
 rfc822time :: Stream s m Char => ParsecT s u m (TimeOfDay, TimeZone)
 rfc822time = do tod <- hour
 
         Data.Time.RFC822.Parsec
         Data.Time.RFC1123
         Data.Time.RFC1123.Parsec
+        Data.Time.Asctime
+        Data.Time.Asctime.Parsec
 
     Other-modules:
         Data.Time.HTTP.Common