{-# LANGUAGE FlexibleInstances, DeriveTraversable #-}
module Development.Shake.Internal.History.Serialise(
BuildTree(..),
WithTypeReps(..), withTypeReps,
WithKeys(..), withKeys, withIds, withoutKeys,
SendAllKeys(..), RecvAllKeys(..),
SendOneKey(..), RecvOneKey(..),
SendDownloadFiles(..),
SendUpload(..)
) where
import Development.Shake.Internal.History.Bloom
import General.Extra
import General.Binary
import General.Ids
import Data.List.Extra
import Development.Shake.Internal.Value
import Development.Shake.Internal.FileInfo
import Development.Shake.Internal.History.Types
import qualified Data.HashMap.Strict as Map
import Data.Semigroup
import Data.Typeable
import Prelude
data BuildTree key
= Depend [key] [([BS_Identity], BuildTree key)]
| Done BS_Store [(FilePath, FileSize, FileHash)]
instance BinaryEx (BuildTree Int) where
getEx :: ByteString -> BuildTree Int
getEx = ByteString -> BuildTree Int
forall a. HasCallStack => a
undefined
putEx :: BuildTree Int -> Builder
putEx = BuildTree Int -> Builder
forall a. HasCallStack => a
undefined
instance Eq key => Semigroup (BuildTree key) where
Depend [key]
ks1 [([ByteString], BuildTree key)]
vs1 <> :: BuildTree key -> BuildTree key -> BuildTree key
<> Depend [key]
ks2 [([ByteString], BuildTree key)]
vs2
| [key]
ks1 [key] -> [key] -> Bool
forall a. Eq a => a -> a -> Bool
== [key]
ks2 = [key] -> [([ByteString], BuildTree key)] -> BuildTree key
forall key.
[key] -> [([ByteString], BuildTree key)] -> BuildTree key
Depend [key]
ks1 ([([ByteString], BuildTree key)] -> BuildTree key)
-> [([ByteString], BuildTree key)] -> BuildTree key
forall a b. (a -> b) -> a -> b
$ (([ByteString], BuildTree key)
-> ([ByteString], BuildTree key) -> Ordering)
-> [([ByteString], BuildTree key)]
-> [([ByteString], BuildTree key)]
-> [([ByteString], BuildTree key)]
forall a. (a -> a -> Ordering) -> [a] -> [a] -> [a]
mergeBy ([ByteString], BuildTree key)
-> ([ByteString], BuildTree key) -> Ordering
forall a. HasCallStack => a
undefined [([ByteString], BuildTree key)]
vs1 [([ByteString], BuildTree key)]
vs2
| Bool
otherwise = [key] -> [([ByteString], BuildTree key)] -> BuildTree key
forall key.
[key] -> [([ByteString], BuildTree key)] -> BuildTree key
Depend [key]
ks2 [([ByteString], BuildTree key)]
vs2
x :: BuildTree key
x@Done{} <> BuildTree key
_ = BuildTree key
x
BuildTree key
_ <> y :: BuildTree key
y@Done{} = BuildTree key
y
instance Eq key => Monoid (BuildTree key) where
mempty :: BuildTree key
mempty = [key] -> [([ByteString], BuildTree key)] -> BuildTree key
forall key.
[key] -> [([ByteString], BuildTree key)] -> BuildTree key
Depend [] []
mappend :: BuildTree key -> BuildTree key -> BuildTree key
mappend = BuildTree key -> BuildTree key -> BuildTree key
forall a. Semigroup a => a -> a -> a
(<>)
data WithTypeReps a = WithTypeReps [BS_QTypeRep] a
instance BinaryEx a => BinaryEx (WithTypeReps a) where
putEx :: WithTypeReps a -> Builder
putEx = WithTypeReps a -> Builder
forall a. HasCallStack => a
undefined
getEx :: ByteString -> WithTypeReps a
getEx = ByteString -> WithTypeReps a
forall a. HasCallStack => a
undefined
withTypeReps :: Traversable f => f TypeRep -> WithTypeReps (f Int)
withTypeReps :: f TypeRep -> WithTypeReps (f Int)
withTypeReps = f TypeRep -> WithTypeReps (f Int)
forall a. HasCallStack => a
undefined
data WithKeys a = WithKeys [BS_Key] a
instance BinaryEx a => BinaryEx (WithKeys a) where
putEx :: WithKeys a -> Builder
putEx = WithKeys a -> Builder
forall a. HasCallStack => a
undefined
getEx :: ByteString -> WithKeys a
getEx = ByteString -> WithKeys a
forall a. HasCallStack => a
undefined
withKeys :: Traversable f => f Key -> WithKeys (f Int)
withKeys :: f Key -> WithKeys (f Int)
withKeys = f Key -> WithKeys (f Int)
forall a. HasCallStack => a
undefined
withIds :: Traversable f => (Id -> m Key) -> f Id -> m (WithKeys (f Int))
withIds :: (Id -> m Key) -> f Id -> m (WithKeys (f Int))
withIds = (Id -> m Key) -> f Id -> m (WithKeys (f Int))
forall a. HasCallStack => a
undefined
withoutKeys :: Map.HashMap TypeRep (BinaryOp Key) -> WithKeys (f Int) -> f Key
withoutKeys :: HashMap TypeRep (BinaryOp Key) -> WithKeys (f Int) -> f Key
withoutKeys = HashMap TypeRep (BinaryOp Key) -> WithKeys (f Int) -> f Key
forall a. HasCallStack => a
undefined
data SendAllKeys typ = SendAllKeys Ver [(typ, Ver)]
deriving (a -> SendAllKeys b -> SendAllKeys a
(a -> b) -> SendAllKeys a -> SendAllKeys b
(forall a b. (a -> b) -> SendAllKeys a -> SendAllKeys b)
-> (forall a b. a -> SendAllKeys b -> SendAllKeys a)
-> Functor SendAllKeys
forall a b. a -> SendAllKeys b -> SendAllKeys a
forall a b. (a -> b) -> SendAllKeys a -> SendAllKeys b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> SendAllKeys b -> SendAllKeys a
$c<$ :: forall a b. a -> SendAllKeys b -> SendAllKeys a
fmap :: (a -> b) -> SendAllKeys a -> SendAllKeys b
$cfmap :: forall a b. (a -> b) -> SendAllKeys a -> SendAllKeys b
Functor, SendAllKeys a -> Bool
(a -> m) -> SendAllKeys a -> m
(a -> b -> b) -> b -> SendAllKeys a -> b
(forall m. Monoid m => SendAllKeys m -> m)
-> (forall m a. Monoid m => (a -> m) -> SendAllKeys a -> m)
-> (forall m a. Monoid m => (a -> m) -> SendAllKeys a -> m)
-> (forall a b. (a -> b -> b) -> b -> SendAllKeys a -> b)
-> (forall a b. (a -> b -> b) -> b -> SendAllKeys a -> b)
-> (forall b a. (b -> a -> b) -> b -> SendAllKeys a -> b)
-> (forall b a. (b -> a -> b) -> b -> SendAllKeys a -> b)
-> (forall a. (a -> a -> a) -> SendAllKeys a -> a)
-> (forall a. (a -> a -> a) -> SendAllKeys a -> a)
-> (forall a. SendAllKeys a -> [a])
-> (forall a. SendAllKeys a -> Bool)
-> (forall a. SendAllKeys a -> Int)
-> (forall a. Eq a => a -> SendAllKeys a -> Bool)
-> (forall a. Ord a => SendAllKeys a -> a)
-> (forall a. Ord a => SendAllKeys a -> a)
-> (forall a. Num a => SendAllKeys a -> a)
-> (forall a. Num a => SendAllKeys a -> a)
-> Foldable SendAllKeys
forall a. Eq a => a -> SendAllKeys a -> Bool
forall a. Num a => SendAllKeys a -> a
forall a. Ord a => SendAllKeys a -> a
forall m. Monoid m => SendAllKeys m -> m
forall a. SendAllKeys a -> Bool
forall a. SendAllKeys a -> Int
forall a. SendAllKeys a -> [a]
forall a. (a -> a -> a) -> SendAllKeys a -> a
forall m a. Monoid m => (a -> m) -> SendAllKeys a -> m
forall b a. (b -> a -> b) -> b -> SendAllKeys a -> b
forall a b. (a -> b -> b) -> b -> SendAllKeys a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: SendAllKeys a -> a
$cproduct :: forall a. Num a => SendAllKeys a -> a
sum :: SendAllKeys a -> a
$csum :: forall a. Num a => SendAllKeys a -> a
minimum :: SendAllKeys a -> a
$cminimum :: forall a. Ord a => SendAllKeys a -> a
maximum :: SendAllKeys a -> a
$cmaximum :: forall a. Ord a => SendAllKeys a -> a
elem :: a -> SendAllKeys a -> Bool
$celem :: forall a. Eq a => a -> SendAllKeys a -> Bool
length :: SendAllKeys a -> Int
$clength :: forall a. SendAllKeys a -> Int
null :: SendAllKeys a -> Bool
$cnull :: forall a. SendAllKeys a -> Bool
toList :: SendAllKeys a -> [a]
$ctoList :: forall a. SendAllKeys a -> [a]
foldl1 :: (a -> a -> a) -> SendAllKeys a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> SendAllKeys a -> a
foldr1 :: (a -> a -> a) -> SendAllKeys a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> SendAllKeys a -> a
foldl' :: (b -> a -> b) -> b -> SendAllKeys a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> SendAllKeys a -> b
foldl :: (b -> a -> b) -> b -> SendAllKeys a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> SendAllKeys a -> b
foldr' :: (a -> b -> b) -> b -> SendAllKeys a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> SendAllKeys a -> b
foldr :: (a -> b -> b) -> b -> SendAllKeys a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> SendAllKeys a -> b
foldMap' :: (a -> m) -> SendAllKeys a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> SendAllKeys a -> m
foldMap :: (a -> m) -> SendAllKeys a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> SendAllKeys a -> m
fold :: SendAllKeys m -> m
$cfold :: forall m. Monoid m => SendAllKeys m -> m
Foldable, Functor SendAllKeys
Foldable SendAllKeys
Functor SendAllKeys
-> Foldable SendAllKeys
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SendAllKeys a -> f (SendAllKeys b))
-> (forall (f :: * -> *) a.
Applicative f =>
SendAllKeys (f a) -> f (SendAllKeys a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SendAllKeys a -> m (SendAllKeys b))
-> (forall (m :: * -> *) a.
Monad m =>
SendAllKeys (m a) -> m (SendAllKeys a))
-> Traversable SendAllKeys
(a -> f b) -> SendAllKeys a -> f (SendAllKeys b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
SendAllKeys (m a) -> m (SendAllKeys a)
forall (f :: * -> *) a.
Applicative f =>
SendAllKeys (f a) -> f (SendAllKeys a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SendAllKeys a -> m (SendAllKeys b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SendAllKeys a -> f (SendAllKeys b)
sequence :: SendAllKeys (m a) -> m (SendAllKeys a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
SendAllKeys (m a) -> m (SendAllKeys a)
mapM :: (a -> m b) -> SendAllKeys a -> m (SendAllKeys b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SendAllKeys a -> m (SendAllKeys b)
sequenceA :: SendAllKeys (f a) -> f (SendAllKeys a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
SendAllKeys (f a) -> f (SendAllKeys a)
traverse :: (a -> f b) -> SendAllKeys a -> f (SendAllKeys b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SendAllKeys a -> f (SendAllKeys b)
$cp2Traversable :: Foldable SendAllKeys
$cp1Traversable :: Functor SendAllKeys
Traversable)
instance BinaryEx (SendAllKeys Int) where
putEx :: SendAllKeys Int -> Builder
putEx = SendAllKeys Int -> Builder
forall a. HasCallStack => a
undefined
getEx :: ByteString -> SendAllKeys Int
getEx = ByteString -> SendAllKeys Int
forall a. HasCallStack => a
undefined
newtype RecvAllKeys key = RecvAllKeys [(key, Ver, [key], Bloom [BS_Identity])]
instance BinaryEx (RecvAllKeys Int) where
getEx :: ByteString -> RecvAllKeys Int
getEx = ByteString -> RecvAllKeys Int
forall a. HasCallStack => a
undefined
putEx :: RecvAllKeys Int -> Builder
putEx = RecvAllKeys Int -> Builder
forall a. HasCallStack => a
undefined
data SendOneKey key = SendOneKey Ver key Ver Ver [(key, BS_Identity)]
instance BinaryEx (SendOneKey Int) where
getEx :: ByteString -> SendOneKey Int
getEx = ByteString -> SendOneKey Int
forall a. HasCallStack => a
undefined
putEx :: SendOneKey Int -> Builder
putEx = SendOneKey Int -> Builder
forall a. HasCallStack => a
undefined
newtype RecvOneKey key = RecvOneKey (BuildTree key)
instance BinaryEx (RecvOneKey Int) where
getEx :: ByteString -> RecvOneKey Int
getEx = ByteString -> RecvOneKey Int
forall a. HasCallStack => a
undefined
putEx :: RecvOneKey Int -> Builder
putEx = RecvOneKey Int -> Builder
forall a. HasCallStack => a
undefined
data SendDownloadFiles key = SendDownloadFiles Ver key Ver Ver [(FilePath, FileSize, FileHash)]
instance BinaryEx (SendDownloadFiles Int) where
getEx :: ByteString -> SendDownloadFiles Int
getEx = ByteString -> SendDownloadFiles Int
forall a. HasCallStack => a
undefined
putEx :: SendDownloadFiles Int -> Builder
putEx = SendDownloadFiles Int -> Builder
forall a. HasCallStack => a
undefined
data SendUpload key = SendUpload Ver key Ver Ver [[(key, BS_Identity)]] BS_Store [(FilePath, FileSize, FileHash)]
instance BinaryEx (SendUpload Int) where
getEx :: ByteString -> SendUpload Int
getEx = ByteString -> SendUpload Int
forall a. HasCallStack => a
undefined
putEx :: SendUpload Int -> Builder
putEx = SendUpload Int -> Builder
forall a. HasCallStack => a
undefined