{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
module Codec.Winery
( Schema
, SchemaP(..)
, Tag(..)
, Serialise(..)
, testSerialise
, DecodeException(..)
, schema
, toBuilderWithSchema
, serialise
, deserialise
, deserialiseBy
, deserialiseTerm
, splitSchema
, writeFileSerialise
, readFileDeserialise
, serialiseSchema
, schemaToBuilder
, deserialiseSchema
, Extractor(..)
, unwrapExtractor
, Decoder
, evalDecoder
, serialiseOnly
, getDecoder
, getDecoderBy
, Term(..)
, encodeTerm
, Subextractor(..)
, buildExtractor
, extractListBy
, extractField
, extractFieldBy
, extractConstructor
, extractConstructorBy
, extractVoid
, ExtractException(..)
, VarInt(..)
, WineryException(..)
, prettyWineryException
, unexpectedSchema
, SchemaGen
, getSchema
, Plan(..)
, mkPlan
, WineryRecord(..)
, WineryVariant(..)
, WineryProduct(..)
, GSerialiseRecord
, gschemaGenRecord
, gtoBuilderRecord
, gextractorRecord
, gdecodeCurrentRecord
, GSerialiseVariant
, GConstructorCount
, GEncodeVariant
, GDecodeVariant
, gschemaGenVariant
, gtoBuilderVariant
, gextractorVariant
, gdecodeCurrentVariant
, GEncodeProduct
, GDecodeProduct
, gschemaGenProduct
, gtoBuilderProduct
, gextractorProduct
, gdecodeCurrentProduct
, decodeCurrentDefault
, BundleSerialise(..)
, bundleRecord
, bundleRecordDefault
, bundleVariant
, bootstrapSchema
) where
import Codec.Winery.Base as W
import Codec.Winery.Class
import Codec.Winery.Internal
import Control.Applicative
import Control.Exception (throw, throwIO)
import qualified Data.ByteString as B
import qualified Data.ByteString.FastBuilder as BB
import Data.Function (fix)
import qualified Data.Text as T
import Data.Text.Prettyprint.Doc (pretty, dquotes)
import Data.Typeable
import qualified Data.Vector as V
import GHC.Generics (Generic, Rep)
import System.IO
import qualified Test.QuickCheck as QC
decodeTerm :: Schema -> Decoder Term
decodeTerm = go [] where
go points = \case
SBool -> TBool <$> decodeCurrent
W.SChar -> TChar <$> decodeCurrent
SWord8 -> TWord8 <$> getWord8
SWord16 -> TWord16 <$> getWord16
SWord32 -> TWord32 <$> getWord32
SWord64 -> TWord64 <$> getWord64
SInt8 -> TInt8 <$> decodeCurrent
SInt16 -> TInt16 <$> decodeCurrent
SInt32 -> TInt32 <$> decodeCurrent
SInt64 -> TInt64 <$> decodeCurrent
SInteger -> TInteger <$> decodeVarInt
SFloat -> TFloat <$> decodeCurrent
SDouble -> TDouble <$> decodeCurrent
SBytes -> TBytes <$> decodeCurrent
W.SText -> TText <$> decodeCurrent
SUTCTime -> TUTCTime <$> decodeCurrent
SVector sch -> do
n <- decodeVarInt
TVector <$> V.replicateM n (go points sch)
SProduct schs -> TProduct <$> traverse (go points) schs
SRecord schs -> TRecord <$> traverse (\(k, s) -> (,) k <$> go points s) schs
SVariant schs -> do
let !decoders = V.map (\(name, sch) -> let !m = go points sch in (name, m)) schs
tag <- decodeVarInt
let (name, dec) = maybe (throw InvalidTag) id $ decoders V.!? tag
TVariant tag name <$> dec
SVar i -> indexDefault (throw InvalidTag) points i
SFix s' -> fix $ \a -> go (a : points) s'
STag _ s -> go points s
SLet s t -> go (go points s : points) t
encodeTerm :: Term -> BB.Builder
encodeTerm = \case
TBool b -> toBuilder b
TChar x -> toBuilder x
TWord8 x -> toBuilder x
TWord16 x -> toBuilder x
TWord32 x -> toBuilder x
TWord64 x -> toBuilder x
TInt8 x -> toBuilder x
TInt16 x -> toBuilder x
TInt32 x -> toBuilder x
TInt64 x -> toBuilder x
TInteger x -> toBuilder x
TFloat x -> toBuilder x
TDouble x -> toBuilder x
TBytes x -> toBuilder x
TText x -> toBuilder x
TUTCTime x -> toBuilder x
TVector xs -> foldMap encodeTerm xs
TProduct xs -> foldMap encodeTerm xs
TRecord xs -> foldMap (encodeTerm . snd) xs
TVariant tag _ t -> toBuilder tag <> encodeTerm t
deserialiseTerm :: B.ByteString -> Either WineryException (Schema, Term)
deserialiseTerm bs_ = do
(sch, bs) <- splitSchema bs_
return (sch, decodeTerm sch `evalDecoder` bs)
testSerialise :: forall a. (Eq a, Show a, Serialise a) => a -> QC.Property
testSerialise x = case getDecoderBy extractor (schema (Proxy @ a)) of
Left e -> QC.counterexample (show e) False
Right f -> QC.counterexample "extractor" (evalDecoder f b QC.=== x)
QC..&&. QC.counterexample "decodeCurrent" (evalDecoder decodeCurrent b QC.=== x)
where
b = serialiseOnly x
decodeCurrentDefault :: forall a. Serialise a => Decoder a
decodeCurrentDefault = case getDecoderBy extractor (schema (Proxy @ a)) of
Left err -> error $ "decodeCurrentDefault: failed to get a decoder from the current schema"
++ show err
Right a -> a
getDecoder :: forall a. Serialise a => Schema -> Either WineryException (Decoder a)
getDecoder sch
| sch == schema (Proxy @ a) = Right decodeCurrent
| otherwise = getDecoderBy extractor sch
{-# INLINE getDecoder #-}
getDecoderBy :: Extractor a -> Schema -> Either WineryException (Decoder a)
getDecoderBy (Extractor plan) sch = (\f -> f <$> decodeTerm sch)
<$> unPlan plan sch `unStrategy` StrategyEnv 0 []
{-# INLINE getDecoderBy #-}
serialise :: Serialise a => a -> B.ByteString
serialise = BB.toStrictByteString . toBuilderWithSchema
{-# INLINE serialise #-}
writeFileSerialise :: Serialise a => FilePath -> a -> IO ()
writeFileSerialise path a = withBinaryFile path WriteMode
$ \h -> BB.hPutBuilder h $ toBuilderWithSchema a
{-# INLINE writeFileSerialise #-}
toBuilderWithSchema :: forall a. Serialise a => a -> BB.Builder
toBuilderWithSchema a = mappend (BB.word8 currentSchemaVersion)
$ toBuilder (schema (Proxy @ a), a)
{-# INLINE toBuilderWithSchema #-}
splitSchema :: B.ByteString -> Either WineryException (Schema, B.ByteString)
splitSchema bs_ = case B.uncons bs_ of
Just (ver, bs) -> do
m <- bootstrapSchema ver >>= getDecoder
return $ flip evalDecoder bs $ do
sch <- m
Decoder $ \bs' i -> DecoderResult (B.length bs') (sch, B.drop i bs')
Nothing -> Left EmptyInput
serialiseSchema :: Schema -> B.ByteString
serialiseSchema = BB.toStrictByteString . schemaToBuilder
schemaToBuilder :: Schema -> BB.Builder
schemaToBuilder = mappend (BB.word8 currentSchemaVersion) . toBuilder
deserialise :: Serialise a => B.ByteString -> Either WineryException a
deserialise bs_ = do
(sch, bs) <- splitSchema bs_
dec <- getDecoder sch
return $ evalDecoder dec bs
{-# INLINE deserialise #-}
deserialiseBy :: Extractor a -> B.ByteString -> Either WineryException a
deserialiseBy e bs_ = do
(sch, bs) <- splitSchema bs_
dec <- getDecoderBy e sch
return $ evalDecoder dec bs
readFileDeserialise :: Serialise a => FilePath -> IO a
readFileDeserialise path = B.readFile path >>= either throwIO pure . deserialise
deserialiseSchema :: B.ByteString -> Either WineryException Schema
deserialiseSchema bs_ = case B.uncons bs_ of
Just (ver, bs) -> do
m <- bootstrapSchema ver >>= getDecoder
return $ evalDecoder m bs
Nothing -> Left EmptyInput
serialiseOnly :: Serialise a => a -> B.ByteString
serialiseOnly = BB.toStrictByteString . toBuilder
{-# INLINE serialiseOnly #-}
buildExtractor :: Typeable a => Subextractor a -> Extractor a
buildExtractor (Subextractor e) = Extractor $ mkPlan $ unwrapExtractor e
{-# INLINE buildExtractor #-}
newtype Subextractor a = Subextractor { unSubextractor :: Extractor a }
deriving (Functor, Applicative, Alternative)
extractField :: Serialise a => T.Text -> Subextractor a
extractField = extractFieldBy extractor
{-# INLINE extractField #-}
extractFieldBy :: Extractor a -> T.Text -> Subextractor a
extractFieldBy (Extractor g) name = Subextractor $ Extractor $ Plan $ \case
SRecord schs -> case lookupWithIndexV name schs of
Just (i, sch) -> do
m <- unPlan g sch
return $ \case
TRecord xs -> maybe (error msg) (m . snd) $ xs V.!? i
t -> throw $ InvalidTerm t
_ -> throwStrategy $ FieldNotFound rep name (map fst $ V.toList schs)
s -> throwStrategy $ UnexpectedSchema rep "a record" s
where
rep = "extractFieldBy ... " <> dquotes (pretty name)
msg = "Codec.Winery.extractFieldBy ... " <> show name <> ": impossible"
extractConstructorBy :: Typeable a => (Extractor a, T.Text, a -> r) -> Subextractor r -> Subextractor r
extractConstructorBy (d, name, f) cont = Subextractor $ Extractor $ Plan $ \case
SVariant schs0 -> Strategy $ \decs -> do
let run :: Extractor x -> Schema -> Either WineryException (Term -> x)
run e s = unwrapExtractor e s `unStrategy` decs
case lookupWithIndexV name schs0 of
Just (i, s) -> do
(j, dec) <- fmap ((,) i) $ run d $ case s of
SProduct [s'] -> s'
s' -> s'
let rest = SVariant $ V.filter ((/=name) . fst) schs0
k <- run (unSubextractor cont) rest
return $ \case
TVariant tag _ v
| tag == j -> f $ dec v
t -> k t
_ -> run (unSubextractor cont) (SVariant schs0)
s -> throwStrategy $ UnexpectedSchema rep "a variant" s
where
rep = "extractConstructorBy ... " <> dquotes (pretty name)
extractConstructor :: (Serialise a) => (T.Text, a -> r) -> Subextractor r -> Subextractor r
extractConstructor (name, f) = extractConstructorBy (extractor, name, f)
{-# INLINE extractConstructor #-}
extractVoid :: Typeable r => Subextractor r
extractVoid = Subextractor $ Extractor $ mkPlan $ \case
SVariant schs0
| V.null schs0 -> return $ throw . InvalidTerm
s -> throwStrategy $ UnexpectedSchema "extractVoid" "no constructors" s
infixr 1 `extractConstructorBy`
infixr 1 `extractConstructor`
newtype WineryRecord a = WineryRecord { unWineryRecord :: a }
instance (GEncodeProduct (Rep a), GSerialiseRecord (Rep a), GDecodeProduct (Rep a), Generic a, Typeable a) => Serialise (WineryRecord a) where
schemaGen _ = gschemaGenRecord (Proxy @ a)
toBuilder = gtoBuilderRecord . unWineryRecord
extractor = WineryRecord <$> gextractorRecord Nothing
decodeCurrent = WineryRecord <$> gdecodeCurrentRecord
newtype WineryProduct a = WineryProduct { unWineryProduct :: a }
instance (GEncodeProduct (Rep a), GSerialiseProduct (Rep a), GDecodeProduct (Rep a), Generic a, Typeable a) => Serialise (WineryProduct a) where
schemaGen _ = gschemaGenProduct (Proxy @ a)
toBuilder = gtoBuilderProduct . unWineryProduct
extractor = WineryProduct <$> gextractorProduct
decodeCurrent = WineryProduct <$> gdecodeCurrentProduct
newtype WineryVariant a = WineryVariant { unWineryVariant :: a }
instance (GConstructorCount (Rep a), GSerialiseVariant (Rep a), GEncodeVariant (Rep a), GDecodeVariant (Rep a), Generic a, Typeable a) => Serialise (WineryVariant a) where
schemaGen _ = gschemaGenVariant (Proxy @ a)
toBuilder = gtoBuilderVariant . unWineryVariant
extractor = WineryVariant <$> gextractorVariant
decodeCurrent = WineryVariant <$> gdecodeCurrentVariant