{-# LANGUAGE GADTs #-}
module Toml.Type.UValue
( UValue (..)
, typeCheck
) where
import Data.Text (Text)
import Data.Time (Day, LocalTime, TimeOfDay, ZonedTime, zonedTimeToUTC)
import Data.Type.Equality ((:~:) (..))
import Toml.Type.AnyValue (AnyValue (..))
import Toml.Type.Value (TypeMismatchError, Value (..), sameValue)
data UValue
= UBool !Bool
| UInteger !Integer
| UDouble !Double
| UText !Text
| UZoned !ZonedTime
| ULocal !LocalTime
| UDay !Day
| UHours !TimeOfDay
| UArray ![UValue]
deriving stock (Int -> UValue -> ShowS
[UValue] -> ShowS
UValue -> String
(Int -> UValue -> ShowS)
-> (UValue -> String) -> ([UValue] -> ShowS) -> Show UValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UValue] -> ShowS
$cshowList :: [UValue] -> ShowS
show :: UValue -> String
$cshow :: UValue -> String
showsPrec :: Int -> UValue -> ShowS
$cshowsPrec :: Int -> UValue -> ShowS
Show)
instance Eq UValue where
(UBool b1 :: Bool
b1) == :: UValue -> UValue -> Bool
== (UBool b2 :: Bool
b2) = Bool
b1 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
b2
(UInteger i1 :: Integer
i1) == (UInteger i2 :: Integer
i2) = Integer
i1 Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
i2
(UDouble f1 :: Double
f1) == (UDouble f2 :: Double
f2)
| Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
f1 Bool -> Bool -> Bool
&& Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
f2 = Bool
True
| Bool
otherwise = Double
f1 Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
f2
(UText s1 :: Text
s1) == (UText s2 :: Text
s2) = Text
s1 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
s2
(UZoned a :: ZonedTime
a) == (UZoned b :: ZonedTime
b) = ZonedTime -> UTCTime
zonedTimeToUTC ZonedTime
a UTCTime -> UTCTime -> Bool
forall a. Eq a => a -> a -> Bool
== ZonedTime -> UTCTime
zonedTimeToUTC ZonedTime
b
(ULocal a :: LocalTime
a) == (ULocal b :: LocalTime
b) = LocalTime
a LocalTime -> LocalTime -> Bool
forall a. Eq a => a -> a -> Bool
== LocalTime
b
(UDay a :: Day
a) == (UDay b :: Day
b) = Day
a Day -> Day -> Bool
forall a. Eq a => a -> a -> Bool
== Day
b
(UHours a :: TimeOfDay
a) == (UHours b :: TimeOfDay
b) = TimeOfDay
a TimeOfDay -> TimeOfDay -> Bool
forall a. Eq a => a -> a -> Bool
== TimeOfDay
b
(UArray a1 :: [UValue]
a1) == (UArray a2 :: [UValue]
a2) = [UValue]
a1 [UValue] -> [UValue] -> Bool
forall a. Eq a => a -> a -> Bool
== [UValue]
a2
_ == _ = Bool
False
typeCheck :: UValue -> Either TypeMismatchError AnyValue
typeCheck :: UValue -> Either TypeMismatchError AnyValue
typeCheck (UBool b :: Bool
b) = Value 'TBool -> Either TypeMismatchError AnyValue
forall (t :: TValue) l. Value t -> Either l AnyValue
rightAny (Value 'TBool -> Either TypeMismatchError AnyValue)
-> Value 'TBool -> Either TypeMismatchError AnyValue
forall a b. (a -> b) -> a -> b
$ Bool -> Value 'TBool
Bool Bool
b
typeCheck (UInteger n :: Integer
n) = Value 'TInteger -> Either TypeMismatchError AnyValue
forall (t :: TValue) l. Value t -> Either l AnyValue
rightAny (Value 'TInteger -> Either TypeMismatchError AnyValue)
-> Value 'TInteger -> Either TypeMismatchError AnyValue
forall a b. (a -> b) -> a -> b
$ Integer -> Value 'TInteger
Integer Integer
n
typeCheck (UDouble f :: Double
f) = Value 'TDouble -> Either TypeMismatchError AnyValue
forall (t :: TValue) l. Value t -> Either l AnyValue
rightAny (Value 'TDouble -> Either TypeMismatchError AnyValue)
-> Value 'TDouble -> Either TypeMismatchError AnyValue
forall a b. (a -> b) -> a -> b
$ Double -> Value 'TDouble
Double Double
f
typeCheck (UText s :: Text
s) = Value 'TText -> Either TypeMismatchError AnyValue
forall (t :: TValue) l. Value t -> Either l AnyValue
rightAny (Value 'TText -> Either TypeMismatchError AnyValue)
-> Value 'TText -> Either TypeMismatchError AnyValue
forall a b. (a -> b) -> a -> b
$ Text -> Value 'TText
Text Text
s
typeCheck (UZoned d :: ZonedTime
d) = Value 'TZoned -> Either TypeMismatchError AnyValue
forall (t :: TValue) l. Value t -> Either l AnyValue
rightAny (Value 'TZoned -> Either TypeMismatchError AnyValue)
-> Value 'TZoned -> Either TypeMismatchError AnyValue
forall a b. (a -> b) -> a -> b
$ ZonedTime -> Value 'TZoned
Zoned ZonedTime
d
typeCheck (ULocal d :: LocalTime
d) = Value 'TLocal -> Either TypeMismatchError AnyValue
forall (t :: TValue) l. Value t -> Either l AnyValue
rightAny (Value 'TLocal -> Either TypeMismatchError AnyValue)
-> Value 'TLocal -> Either TypeMismatchError AnyValue
forall a b. (a -> b) -> a -> b
$ LocalTime -> Value 'TLocal
Local LocalTime
d
typeCheck (UDay d :: Day
d) = Value 'TDay -> Either TypeMismatchError AnyValue
forall (t :: TValue) l. Value t -> Either l AnyValue
rightAny (Value 'TDay -> Either TypeMismatchError AnyValue)
-> Value 'TDay -> Either TypeMismatchError AnyValue
forall a b. (a -> b) -> a -> b
$ Day -> Value 'TDay
Day Day
d
typeCheck (UHours d :: TimeOfDay
d) = Value 'THours -> Either TypeMismatchError AnyValue
forall (t :: TValue) l. Value t -> Either l AnyValue
rightAny (Value 'THours -> Either TypeMismatchError AnyValue)
-> Value 'THours -> Either TypeMismatchError AnyValue
forall a b. (a -> b) -> a -> b
$ TimeOfDay -> Value 'THours
Hours TimeOfDay
d
typeCheck (UArray a :: [UValue]
a) = case [UValue]
a of
[] -> Value 'TArray -> Either TypeMismatchError AnyValue
forall (t :: TValue) l. Value t -> Either l AnyValue
rightAny (Value 'TArray -> Either TypeMismatchError AnyValue)
-> Value 'TArray -> Either TypeMismatchError AnyValue
forall a b. (a -> b) -> a -> b
$ [Value Any] -> Value 'TArray
forall (t :: TValue). [Value t] -> Value 'TArray
Array []
x :: UValue
x:xs :: [UValue]
xs -> do
AnyValue v :: Value t
v <- UValue -> Either TypeMismatchError AnyValue
typeCheck UValue
x
Value 'TArray -> AnyValue
forall (t :: TValue). Value t -> AnyValue
AnyValue (Value 'TArray -> AnyValue)
-> ([Value t] -> Value 'TArray) -> [Value t] -> AnyValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value t] -> Value 'TArray
forall (t :: TValue). [Value t] -> Value 'TArray
Array ([Value t] -> AnyValue)
-> Either TypeMismatchError [Value t]
-> Either TypeMismatchError AnyValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value t -> [UValue] -> Either TypeMismatchError [Value t]
forall (t :: TValue).
Value t -> [UValue] -> Either TypeMismatchError [Value t]
checkElem Value t
v [UValue]
xs
where
checkElem :: Value t -> [UValue] -> Either TypeMismatchError [Value t]
checkElem :: Value t -> [UValue] -> Either TypeMismatchError [Value t]
checkElem v :: Value t
v [] = [Value t] -> Either TypeMismatchError [Value t]
forall a b. b -> Either a b
Right [Value t
v]
checkElem v :: Value t
v (x :: UValue
x:xs :: [UValue]
xs) = do
AnyValue vx :: Value t
vx <- UValue -> Either TypeMismatchError AnyValue
typeCheck UValue
x
t :~: t
Refl <- Value t -> Value t -> Either TypeMismatchError (t :~: t)
forall (a :: TValue) (b :: TValue).
Value a -> Value b -> Either TypeMismatchError (a :~: b)
sameValue Value t
v Value t
vx
(Value t
v Value t -> [Value t] -> [Value t]
forall a. a -> [a] -> [a]
:) ([Value t] -> [Value t])
-> Either TypeMismatchError [Value t]
-> Either TypeMismatchError [Value t]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value t -> [UValue] -> Either TypeMismatchError [Value t]
forall (t :: TValue).
Value t -> [UValue] -> Either TypeMismatchError [Value t]
checkElem Value t
vx [UValue]
xs
rightAny :: Value t -> Either l AnyValue
rightAny :: Value t -> Either l AnyValue
rightAny = AnyValue -> Either l AnyValue
forall a b. b -> Either a b
Right (AnyValue -> Either l AnyValue)
-> (Value t -> AnyValue) -> Value t -> Either l AnyValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value t -> AnyValue
forall (t :: TValue). Value t -> AnyValue
AnyValue