diff -rU 3 haskelldb-2.1.1/haskelldb.cabal haskelldb-2.1.2/haskelldb.cabal
--- haskelldb-2.1.1/haskelldb.cabal	2012-10-02 17:07:26.000000000 -0430
+++ haskelldb-2.1.2/haskelldb.cabal	2012-10-02 14:37:13.000000000 -0430
@@ -20,7 +20,8 @@
                  old-time >= 1 && < 2, 
                  old-locale >= 1 && < 2, 
                  directory >= 1 && < 2,
-                 containers >= 0.3 && < 1
+                 containers >= 0.3 && < 1,
+                 time
   Extensions:
     EmptyDataDecls,
     DeriveDataTypeable,
diff -rU 3 haskelldb-2.1.1/src/Database/HaskellDB/Database.hs haskelldb-2.1.2/src/Database/HaskellDB/Database.hs
--- haskelldb-2.1.1/src/Database/HaskellDB/Database.hs	2012-10-02 17:07:26.000000000 -0430
+++ haskelldb-2.1.2/src/Database/HaskellDB/Database.hs	2012-10-02 18:20:19.000000000 -0430
@@ -42,6 +42,7 @@
 import Database.HaskellDB.HDBRec
 
 import System.Time
+import Data.Time.LocalTime
 import Control.Monad
 
 infix 9 !.
@@ -103,6 +104,8 @@
 	       , getBool :: s -> String -> IO (Maybe Bool)
 		 -- | Get a 'CalendarTime' value.
 	       , getCalendarTime :: s -> String -> IO (Maybe CalendarTime)
+		 -- | Get a 'LocalTime' value.
+	       , getLocalTime :: s -> String -> IO (Maybe LocalTime)
 	       }
 
 
@@ -144,6 +147,7 @@
 instance GetValue Double where getValue = getNonNull
 instance GetValue Bool where getValue = getNonNull
 instance GetValue CalendarTime where getValue = getNonNull
+instance GetValue LocalTime where getValue = getNonNull
 instance Size n => GetValue (BoundedString n) where getValue = getNonNull
 
 instance GetValue (Maybe String) where getValue = getString
@@ -152,6 +156,7 @@
 instance GetValue (Maybe Double) where getValue = getDouble
 instance GetValue (Maybe Bool) where getValue = getBool
 instance GetValue (Maybe CalendarTime) where getValue = getCalendarTime
+instance GetValue (Maybe LocalTime) where getValue = getLocalTime
 instance Size n => GetValue (Maybe (BoundedString n)) where 
     getValue fs s f = liftM (liftM trunc) (getValue fs s f)
 
diff -rU 3 haskelldb-2.1.1/src/Database/HaskellDB/DBLayout.hs haskelldb-2.1.2/src/Database/HaskellDB/DBLayout.hs
--- haskelldb-2.1.1/src/Database/HaskellDB/DBLayout.hs	2012-10-02 17:07:26.000000000 -0430
+++ haskelldb-2.1.2/src/Database/HaskellDB/DBLayout.hs	2012-10-02 17:42:27.000000000 -0430
@@ -17,7 +17,7 @@
 module Database.HaskellDB.DBLayout
   (module Database.HaskellDB.BoundedString
   , module Database.HaskellDB.DBSpec
-  , CalendarTime
+  , CalendarTime, LocalTime
   , Expr, Table, Attr, baseTable
   , RecCons, RecNil, FieldTag, fieldName
   , hdbMakeEntry, mkAttr, ( # )
@@ -30,6 +30,7 @@
 
 import Database.HaskellDB.BoundedString
 import System.Time (CalendarTime)
+import Data.Time.LocalTime (LocalTime)
 import Database.HaskellDB.Query (Expr, Table, Attr(..)
                                 , baseTable, attribute, (<<), emptyTable)
 import Database.HaskellDB.DBSpec
diff -rU 3 haskelldb-2.1.1/src/Database/HaskellDB/FieldType.hs haskelldb-2.1.2/src/Database/HaskellDB/FieldType.hs
--- haskelldb-2.1.1/src/Database/HaskellDB/FieldType.hs	2012-10-02 17:07:26.000000000 -0430
+++ haskelldb-2.1.2/src/Database/HaskellDB/FieldType.hs	2012-10-02 14:38:23.000000000 -0430
@@ -21,6 +21,7 @@
 
 import Data.Dynamic
 import System.Time
+import Data.Time.LocalTime
 
 import Database.HaskellDB.HDBRec (RecCons(..), Record, RecNil(..), ShowLabels)
 import Database.HaskellDB.BoundedString
@@ -38,6 +39,7 @@
     | DoubleT
     | BoolT
     | CalendarTimeT
+    | LocalTimeT
     | BStrT Int
     deriving (Eq,Ord,Show,Read)
 
@@ -64,6 +66,7 @@
 toHaskellType DoubleT = "Double"
 toHaskellType BoolT = "Bool"
 toHaskellType CalendarTimeT = "CalendarTime"
+toHaskellType LocalTimeT = "LocalTime"
 toHaskellType (BStrT a) = "BStr" ++ show a
 
 -- | Given a query, returns a list of the field names and their
@@ -116,6 +119,9 @@
 instance ExprType CalendarTime where
   fromHaskellType _ = (CalendarTimeT, False)
 
+instance ExprType LocalTime where
+  fromHaskellType _ = (LocalTimeT, False)
+
 instance (Size n) => ExprType (BoundedString n) where
   fromHaskellType b = (BStrT (listBound b), False)
 
diff -rU 3 haskelldb-2.1.1/src/Database/HaskellDB/Sql/Default.hs haskelldb-2.1.2/src/Database/HaskellDB/Sql/Default.hs
--- haskelldb-2.1.1/src/Database/HaskellDB/Sql/Default.hs	2012-10-02 17:07:26.000000000 -0430
+++ haskelldb-2.1.2/src/Database/HaskellDB/Sql/Default.hs	2012-10-02 13:39:53.000000000 -0430
@@ -98,6 +98,7 @@
       DoubleT       -> SqlType "double precision"
       BoolT         -> SqlType "bit"
       CalendarTimeT -> SqlType "timestamp with time zone"
+      LocalTimeT    -> SqlType "timestamp without time zone"
       BStrT a       -> SqlType1 "varchar" a
 
 -----------------------------------------------------------
