{-# LANGUAGE TypeFamilies #-}
{-|
Module      : Toml.ToValue
Description : Automation for converting application values to TOML.
Copyright   : (c) Eric Mertens, 2023
License     : ISC
Maintainer  : emertens@gmail.com

The 'ToValue' class provides a conversion function from
application-specific to TOML values.

Because the top-level TOML document is always a table,
the 'ToTable' class is for types that specifically support
conversion from a 'Table'.

"Toml.ToValue.Generic" can be used to derive instances of 'ToTable'
automatically for record types.

-}
module Toml.ToValue (
    ToValue(..),

    -- * Table construction
    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)

-- | Build a 'Table' from a list of key-value pairs.
--
-- Use '.=' for a convenient way to build the pairs.
--
-- @since 1.3.0.0
table :: [(String, Value)] -> Table
table :: [(String, Value)] -> Table
table = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
{-# INLINE table #-}

-- | Convenience function for building key-value pairs while
-- constructing a 'Table'.
--
-- @'table' [a '.=' b, c '.=' d]@
(.=) :: 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 for types that can be embedded into 'Value'
class ToValue a where

    -- | Embed a single thing into a TOML value.
    toValue :: a -> Value

    -- | Helper for converting a list of things into a value. This is typically
    -- left to be defined by its default implementation and exists to help define
    -- the encoding for TOML arrays.
    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 for things that can be embedded into a TOML table.
--
-- Implement this for things that embed into a 'Table' and then
-- the 'ToValue' instance can be derived with 'defaultTableToValue'.
class ToValue a => ToTable a where

    -- | Convert a single value into a table
    toTable :: a -> Table

-- | @since 1.0.1.0
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]

-- | @since 1.0.1.0
instance (ToKey k, ToValue v) => ToValue (Map k v) where
    toValue :: Map k v -> Value
toValue = forall a. ToTable a => a -> Value
defaultTableToValue

-- | Convert to a table key
--
-- @since 1.3.0.0
class ToKey a where
    toKey :: a -> String

-- | toKey = id
--
-- @since 1.3.0.0
instance Char ~ a => ToKey [a] where
    toKey :: [a] -> String
toKey = forall a. a -> a
id

-- | toKey = unpack
--
-- @since 1.3.0.0
instance ToKey Data.Text.Text where
    toKey :: Text -> String
toKey =Text -> String
Data.Text.unpack

-- | toKey = unpack
--
-- @since 1.3.0.0
instance ToKey Data.Text.Lazy.Text where
    toKey :: Text -> String
toKey = Text -> String
Data.Text.Lazy.unpack

-- | Convenience function for building 'ToValue' instances.
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

-- | Identity function
instance ToValue Value where
    toValue :: Value -> Value
toValue = forall a. a -> a
id

-- | Single characters are encoded as singleton strings. Lists of characters
-- are encoded as a single string value.
instance ToValue Char where
    toValue :: Char -> Value
toValue Char
x = String -> Value
String [Char
x]
    toValueList :: String -> Value
toValueList = String -> Value
String

-- | Encodes as string literal
--
-- @since 1.2.1.0
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

-- | Encodes as string literal
--
-- @since 1.2.1.0
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

-- | This instance defers to the list element's 'toValueList' implementation.
instance ToValue a => ToValue [a] where
    toValue :: [a] -> Value
toValue = forall a. ToValue a => [a] -> Value
toValueList

-- | Converts to list and encodes that to value
--
-- @since 1.3.0.0
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

-- | Converts to list and encodes that to value
--
-- @since 1.3.0.0
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

-- | Converts to a 'Double'. This can overflow to infinity.
--
-- @since 1.3.0.0
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