#ifdef DEFAULT_SIGNATURES
#endif
module Data.SafeCopy.SafeCopy where
import Data.Serialize
import Control.Monad
import Data.Int (Int32)
import Data.List
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
errorTypeName _ = "<unkown type>"
#ifdef DEFAULT_SIGNATURES
default getCopy :: Serialize a => Contained (Get a)
getCopy = contain get
default putCopy :: Serialize a => a -> Contained Put
putCopy = contain . put
#endif
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
= checkConsistency 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 :: (SafeCopy a, Migrate a, Migrate (Reverse a)) => Kind a
extended_extension = Extended extension
extended_base :: (Migrate (Reverse a)) => Kind a
extended_base = Extended base
extension :: (SafeCopy a, 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 (ab)
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, Monad m) => Proxy a -> m b -> m b
checkConsistency proxy ks
= case consistentFromProxy proxy of
NotConsistent msg -> fail msg
Consistent -> ks
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 a, 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