{-# LANGUAGE ExistentialQuantification, RecordWildCards, ScopedTypeVariables #-}
{-# LANGUAGE ConstraintKinds, GeneralizedNewtypeDeriving #-}
module Development.Shake.Internal.Value(
    QTypeRep(..),
    Value, newValue, fromValue,
    Key, newKey, fromKey, typeKey,
    ShakeValue
    ) where
import Development.Shake.Classes
import Development.Shake.Internal.Errors
import Data.Typeable.Extra
import Numeric
import Data.Bits
import Unsafe.Coerce
newtype QTypeRep = QTypeRep {fromQTypeRep :: TypeRep}
    deriving (Eq,Hashable)
instance NFData QTypeRep where
    
    
    rnf (QTypeRep x) = x `seq` ()
instance Show QTypeRep where
    show (QTypeRep x) = show x ++ " {" ++ showHex (abs $ hashWithSalt 0 x) "" ++ "}"
type ShakeValue a = (Show a, Typeable a, Eq a, Hashable a, Binary a, NFData a)
data Key = forall a . Key
    {keyType :: TypeRep
    ,keyShow :: a -> String
    ,keyRnf :: a -> ()
    ,keyEq :: a -> a -> Bool
    ,keyHash :: Int -> a -> Int
    ,keyValue :: a
    }
data Value = forall a . Value
    {valueType :: TypeRep
    ,valueShow :: a -> String
    ,valueRnf :: a -> ()
    ,valueValue :: a
    }
newKey :: forall a . ShakeValue a => a -> Key
newKey = Key (typeRep (Proxy :: Proxy a)) show rnf (==) hashWithSalt
newValue :: forall a . (Typeable a, Show a, NFData a) => a -> Value
newValue = Value (typeRep (Proxy :: Proxy a)) show rnf
typeKey :: Key -> TypeRep
typeKey Key{..} = keyType
fromKey :: forall a . Typeable a => Key -> a
fromKey Key{..}
    | keyType == resType = unsafeCoerce keyValue
    | otherwise = errorInternal $ "fromKey, bad cast, have " ++ show keyType ++ ", wanted " ++ show resType
    where resType = typeRep (Proxy :: Proxy a)
fromValue :: forall a . Typeable a => Value -> a
fromValue Value{..}
    | valueType == resType = unsafeCoerce valueValue
    | otherwise = errorInternal $ "fromValue, bad cast, have " ++ show valueType ++ ", wanted " ++ show resType
    where resType = typeRep (Proxy :: Proxy a)
instance Show Key where
    show Key{..} = keyShow keyValue
instance Show Value where
    show Value{..} = valueShow valueValue
instance NFData Key where
    rnf Key{..} = keyRnf keyValue
instance NFData Value where
    rnf Value{..} = valueRnf valueValue
instance Hashable Key where
    hashWithSalt salt Key{..} = hashWithSalt salt keyType `xor` keyHash salt keyValue
instance Eq Key where
    Key{keyType=at,keyValue=a,keyEq=eq} == Key{keyType=bt,keyValue=b}
        | at /= bt = False
        | otherwise = eq a (unsafeCoerce b)