module Cfg.Deriving.Value where
import Cfg.Parser
import Cfg.Parser.Value
import Data.Coerce
import GHC.Generics
newtype Value a = Value {forall a. Value a -> a
unValue :: a}
instance (Generic a) => Generic (Value a) where
  type Rep (Value a) = Rep a
  to :: forall x. Rep (Value a) x -> Value a
to = a -> Value a
forall a. a -> Value a
Value (a -> Value a) -> (Rep a x -> a) -> Rep a x -> Value a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rep a x -> a
forall a x. Generic a => Rep a x -> a
forall x. Rep a x -> a
to
  from :: forall x. Value a -> Rep (Value a) x
from (Value a
x) = a -> Rep a x
forall x. a -> Rep a x
forall a x. Generic a => a -> Rep a x
from a
x
instance (Generic a, GValueParser (Rep a)) => ValueParser (Value a) where
  parser :: Parser (Value a)
parser = Parser a -> Parser (Value a)
forall a b. Coercible a b => a -> b
coerce (Parser a -> Parser (Value a))
-> (Parser a -> Parser (Value a)) -> Parser a -> Parser (Value a)
forall a. a -> a -> a
`asTypeOf` (a -> Value a) -> Parser a -> Parser (Value a)
forall a b.
(a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Value a
forall a. a -> Value a
Value (Parser a -> Parser (Value a)) -> Parser a -> Parser (Value a)
forall a b. (a -> b) -> a -> b
$ forall a. (Generic a, GValueParser (Rep a)) => Parser a
defaultValueParser @a
instance (Generic a, GValueParser (Rep a)) => ConfigParser (Value a)