{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeOperators #-}
module Toml.Type.Value
(
TValue (..)
, showType
, Value (..)
, DateTime (..)
, eqValueList
, valueType
, TypeMismatchError (..)
, sameValue
) where
import Data.String (IsString (..))
import Data.Text (Text)
import Data.Time (Day, LocalTime, TimeOfDay, ZonedTime, zonedTimeToUTC)
import Data.Type.Equality ((:~:) (..))
data TValue = TBool | TInteger | TDouble | TText | TDate | TArray
deriving (Eq, Show)
showType :: TValue -> String
showType = drop 1 . show
data Value (t :: TValue) where
Bool :: Bool -> Value 'TBool
Integer :: Integer -> Value 'TInteger
Double :: Double -> Value 'TDouble
Text :: Text -> Value 'TText
Date :: DateTime -> Value 'TDate
Array :: [Value t] -> Value 'TArray
deriving instance Show (Value t)
instance (t ~ 'TInteger) => Num (Value t) where
(Integer a) + (Integer b) = Integer $ a + b
(Integer a) * (Integer b) = Integer $ a * b
abs (Integer a) = Integer (abs a)
signum (Integer a) = Integer (signum a)
fromInteger = Integer
negate (Integer a) = Integer (negate a)
instance (t ~ 'TText) => IsString (Value t) where
fromString = Text . fromString @Text
instance Eq (Value t) where
(Bool b1) == (Bool b2) = b1 == b2
(Integer i1) == (Integer i2) = i1 == i2
(Double f1) == (Double f2) = f1 == f2
(Text s1) == (Text s2) = s1 == s2
(Date d1) == (Date d2) = d1 == d2
(Array a1) == (Array a2) = eqValueList a1 a2
eqValueList :: [Value a] -> [Value b] -> Bool
eqValueList [] [] = True
eqValueList (x:xs) (y:ys) = case sameValue x y of
Right Refl -> x == y && eqValueList xs ys
Left _ -> False
eqValueList _ _ = False
valueType :: Value t -> TValue
valueType (Bool _) = TBool
valueType (Integer _) = TInteger
valueType (Double _) = TDouble
valueType (Text _) = TText
valueType (Date _) = TDate
valueType (Array _) = TArray
data DateTime
= Zoned !ZonedTime
| Local !LocalTime
| Day !Day
| Hours !TimeOfDay
deriving (Show)
instance Eq DateTime where
(Zoned a) == (Zoned b) = zonedTimeToUTC a == zonedTimeToUTC b
(Local a) == (Local b) = a == b
(Day a) == (Day b) = a == b
(Hours a) == (Hours b) = a == b
_ == _ = False
data TypeMismatchError = TypeMismatchError
{ typeExpected :: TValue
, typeActual :: TValue
} deriving (Eq)
instance Show TypeMismatchError where
show TypeMismatchError{..} = "Expected type '" ++ showType typeExpected
++ "' but actual type: '" ++ showType typeActual ++ "'"
sameValue :: Value a -> Value b -> Either TypeMismatchError (a :~: b)
sameValue Bool{} Bool{} = Right Refl
sameValue Integer{} Integer{} = Right Refl
sameValue Double{} Double{} = Right Refl
sameValue Text{} Text{} = Right Refl
sameValue Date{} Date{} = Right Refl
sameValue Array{} Array{} = Right Refl
sameValue l r = Left $ TypeMismatchError
{ typeExpected = valueType l
, typeActual = valueType r
}