Rename Config/defaultConfig to S/serializeConfig

This commit is contained in:
Harendra Kumar 2023-11-22 01:22:57 +05:30 committed by Adithya Kumar
parent 7d50e5e03e
commit 1640a686e7
8 changed files with 42 additions and 43 deletions

View File

@ -20,5 +20,5 @@ import qualified Streamly.Internal.Data.Serialize as Serialize
$(genLargeRecord "RecCompatible" 50) $(genLargeRecord "RecCompatible" 50)
$(Serialize.deriveSerializeWith $(Serialize.deriveSerializeWith
(Serialize.encodeRecordFields True Serialize.defaultConfig) (Serialize.encodeRecordFields True Serialize.serializeConfig)
[d|instance Serialize RecCompatible|]) [d|instance Serialize RecCompatible|])

View File

@ -53,8 +53,8 @@ module Streamly.Data.Serialize
, Serialize(..) , Serialize(..)
-- Deriving instances -- Deriving instances
, Config -- XXX rename to SerializeConfig , SerializeConfig
, defaultConfig -- XXX rename to defaultSerializeConfig , serializeConfig
, inlineSize , inlineSize
, inlineSerialize , inlineSerialize
, inlineDeserialize , inlineDeserialize

View File

@ -159,8 +159,8 @@ mkSizeOfExpr False True (TheType con) = RecHeader.mkRecSizeOfExpr con
mkSizeOfExpr _ _ _ = errorUnimplemented mkSizeOfExpr _ _ _ = errorUnimplemented
mkSizeDec :: Config -> Type -> [DataCon] -> Q [Dec] mkSizeDec :: SerializeConfig -> Type -> [DataCon] -> Q [Dec]
mkSizeDec (Config {..}) headTy cons = do mkSizeDec (SerializeConfig {..}) headTy cons = do
-- INLINE on sizeOf actually worsens some benchmarks, and improves none -- INLINE on sizeOf actually worsens some benchmarks, and improves none
sizeOfMethod <- sizeOfMethod <-
mkSizeOfExpr mkSizeOfExpr
@ -268,8 +268,8 @@ mkDeserializeExpr False True _ (TheType con@(SimpleDataCon _ fields)) = do
mkDeserializeExpr _ _ _ _ = errorUnimplemented mkDeserializeExpr _ _ _ _ = errorUnimplemented
mkDeserializeDec :: Config -> Type -> [DataCon] -> Q [Dec] mkDeserializeDec :: SerializeConfig -> Type -> [DataCon] -> Q [Dec]
mkDeserializeDec (Config {..}) headTy cons = do mkDeserializeDec (SerializeConfig {..}) headTy cons = do
peekMethod <- peekMethod <-
mkDeserializeExpr mkDeserializeExpr
cfgConstructorTagAsString cfgConstructorTagAsString
@ -378,8 +378,8 @@ mkSerializeExpr False True (TheType con) =
mkSerializeExpr _ _ _ = errorUnimplemented mkSerializeExpr _ _ _ = errorUnimplemented
mkSerializeDec :: Config -> Type -> [DataCon] -> Q [Dec] mkSerializeDec :: SerializeConfig -> Type -> [DataCon] -> Q [Dec]
mkSerializeDec (Config {..}) headTy cons = do mkSerializeDec (SerializeConfig {..}) headTy cons = do
pokeMethod <- pokeMethod <-
mkSerializeExpr mkSerializeExpr
cfgConstructorTagAsString cfgConstructorTagAsString
@ -423,7 +423,7 @@ mkSerializeDec (Config {..}) headTy cons = do
-- Usage: -- Usage:
-- @ -- @
-- $(deriveSerializeInternal -- $(deriveSerializeInternal
-- defaultConfig -- serializeConfig
-- [AppT (ConT ''Serialize) (VarT (mkName "b"))] -- [AppT (ConT ''Serialize) (VarT (mkName "b"))]
-- (AppT -- (AppT
-- (AppT (ConT ''CustomDataType) (VarT (mkName "a"))) -- (AppT (ConT ''CustomDataType) (VarT (mkName "a")))
@ -438,7 +438,7 @@ mkSerializeDec (Config {..}) headTy cons = do
-- ]) -- ])
-- @ -- @
deriveSerializeInternal :: deriveSerializeInternal ::
Config -> Type -> [DataCon] -> ([Dec] -> Q [Dec]) -> Q [Dec] SerializeConfig -> Type -> [DataCon] -> ([Dec] -> Q [Dec]) -> Q [Dec]
deriveSerializeInternal conf headTy cons next = do deriveSerializeInternal conf headTy cons next = do
sizeDec <- mkSizeDec conf headTy cons sizeDec <- mkSizeDec conf headTy cons
peekDec <- mkDeserializeDec conf headTy cons peekDec <- mkDeserializeDec conf headTy cons
@ -457,10 +457,10 @@ deriveSerializeInternal conf headTy cons next = do
-- --
-- @ -- @
-- \$(deriveSerializeWith -- \$(deriveSerializeWith
-- defaultConfig -- serializeConfig
-- [d|instance Serialize a => Serialize (Maybe a)|]) -- [d|instance Serialize a => Serialize (Maybe a)|])
-- @ -- @
deriveSerializeWith :: Config -> Q [Dec] -> Q [Dec] deriveSerializeWith :: SerializeConfig -> Q [Dec] -> Q [Dec]
deriveSerializeWith conf mDecs = do deriveSerializeWith conf mDecs = do
dec <- mDecs dec <- mDecs
case dec of case dec of
@ -505,7 +505,7 @@ deriveSerializeWith conf mDecs = do
-- | Given a 'Serialize' instance declaration splice without the methods, -- | Given a 'Serialize' instance declaration splice without the methods,
-- generate a full instance declaration including all the type class methods. -- generate a full instance declaration including all the type class methods.
-- --
-- >>> deriveSerialize = deriveSerializeWith defaultConfig -- >>> deriveSerialize = deriveSerializeWith serializeConfig
-- --
-- Usage: -- Usage:
-- --
@ -514,4 +514,4 @@ deriveSerializeWith conf mDecs = do
-- [d|instance Serialize a => Serialize (Maybe a)|]) -- [d|instance Serialize a => Serialize (Maybe a)|])
-- @ -- @
deriveSerialize :: Q [Dec] -> Q [Dec] deriveSerialize :: Q [Dec] -> Q [Dec]
deriveSerialize = deriveSerializeWith defaultConfig deriveSerialize = deriveSerializeWith serializeConfig

