{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Data.SafeCopy.SafeCopy where
import Control.Monad
import Control.Monad.Trans.Class (lift)
import qualified Control.Monad.Fail as Fail
import Control.Monad.Trans.State as State (evalStateT, modify, StateT)
import qualified Control.Monad.Trans.State as State (get)
import Control.Monad.Trans.RWS as RWS (evalRWST, modify, RWST, tell)
import qualified Control.Monad.Trans.RWS as RWS (get)
import Data.Bits (shiftR)
import Data.Int (Int32)
import Data.List
import Data.Map as Map (Map, lookup, insert)
import Data.Serialize
import Data.Set as Set (insert, member, Set)
import Data.Typeable (Typeable, TypeRep, typeOf, typeRep)
import Data.Word (Word8)
import GHC.Generics
import Generic.Data as G (Constructors, gconIndex, gconNum)
import Unsafe.Coerce (unsafeCoerce)
class SafeCopy (MigrateFrom a) => Migrate a where
type MigrateFrom a
migrate :: MigrateFrom a -> a
newtype Reverse a = Reverse { unReverse :: a }
data Kind a where
Primitive :: Kind a
Base :: Kind a
Extends :: (Migrate a) => Proxy (MigrateFrom a) -> Kind a
Extended :: (Migrate (Reverse a)) => Kind a -> Kind a
isPrimitive :: Kind a -> Bool
isPrimitive Primitive = True
isPrimitive _ = False
newtype Prim a = Prim { getPrimitive :: a }
class SafeCopy a where
version :: Version a
version = Version 0
kind :: Kind a
kind = Base
getCopy :: Contained (Get a)
putCopy :: a -> Contained Put
internalConsistency :: Consistency a
internalConsistency = computeConsistency Proxy
objectProfile :: Profile a
objectProfile = mkProfile Proxy
errorTypeName :: Proxy a -> String
default errorTypeName :: Typeable a => Proxy a -> String
errorTypeName _ = show (typeRep (Proxy @a))
default putCopy :: (GPutCopy (Rep a) DatatypeInfo, Constructors a) => a -> Contained Put
putCopy a = (contain . gputCopy (ConstructorInfo (fromIntegral (gconNum @a)) (fromIntegral (gconIndex a))) . from) a
default getCopy :: (GGetCopy (Rep a) DatatypeInfo, Constructors a) => Contained (Get a)
getCopy = contain (to <$> ggetCopy (ConstructorCount (fromIntegral (gconNum @a))))
class GPutCopy f p where
gputCopy :: p -> f p -> Put
instance GPutCopy a p => GPutCopy (M1 D c a) p where
gputCopy p (M1 a) = gputCopy p a
{-# INLINE gputCopy #-}
instance (GPutCopy f p, GPutCopy g p) => GPutCopy (f :+: g) p where
gputCopy p (L1 x) = gputCopy @f p x
gputCopy p (R1 x) = gputCopy @g p x
{-# INLINE gputCopy #-}
type SafeCopy' a = (SafeCopy a, Typeable a)
instance (GPutFields a p, p ~ DatatypeInfo) => GPutCopy (M1 C c a) p where
gputCopy p (M1 x) =
(when (_size p >= 2) (putWord8 (fromIntegral (_code p)))) *>
(do putter <- (mconcat . snd) <$> (evalRWST (gputFields p x) () mempty)
putter)
{-# INLINE gputCopy #-}
class GPutFields f p where
gputFields :: p -> f p -> RWST () [Put] (Set TypeRep) PutM ()
instance (GPutFields f p, GPutFields g p) => GPutFields (f :*: g) p where
gputFields p (a :*: b) = gputFields p a >> gputFields p b
{-# INLINE gputFields #-}
instance GPutFields f p => GPutFields (M1 S c f) p where
gputFields p (M1 a) = gputFields p a
{-# INLINE gputFields #-}
instance SafeCopy' a => GPutFields (K1 R a) p where
gputFields _ (K1 a) = do
getSafePutGeneric putCopy a
{-# INLINE gputFields #-}
instance GPutFields U1 p where
gputFields _ _ =
return ()
{-# INLINE gputFields #-}
instance GPutFields V1 p where
gputFields _ _ = undefined
{-# INLINE gputFields #-}
class GGetCopy f p where
ggetCopy :: p -> Get (f a)
instance (GGetCopy f p, p ~ DatatypeInfo) => GGetCopy (M1 D d f) p where
ggetCopy p
| _size p >= 2 = do
!code <- getWord8
M1 <$> ggetCopy (ConstructorInfo (_size p) code)
| otherwise = M1 <$> ggetCopy (ConstructorInfo (_size p) 0)
{-# INLINE ggetCopy #-}
instance (GGetCopy f p, GGetCopy g p, p ~ DatatypeInfo) => GGetCopy (f :+: g) p where
ggetCopy p = do
let sizeL = _size p `shiftR` 1
sizeR = _size p - sizeL
case _code p < sizeL of
True -> L1 <$> ggetCopy @f (ConstructorInfo sizeL (_code p))
False -> R1 <$> ggetCopy @g (ConstructorInfo sizeR (_code p - sizeL))
{-# INLINE ggetCopy #-}
instance GGetFields f p => GGetCopy (M1 C c f) p where
ggetCopy p = do
M1 <$> join (evalStateT (ggetFields p) mempty)
{-# INLINE ggetCopy #-}
class GGetFields f p where
ggetFields :: p -> StateT (Map TypeRep Int32) Get (Get (f a))
instance (GGetFields f p, GGetFields g p) => GGetFields (f :*: g) p where
ggetFields p = do
fgetter <- ggetFields @f p
ggetter <- ggetFields @g p
return ((:*:) <$> fgetter <*> ggetter)
{-# INLINE ggetFields #-}
instance GGetFields f p => GGetFields (M1 S c f) p where
ggetFields p = do
getter <- ggetFields p
return (M1 <$> getter)
{-# INLINE ggetFields #-}
instance SafeCopy' a => GGetFields (K1 R a) p where
ggetFields _ = do
getter <- getSafeGetGeneric
return (K1 <$> getter)
{-# INLINE ggetFields #-}
instance GGetFields U1 p where
ggetFields _p = pure (pure U1)
{-# INLINE ggetFields #-}
instance GGetFields V1 p where
ggetFields _p = undefined
{-# INLINE ggetFields #-}
data DatatypeInfo =
ConstructorCount {_size :: Word8}
| ConstructorInfo {_size :: Word8, _code :: Word8}
deriving Show
getSafeGetGeneric ::
forall a. SafeCopy' a
=> StateT (Map TypeRep Int32) Get (Get a)
getSafeGetGeneric
= checkConsistency proxy $
case kindFromProxy proxy of
Primitive -> return $ unsafeUnPack getCopy
a_kind -> do let rep = typeRep (Proxy :: Proxy a)
reps <- State.get
v <- maybe (lift get) pure (Map.lookup rep reps)
case constructGetterFromVersion (unsafeCoerce v) a_kind of
Right getter -> State.modify (Map.insert rep v) >> return getter
Left msg -> fail msg
where proxy = Proxy :: Proxy a
getSafePutGeneric ::
forall a. SafeCopy' a
=> (a -> Contained Put)
-> a
-> RWST () [Put] (Set TypeRep) PutM ()
getSafePutGeneric cput a
= unpureCheckConsistency proxy $
case kindFromProxy proxy of
Primitive -> tell [unsafeUnPack (cput $ asProxyType a proxy)]
_ -> do reps <- RWS.get
let typ = typeOf a
when (not (member typ reps)) $ do
lift (put (versionFromProxy proxy))
RWS.modify (Set.insert typ)
tell [unsafeUnPack (cput $ asProxyType a proxy)]
where proxy = Proxy :: Proxy a
type GSafeCopy a = (SafeCopy' a, Generic a, GPutCopy (Rep a) DatatypeInfo, Constructors a)
safePutGeneric :: forall a. GSafeCopy a => a -> Put
safePutGeneric a = do
putter <- (mconcat . snd) <$> evalRWST (getSafePutGeneric putCopyDefault a) () mempty
putter
putCopyDefault :: forall a. GSafeCopy a => a -> Contained Put
putCopyDefault a = (contain . gputCopy (ConstructorInfo (fromIntegral (gconNum @a)) (fromIntegral (gconIndex a))) . from) a
constructGetterFromVersion :: SafeCopy a => Version a -> Kind a -> Either String (Get a)
constructGetterFromVersion diskVersion orig_kind =
worker False diskVersion orig_kind
where
worker :: forall a. SafeCopy a => Bool -> Version a -> Kind a -> Either String (Get a)
worker fwd thisVersion thisKind
| version == thisVersion = return $ unsafeUnPack getCopy
| otherwise =
case thisKind of
Primitive -> Left $ errorMsg thisKind "Cannot migrate from primitive types."
Base -> Left $ errorMsg thisKind versionNotFound
Extends b_proxy -> do
previousGetter <- worker fwd (castVersion diskVersion) (kindFromProxy b_proxy)
return $ fmap migrate previousGetter
Extended{} | fwd -> Left $ errorMsg thisKind versionNotFound
Extended a_kind -> do
let rev_proxy :: Proxy (MigrateFrom (Reverse a))
rev_proxy = Proxy
forwardGetter :: Either String (Get a)
forwardGetter = fmap (fmap (unReverse . migrate)) $ worker True (castVersion thisVersion) (kindFromProxy rev_proxy)
previousGetter :: Either String (Get a)
previousGetter = worker fwd (castVersion thisVersion) a_kind
case forwardGetter of
Left{} -> previousGetter
Right val -> Right val
versionNotFound = "Cannot find getter associated with this version number: " ++ show diskVersion
errorMsg fail_kind msg =
concat
[ "safecopy: "
, errorTypeName (proxyFromKind fail_kind)
, ": "
, msg
]
safeGet :: SafeCopy a => Get a
safeGet
= join getSafeGet
getSafeGet :: forall a. SafeCopy a => Get (Get a)
getSafeGet
= checkConsistency proxy $
case kindFromProxy proxy of
Primitive -> return $ unsafeUnPack getCopy
a_kind -> do v <- get
case constructGetterFromVersion v a_kind of
Right getter -> return getter
Left msg -> fail msg
where proxy = Proxy :: Proxy a
safePut :: SafeCopy a => a -> Put
safePut a
= do putter <- getSafePut
putter a
getSafePut :: forall a. SafeCopy a => PutM (a -> Put)
getSafePut
= unpureCheckConsistency proxy $
case kindFromProxy proxy of
Primitive -> return $ \a -> unsafeUnPack (putCopy $ asProxyType a proxy)
_ -> do put (versionFromProxy proxy)
return $ \a -> unsafeUnPack (putCopy $ asProxyType a proxy)
where proxy = Proxy :: Proxy a
extended_extension :: (Migrate a, Migrate (Reverse a)) => Kind a
extended_extension = Extended extension
extended_base :: (Migrate (Reverse a)) => Kind a
extended_base = Extended base
extension :: Migrate a => Kind a
extension = Extends Proxy
base :: Kind a
base = Base
primitive :: Kind a
primitive = Primitive
newtype Version a = Version {unVersion :: Int32} deriving (Read,Show,Eq)
castVersion :: Version a -> Version b
castVersion (Version a) = Version a
instance Num (Version a) where
Version a + Version b = Version (a+b)
Version a - Version b = Version (a-b)
Version a * Version b = Version (a*b)
negate (Version a) = Version (negate a)
abs (Version a) = Version (abs a)
signum (Version a) = Version (signum a)
fromInteger i = Version (fromInteger i)
instance Serialize (Version a) where
get = liftM Version get
put = put . unVersion
newtype Contained a = Contained {unsafeUnPack :: a}
contain :: a -> Contained a
contain = Contained
data Profile a =
PrimitiveProfile |
InvalidProfile String |
Profile
{ profileCurrentVersion :: Int32
, profileSupportedVersions :: [Int32]
} deriving (Show)
mkProfile :: SafeCopy a => Proxy a -> Profile a
mkProfile a_proxy =
case computeConsistency a_proxy of
NotConsistent msg -> InvalidProfile msg
Consistent | isPrimitive (kindFromProxy a_proxy) -> PrimitiveProfile
Consistent ->
Profile{ profileCurrentVersion = unVersion (versionFromProxy a_proxy)
, profileSupportedVersions = availableVersions a_proxy
}
data Consistency a = Consistent | NotConsistent String
availableVersions :: SafeCopy a => Proxy a -> [Int32]
availableVersions a_proxy =
worker True (kindFromProxy a_proxy)
where
worker :: SafeCopy b => Bool -> Kind b -> [Int32]
worker fwd b_kind =
case b_kind of
Primitive -> []
Base -> [unVersion (versionFromKind b_kind)]
Extends b_proxy -> unVersion (versionFromKind b_kind) : worker False (kindFromProxy b_proxy)
Extended sub_kind | fwd -> worker False (getForwardKind sub_kind)
Extended sub_kind -> worker False sub_kind
getForwardKind :: (Migrate (Reverse a)) => Kind a -> Kind (MigrateFrom (Reverse a))
getForwardKind _ = kind
validChain :: SafeCopy a => Proxy a -> Bool
validChain a_proxy =
worker (kindFromProxy a_proxy)
where
worker Primitive = True
worker Base = True
worker (Extends b_proxy) = check (kindFromProxy b_proxy)
worker (Extended a_kind) = worker a_kind
check :: SafeCopy b => Kind b -> Bool
check b_kind
= case b_kind of
Primitive -> False
Base -> True
Extends c_proxy -> check (kindFromProxy c_proxy)
Extended sub_kind -> check sub_kind
checkConsistency :: (SafeCopy a, Fail.MonadFail m) => Proxy a -> m b -> m b
checkConsistency proxy ks
= case consistentFromProxy proxy of
NotConsistent msg -> Fail.fail msg
Consistent -> ks
unpureCheckConsistency :: SafeCopy a => Proxy a -> b -> b
unpureCheckConsistency proxy ks
= case consistentFromProxy proxy of
NotConsistent msg -> error $ "unpureCheckConsistency: " ++ msg
Consistent -> ks
{-# INLINE computeConsistency #-}
computeConsistency :: SafeCopy a => Proxy a -> Consistency a
computeConsistency proxy
| isObviouslyConsistent (kindFromProxy proxy)
= Consistent
| versions /= nub versions
= NotConsistent $ "Duplicate version tags: " ++ show versions
| not (validChain proxy)
= NotConsistent "Primitive types cannot be extended as they have no version tag."
| otherwise
= Consistent
where versions = availableVersions proxy
isObviouslyConsistent :: Kind a -> Bool
isObviouslyConsistent Primitive = True
isObviouslyConsistent Base = True
isObviouslyConsistent _ = False
proxyFromConsistency :: Consistency a -> Proxy a
proxyFromConsistency _ = Proxy
proxyFromKind :: Kind a -> Proxy a
proxyFromKind _ = Proxy
consistentFromProxy :: SafeCopy a => Proxy a -> Consistency a
consistentFromProxy _ = internalConsistency
versionFromProxy :: SafeCopy a => Proxy a -> Version a
versionFromProxy _ = version
versionFromKind :: (SafeCopy a) => Kind a -> Version a
versionFromKind _ = version
versionFromReverseKind :: (SafeCopy (MigrateFrom (Reverse a))) => Kind a -> Version (MigrateFrom (Reverse a))
versionFromReverseKind _ = version
kindFromProxy :: SafeCopy a => Proxy a -> Kind a
kindFromProxy _ = kind
data Proxy a = Proxy
mkProxy :: a -> Proxy a
mkProxy _ = Proxy
asProxyType :: a -> Proxy a -> a
asProxyType a _ = a