{-# LANGUAGE TypeFamilies #-}
module Toml.ToValue (
    ToValue(..),
    
    ToTable(..),
    ToKey(..),
    defaultTableToValue,
    table,
    (.=),
    ) where
import Data.Foldable (toList)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.List.NonEmpty (NonEmpty)
import Data.List.NonEmpty qualified as NonEmpty
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Ratio (Ratio)
import Data.Sequence (Seq)
import Data.Text qualified
import Data.Text.Lazy qualified
import Data.Time (Day, TimeOfDay, LocalTime, ZonedTime)
import Data.Word (Word8, Word16, Word32, Word64)
import Numeric.Natural (Natural)
import Toml.Value (Value(..), Table)
table :: [(String, Value)] -> Table
table :: [(String, Value)] -> Table
table = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
{-# INLINE table #-}
(.=) :: ToValue a => String -> a -> (String, Value)
String
k .= :: forall a. ToValue a => String -> a -> (String, Value)
.= a
v = (String
k, forall a. ToValue a => a -> Value
toValue a
v)
class ToValue a where
    
    toValue :: a -> Value
    
    
    
    toValueList :: [a] -> Value
    toValueList = [Value] -> Value
Array forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. ToValue a => a -> Value
toValue
class ToValue a => ToTable a where
    
    toTable :: a -> Table
instance (ToKey k, ToValue v) => ToTable (Map k v) where
    toTable :: Map k v -> Table
toTable Map k v
m = [(String, Value)] -> Table
table [(forall a. ToKey a => a -> String
toKey k
k, forall a. ToValue a => a -> Value
toValue v
v) | (k
k,v
v) <- forall k a. Map k a -> [(k, a)]
Map.assocs Map k v
m]
instance (ToKey k, ToValue v) => ToValue (Map k v) where
    toValue :: Map k v -> Value
toValue = forall a. ToTable a => a -> Value
defaultTableToValue
class ToKey a where
    toKey :: a -> String
instance Char ~ a => ToKey [a] where
    toKey :: [a] -> String
toKey = forall a. a -> a
id
instance ToKey Data.Text.Text where
    toKey :: Text -> String
toKey =Text -> String
Data.Text.unpack
instance ToKey Data.Text.Lazy.Text where
    toKey :: Text -> String
toKey = Text -> String
Data.Text.Lazy.unpack
defaultTableToValue :: ToTable a => a -> Value
defaultTableToValue :: forall a. ToTable a => a -> Value
defaultTableToValue = Table -> Value
Table forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToTable a => a -> Table
toTable
instance ToValue Value where
    toValue :: Value -> Value
toValue = forall a. a -> a
id
instance ToValue Char where
    toValue :: Char -> Value
toValue Char
x = String -> Value
String [Char
x]
    toValueList :: String -> Value
toValueList = String -> Value
String
instance ToValue Data.Text.Text where
    toValue :: Text -> Value
toValue = forall a. ToValue a => a -> Value
toValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Data.Text.unpack
instance ToValue Data.Text.Lazy.Text where
    toValue :: Text -> Value
toValue = forall a. ToValue a => a -> Value
toValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Data.Text.Lazy.unpack
instance ToValue a => ToValue [a] where
    toValue :: [a] -> Value
toValue = forall a. ToValue a => [a] -> Value
toValueList
instance ToValue a => ToValue (NonEmpty a) where
    toValue :: NonEmpty a -> Value
toValue = forall a. ToValue a => a -> Value
toValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> [a]
NonEmpty.toList
instance ToValue a => ToValue (Seq a) where
    toValue :: Seq a -> Value
toValue = forall a. ToValue a => a -> Value
toValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
instance Integral a => ToValue (Ratio a) where
    toValue :: Ratio a -> Value
toValue = Double -> Value
Float forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Real a, Fractional b) => a -> b
realToFrac
instance ToValue Double    where toValue :: Double -> Value
toValue = Double -> Value
Float
instance ToValue Float     where toValue :: Float -> Value
toValue = Double -> Value
Float forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Real a, Fractional b) => a -> b
realToFrac
instance ToValue Bool      where toValue :: Bool -> Value
toValue = Bool -> Value
Bool
instance ToValue TimeOfDay where toValue :: TimeOfDay -> Value
toValue = TimeOfDay -> Value
TimeOfDay
instance ToValue LocalTime where toValue :: LocalTime -> Value
toValue = LocalTime -> Value
LocalTime
instance ToValue ZonedTime where toValue :: ZonedTime -> Value
toValue = ZonedTime -> Value
ZonedTime
instance ToValue Day       where toValue :: Day -> Value
toValue = Day -> Value
Day
instance ToValue Integer   where toValue :: Integer -> Value
toValue = Integer -> Value
Integer
instance ToValue Natural   where toValue :: Natural -> Value
toValue = Integer -> Value
Integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance ToValue Int       where toValue :: Int -> Value
toValue = Integer -> Value
Integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance ToValue Int8      where toValue :: Int8 -> Value
toValue = Integer -> Value
Integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance ToValue Int16     where toValue :: Int16 -> Value
toValue = Integer -> Value
Integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance ToValue Int32     where toValue :: Int32 -> Value
toValue = Integer -> Value
Integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance ToValue Int64     where toValue :: Int64 -> Value
toValue = Integer -> Value
Integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance ToValue Word      where toValue :: Word -> Value
toValue = Integer -> Value
Integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance ToValue Word8     where toValue :: Word8 -> Value
toValue = Integer -> Value
Integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance ToValue Word16    where toValue :: Word16 -> Value
toValue = Integer -> Value
Integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance ToValue Word32    where toValue :: Word32 -> Value
toValue = Integer -> Value
Integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance ToValue Word64    where toValue :: Word64 -> Value
toValue = Integer -> Value
Integer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral