#if __GLASGOW_HASKELL__ < 709
#define OVERLAP
#else
#define OVERLAP {-# OVERLAPPABLE #-}
#endif
module Pinch.Internal.Generic
    ( Field(..)
    , getField
    , putField
    , field
    , Enumeration(..)
    , enum
    , Void(..)
    ) where
#if __GLASGOW_HASKELL__ < 709
import Data.Foldable    (Foldable)
import Data.Monoid      (Monoid)
import Data.Traversable (Traversable)
#endif
import Control.Applicative
import Control.DeepSeq     (NFData)
import Data.Proxy          (Proxy (..))
import Data.Typeable       (Typeable)
import GHC.Generics
import GHC.TypeLits
import qualified Data.HashMap.Strict as HM
import Pinch.Internal.Pinchable
import Pinch.Internal.TType
import Pinch.Internal.Value     (Value (..))
class Combinable t where
    combine :: Value t -> Value t -> Value t
instance Combinable TStruct where
    combine (VStruct as) (VStruct bs) = VStruct $ as `HM.union` bs
instance OVERLAP GPinchable a => GPinchable (M1 i c a) where
    type GTag (M1 i c a) = GTag a
    gPinch = gPinch . unM1
    gUnpinch = fmap M1 . gUnpinch
instance (Datatype d, GPinchable a) => GPinchable (D1 d a) where
    type GTag (D1 d a) = GTag a
    gPinch = gPinch . unM1
    gUnpinch v =
        parserCatch (gUnpinch v)
            (\msg -> fail $ "Failed to read '" ++ name ++ "': " ++ msg)
            (return . M1)
      where
        name = datatypeName (undefined :: D1 d a b)
instance
  ( GPinchable a
  , GPinchable b
  , GTag a ~ GTag b
  , Combinable (GTag a)
  ) => GPinchable (a :*: b) where
    type GTag (a :*: b) = GTag a
    gPinch (a :*: b) = gPinch a `combine` gPinch b
    gUnpinch m = (:*:) <$> gUnpinch m <*> gUnpinch m
instance
  ( GPinchable a
  , GPinchable b
  , GTag a ~ GTag b
  ) => GPinchable (a :+: b) where
    type GTag (a :+: b) = GTag a
    gPinch (L1 a) = gPinch a
    gPinch (R1 b) = gPinch b
    gUnpinch m = L1 <$> gUnpinch m <|> R1 <$> gUnpinch m
newtype Field (n :: Nat) a = Field a
  deriving
    (Bounded, Eq, Enum, Foldable, Functor, Generic, Monoid, NFData, Ord, Show,
     Traversable, Typeable)
getField :: Field n a -> a
getField (Field a) = a
putField :: a -> Field n a
putField = Field
field :: Functor f => (a -> f b) -> Field n a -> f (Field n b)
field f (Field a) = Field <$> f a
instance OVERLAP (Pinchable a, KnownNat n)
  => GPinchable (K1 i (Field n a)) where
    type GTag (K1 i (Field n a)) = TStruct
    gPinch (K1 (Field a)) = struct [n .= a]
      where
        n = fromIntegral $ natVal (Proxy :: Proxy n)
    gUnpinch m = K1 . Field <$> m .: n
      where
        n = fromIntegral $ natVal (Proxy :: Proxy n)
instance
  (Pinchable a, KnownNat n)
  => GPinchable (K1 i (Field n (Maybe a))) where
    type GTag (K1 i (Field n (Maybe a))) = TStruct
    gPinch (K1 (Field a)) = struct [n ?= a]
      where
        n = fromIntegral $ natVal (Proxy :: Proxy n)
    gUnpinch m = K1 . Field <$> m .:? n
      where
        n = fromIntegral $ natVal (Proxy :: Proxy n)
data Enumeration (n :: Nat) = Enumeration
  deriving
    (Eq, Generic, Ord, Show, Typeable)
instance NFData (Enumeration n)
enum :: Enumeration n
enum = Enumeration
instance KnownNat n => GPinchable (K1 i (Enumeration n)) where
    type GTag (K1 i (Enumeration n)) = TEnum
    gPinch (K1 Enumeration) = VInt32 . fromIntegral $ natVal (Proxy :: Proxy n)
    gUnpinch (VInt32 i)
        | i == val  = return (K1 Enumeration)
        | otherwise = fail $ "Couldn't match enum value " ++ show i
      where
        val = fromIntegral $ natVal (Proxy :: Proxy n)
    gUnpinch x = fail $ "Failed to read enum. Got " ++ show x
data Void = Void
  deriving
    (Eq, Generic, Ord, Show, Typeable)
instance GPinchable (K1 i Void) where
    type GTag (K1 i Void) = TStruct
    gPinch (K1 Void) = struct []
    
    gUnpinch (VStruct m) | HM.null m = return $ K1 Void
    gUnpinch x = fail $
        "Failed to read response. Expected void, got: " ++ show x