module Database.PostgreSQL.PQTypes.Interval (
Interval(..)
, iyears
, imonths
, idays
, ihours
, iminutes
, iseconds
, imicroseconds
) where
import Control.Applicative
import Data.Int
import Data.List
import Data.Monoid
import Data.Typeable
import Foreign.Storable
import Prelude
import qualified Data.ByteString.Char8 as BS
import Database.PostgreSQL.PQTypes.Format
import Database.PostgreSQL.PQTypes.FromSQL
import Database.PostgreSQL.PQTypes.Internal.Utils
import Database.PostgreSQL.PQTypes.ToSQL
data Interval = Interval {
intYears :: !Int32
, intMonths :: !Int32
, intDays :: !Int32
, intHours :: !Int32
, intMinutes :: !Int32
, intSeconds :: !Int32
, intMicroseconds :: !Int32
} deriving (Eq, Ord, Typeable)
instance Show Interval where
showsPrec _ Interval{..} = (++) . intercalate ", " $ filter (not . null) [
f intYears "year"
, f intMonths "month"
, f intDays "day"
, f intHours "hour"
, f intMinutes "minute"
, f intSeconds "second"
, f intMicroseconds "microsecond"
]
where
f n desc = case n of
0 -> ""
1 -> show n ++ " " ++ desc
_ -> show n ++ " " ++ desc ++ "s"
instance Monoid Interval where
mempty = Interval 0 0 0 0 0 0 0
mappend a b = Interval {
intYears = intYears a + intYears b
, intMonths = intMonths a + intMonths b
, intDays = intDays a + intDays b
, intHours = intHours a + intHours b
, intMinutes = intMinutes a + intMinutes b
, intSeconds = intSeconds a + intSeconds b
, intMicroseconds = intMicroseconds a + intMicroseconds b
}
instance Storable Interval where
sizeOf _ = (28)
alignment _ = 4
peek ptr = Interval
<$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
<*> (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
<*> (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
<*> (\hsc_ptr -> peekByteOff hsc_ptr 12) ptr
<*> (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
<*> (\hsc_ptr -> peekByteOff hsc_ptr 20) ptr
<*> (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
poke ptr Interval{..} = do
(\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr intYears
(\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr intMonths
(\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr intDays
(\hsc_ptr -> pokeByteOff hsc_ptr 12) ptr intHours
(\hsc_ptr -> pokeByteOff hsc_ptr 16) ptr intMinutes
(\hsc_ptr -> pokeByteOff hsc_ptr 20) ptr intSeconds
(\hsc_ptr -> pokeByteOff hsc_ptr 24) ptr intMicroseconds
instance PQFormat Interval where
pqFormat = const $ BS.pack "%interval"
instance FromSQL Interval where
type PQBase Interval = Interval
fromSQL Nothing = unexpectedNULL
fromSQL (Just int) = return int
instance ToSQL Interval where
type PQDest Interval = Interval
toSQL int _ = putAsPtr int
iyears :: Int32 -> Interval
iyears v = mempty { intYears = v }
imonths :: Int32 -> Interval
imonths v = mempty { intMonths = v }
idays :: Int32 -> Interval
idays v = mempty { intDays = v }
ihours :: Int32 -> Interval
ihours v = mempty { intHours = v }
iminutes :: Int32 -> Interval
iminutes v = mempty { intMinutes = v }
iseconds :: Int32 -> Interval
iseconds v = mempty { intSeconds = v }
imicroseconds :: Int32 -> Interval
imicroseconds v = mempty { intMicroseconds = v }