View File

@ -11,8 +11,8 @@
module Streamly.Internal.Data.Serialize.TH.Bottom module Streamly.Internal.Data.Serialize.TH.Bottom
( (
-- ** Config -- ** Config
Config(..) SerializeConfig(..)
, defaultConfig , serializeConfig
, inlineSize , inlineSize
, inlineSerialize , inlineSerialize
, inlineDeserialize , inlineDeserialize
@ -81,13 +81,13 @@ import Streamly.Internal.Data.Unbox.TH (DataCon(..))
-- interface file or not. -- interface file or not.
-- | Configuration to control how the 'Serialize' instance is generated. Use -- | Configuration to control how the 'Serialize' instance is generated. Use
-- 'defaultConfig' and config setter functions to generate desired Config. For -- 'serializeConfig' and config setter functions to generate desired Config. For
-- example: -- example:
-- --
-- >>> (inlineSize (Just Inline)) . (inlineSerialize (Just Inlinable)) defaultConfig -- >>> (inlineSize (Just Inline)) . (inlineSerialize (Just Inlinable)) serializeConfig
-- --
data Config = data SerializeConfig =
Config SerializeConfig
{ cfgInlineSize :: Maybe Inline { cfgInlineSize :: Maybe Inline
, cfgInlineSerialize :: Maybe Inline , cfgInlineSerialize :: Maybe Inline
, cfgInlineDeserialize :: Maybe Inline , cfgInlineDeserialize :: Maybe Inline
@ -95,27 +95,27 @@ data Config =
, cfgRecordSyntaxWithHeader :: Bool , cfgRecordSyntaxWithHeader :: Bool
} }
-- | How should we inline the 'size' function? The default in 'defaultConfig' -- | How should we inline the 'size' function? The default in 'serializeConfig'
-- is 'Nothing' which means left to the compiler. Forcing inline on @size@ -- is 'Nothing' which means left to the compiler. Forcing inline on @size@
-- function actually worsens some benchmarks and improves none. -- function actually worsens some benchmarks and improves none.
inlineSize :: Maybe Inline -> Config -> Config inlineSize :: Maybe Inline -> SerializeConfig -> SerializeConfig
inlineSize v cfg = cfg {cfgInlineSize = v} inlineSize v cfg = cfg {cfgInlineSize = v}
-- XXX Should we make the default Inlinable instead? -- XXX Should we make the default Inlinable instead?
-- | How should we inline the 'serialize' function? The default in -- | How should we inline the 'serialize' function? The default in
-- 'defaultConfig' is 'Just Inline'. However, aggressive inlining can bloat the -- 'serializeConfig' is 'Just Inline'. However, aggressive inlining can bloat
-- code and increase in compilation times when there are big functions and too -- the code and increase in compilation times when there are big functions and
-- many nesting levels so you can change it accordingly. A 'Nothing' value -- too many nesting levels so you can change it accordingly. A 'Nothing' value
-- leaves the decision to the compiler. -- leaves the decision to the compiler.
inlineSerialize :: Maybe Inline -> Config -> Config inlineSerialize :: Maybe Inline -> SerializeConfig -> SerializeConfig
inlineSerialize v cfg = cfg {cfgInlineSerialize = v} inlineSerialize v cfg = cfg {cfgInlineSerialize = v}
-- XXX Should we make the default Inlinable instead? -- XXX Should we make the default Inlinable instead?
-- | How should we inline the 'deserialize' function? See guidelines in -- | How should we inline the 'deserialize' function? See guidelines in
-- 'inlineSerialize'. -- 'inlineSerialize'.
inlineDeserialize :: Maybe Inline -> Config -> Config inlineDeserialize :: Maybe Inline -> SerializeConfig -> SerializeConfig
inlineDeserialize v cfg = cfg {cfgInlineDeserialize = v} inlineDeserialize v cfg = cfg {cfgInlineDeserialize = v}
-- | __Experimental__ -- | __Experimental__
@ -142,7 +142,7 @@ inlineDeserialize v cfg = cfg {cfgInlineDeserialize = v}
-- This option has to be the same on both encoding and decoding side. -- This option has to be the same on both encoding and decoding side.
-- The default is 'False'. -- The default is 'False'.
-- --
encodeConstrNames :: Bool -> Config -> Config encodeConstrNames :: Bool -> SerializeConfig -> SerializeConfig
encodeConstrNames v cfg = cfg {cfgConstructorTagAsString = v} encodeConstrNames v cfg = cfg {cfgConstructorTagAsString = v}
-- XXX We can deserialize each field to Either, so if there is a -- XXX We can deserialize each field to Either, so if there is a
@ -179,7 +179,7 @@ encodeConstrNames v cfg = cfg {cfgConstructorTagAsString = v}
-- --
-- The default is 'False'. -- The default is 'False'.
-- --
encodeRecordFields :: Bool -> Config -> Config encodeRecordFields :: Bool -> SerializeConfig -> SerializeConfig
encodeRecordFields v cfg = cfg {cfgRecordSyntaxWithHeader = v} encodeRecordFields v cfg = cfg {cfgRecordSyntaxWithHeader = v}
-- | The default configuration settings are: -- | The default configuration settings are:
@ -188,9 +188,9 @@ encodeRecordFields v cfg = cfg {cfgRecordSyntaxWithHeader = v}
-- * 'inlineSerialize' 'Just Inline' -- * 'inlineSerialize' 'Just Inline'
-- * 'inlineDeserialize' 'Just Inline' -- * 'inlineDeserialize' 'Just Inline'
-- --
defaultConfig :: Config serializeConfig :: SerializeConfig
defaultConfig = serializeConfig =
Config SerializeConfig
{ cfgInlineSize = Nothing { cfgInlineSize = Nothing
, cfgInlineSerialize = Just Inline , cfgInlineSerialize = Just Inline
, cfgInlineDeserialize = Just Inline , cfgInlineDeserialize = Just Inline

View File

@ -44,11 +44,11 @@ import Test.Hspec as H
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
#ifdef ENABLE_constructorTagAsString #ifdef ENABLE_constructorTagAsString
#define CONF_NAME "ENABLE_constructorTagAsString" #define CONF_NAME "ENABLE_constructorTagAsString"
#define CONF (Serialize.encodeConstrNames True Serialize.defaultConfig) #define CONF (Serialize.encodeConstrNames True Serialize.serializeConfig)
#else #else
#define CONF_NAME "DEFAULT" #define CONF_NAME "DEFAULT"
#define CONF Serialize.defaultConfig #define CONF Serialize.serializeConfig
#endif #endif
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------

View File

@ -29,7 +29,7 @@ instance Arbitrary a => Arbitrary (Rec a) where
arbitrary = Rec <$> arbitrary <*> arbitrary <*> arbitrary arbitrary = Rec <$> arbitrary <*> arbitrary <*> arbitrary
$(Serialize.deriveSerializeWith $(Serialize.deriveSerializeWith
(Serialize.encodeRecordFields True Serialize.defaultConfig) (Serialize.encodeRecordFields True Serialize.serializeConfig)
[d|instance Serialize a => Serialize (Rec a)|]) [d|instance Serialize a => Serialize (Rec a)|])
data River data River
@ -42,5 +42,5 @@ instance Arbitrary River where
arbitrary = elements [Ganga, Yamuna, Godavari] arbitrary = elements [Ganga, Yamuna, Godavari]
$(Serialize.deriveSerializeWith $(Serialize.deriveSerializeWith
(Serialize.encodeConstrNames True Serialize.defaultConfig) (Serialize.encodeConstrNames True Serialize.serializeConfig)
[d|instance Serialize River|]) [d|instance Serialize River|])

View File

@ -30,7 +30,7 @@ instance Arbitrary a => Arbitrary (Rec a) where
arbitrary = Rec <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary arbitrary = Rec <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
$(Serialize.deriveSerializeWith $(Serialize.deriveSerializeWith
(Serialize.encodeRecordFields True Serialize.defaultConfig) (Serialize.encodeRecordFields True Serialize.serializeConfig)
[d|instance Serialize a => Serialize (Rec a)|]) [d|instance Serialize a => Serialize (Rec a)|])
data River data River
@ -44,5 +44,5 @@ instance Arbitrary River where
arbitrary = elements [Ganga, Yamuna, Godavari] arbitrary = elements [Ganga, Yamuna, Godavari]
$(Serialize.deriveSerializeWith $(Serialize.deriveSerializeWith
(Serialize.encodeConstrNames True Serialize.defaultConfig) (Serialize.encodeConstrNames True Serialize.serializeConfig)
[d|instance Serialize River|]) [d|instance Serialize River|])

View File

@ -172,8 +172,7 @@ $(Serialize.deriveSerialize
[d|instance Serialize a => Serialize (Complex a)|]) [d|instance Serialize a => Serialize (Complex a)|])
$(Serialize.deriveSerialize $(Serialize.deriveSerialize
[d|instance Serialize a => Serialize (Ratio a)|]) [d|instance Serialize a => Serialize (Ratio a)|])
$(Serialize.deriveSerializeWith $(Serialize.deriveSerialize
Serialize.defaultConfig
[d|instance Serialize a => Serialize (Const a b)|]) [d|instance Serialize a => Serialize (Const a b)|])
$(Serialize.deriveSerialize $(Serialize.deriveSerialize
[d|instance Serialize a => Serialize (Identity a)|]) [d|instance Serialize a => Serialize (Identity a)|])