{-# OPTIONS -fno-warn-missing-methods #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE EmptyDataDecls #-}
module Data.Time
(
getCurrentTime
,fromGregorian
,UTCTime
,Day
,utctDay
,showTime
,showDay)
where
import Data.Data
import Data.Text
import FFI
import Prelude (Show,Eq,Ord,Int)
data UTCTime
deriving (Typeable)
instance Data UTCTime
instance Show UTCTime
instance Eq UTCTime
instance Ord UTCTime
data Day
deriving (Typeable)
instance Data Day
instance Show Day
instance Eq Day
instance Ord Day
getCurrentTime :: Fay UTCTime
getCurrentTime :: Fay UTCTime
getCurrentTime = String -> Fay UTCTime
forall s a. IsString s => s -> a
ffi String
"(new Date()).getTime()"
fromGregorian :: Int
-> Int
-> Int
-> Day
fromGregorian :: Int -> Int -> Int -> Day
fromGregorian = String -> Int -> Int -> Int -> Day
forall s a. IsString s => s -> a
ffi String
"Date.UTC(%1,%2-1,%3)"
utctDay :: UTCTime -> Day
utctDay :: UTCTime -> Day
utctDay = String -> UTCTime -> Day
forall s a. IsString s => s -> a
ffi String
"%1"
showTime :: UTCTime -> Text
showTime :: UTCTime -> Text
showTime = String -> UTCTime -> Text
forall s a. IsString s => s -> a
ffi String
"new Date(%1).toString()"
showDay :: Day -> Text
showDay :: Day -> Text
showDay =
String -> Day -> Text
forall s a. IsString s => s -> a
ffi String
"(%1).getUTCFullYear() + ' ' + ((%1).getUTCMonth() + 1) + ' ' + ((%1).getUTCDate() + 1)"