{-# LANGUAGE ScopedTypeVariables, AllowAmbiguousTypes #-} {-# LANGUAGE DataKinds, TypeFamilies, RankNTypes, PolyKinds #-} {-# LANGUAGE GADTs, FlexibleContexts #-} {-| Description : Deserialize versioned data Copyright : 2020 Sven Bartscher License : MPL-2.0 Maintainer : sven.bartscher@weltraumschlangen.de Stability : experimental Portability : GHC This module provides operations for deserializing versioned data. The most important entities are the 'VersionedGet' monad and the 'getVersioned' operations, which deserializes a 'VersionedSerialize' value and migrates it to the needed version, if needed. -} module Data.Serialize.Versioned.Get ( VersionedGet , runVersionedGet , getUnversioned , getUnversionedResumable , getVersioned , getEmbeddedDomain , label ) where import qualified Data.Serialize as Cereal import Data.Serialize ( Get , getWord64be ) import Data.Serialize.Versioned.Get.Types import Data.Serialize.Versioned.Internal -- | Reads a versioned container. This container consists of a version -- tag, followed by encoded payload data that is assumed to have been -- serialized with the read version. -- -- Note that this operation doesn't migrate data. Use 'getVersioned' -- in the inner block to actually migrate data. -- -- When using this function, it will pretty much always be inferred to -- an ambiguous type. To avoid this, you can specify the type of the -- argument, like this: -- -- @ -- 'runVersionedGet' (readInner :: 'VersionedGet' MyDomain 5) -- @ -- -- You can of course also use TypeApplications like this: -- -- @ -- 'runVersionedGet' @MyDomain @5 readInner -- @ runVersionedGet :: VersionedGet d a -- ^ The operation to parse the payload of the -- container. The type variable tag encodes which -- version the deserialized data should be migrated -- to. -> Get a runVersionedGet = (>>=) (Cereal.label "Version number" getWord64be) . versionedGetWithVersion -- | Reads a versioned container that is embedded in another versioned -- container. getEmbeddedDomain :: VersionedGet innerD a -> VersionedGet outerD a getEmbeddedDomain = getUnversioned . runVersionedGet