Skip to content

Commit

Permalink
Move Wrap out of Form and into Encode.
Browse files Browse the repository at this point in the history
  • Loading branch information
j6carey committed Jan 8, 2025
1 parent 421c80d commit 1f35910
Show file tree
Hide file tree
Showing 4 changed files with 45 additions and 44 deletions.
17 changes: 1 addition & 16 deletions src/Proto3/Suite/Form.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
Expand Down Expand Up @@ -35,7 +29,6 @@ module Proto3.Suite.Form
, Association
, RepetitionOfMapped
, Wrapper
, Wrap(..)
, RecoverRepetition
, RecoverProtoType
, MessageFieldType
Expand All @@ -47,7 +40,6 @@ import Data.Int (Int32, Int64)
import Data.Kind (Type)
import Data.Word (Word32, Word64)
import GHC.Exts (Constraint)
import GHC.Generics (Generic)
import GHC.TypeLits (ErrorMessage(..), Nat, Symbol, TypeError)
import Prelude hiding (String)
import Proto3.Suite.Types (Bytes, Enumerated, Commented, Fixed, ForceEmit, Nested,
Expand Down Expand Up @@ -206,7 +198,7 @@ type family RepetitionOfMapped (protoType :: ProtoType) :: Repetition
--
-- We never need to construct values; instead we construct values of types
-- such as @`Proto3.Suite.Form.Encode.Encoding` ('Wrapper' protoType)@ or
-- @'Wrap' a@, where @a@ is a corresponding native representation.
-- @`Proto.Suite.Form.Encode.Wrap` a@, where @a@ is a corresponding native representation.
--
-- Note that if Google ever adds wrappers for "sint..." or "...fixed..."
-- then this type constructor will naturally support such wrappers.
Expand All @@ -222,13 +214,6 @@ type instance OneOfOf (Wrapper protoType) "value" = ""

type instance RepetitionOf (Wrapper protoType) "value" = 'Singular 'Implicit

-- | Helps some type classes distinguish wrapped values from encodings of wrapper submessages.
--
-- See also 'Wrapper'.
newtype Wrap (a :: Type) = Wrap { unwrap :: a }
deriving stock (Foldable, Functor, Generic, Traversable)
deriving newtype (Bounded, Enum, Eq, Fractional, Integral, Ord, Num, Read, Real, Show)

-- | Given the Haskell type used by features such as `Proto3.Suite.Class.MessageField`
-- to indicate the encoding of a message field.
type family RecoverRepetition (haskellType :: Type) :: Repetition
Expand Down
1 change: 1 addition & 0 deletions src/Proto3/Suite/Form/Encode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,7 @@ module Proto3.Suite.Form.Encode
, KnownFieldNumber
, Field(..)
, RawField(..)
, Wrap(..)
, Forward(..)
, Reverse(..)
, Vector(..)
Expand Down
17 changes: 16 additions & 1 deletion src/Proto3/Suite/Form/Encode/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,15 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MagicHash #-}
Expand Down Expand Up @@ -52,6 +58,7 @@ module Proto3.Suite.Form.Encode.Core
, fieldNumber
, Field(..)
, RawField(..)
, Wrap(..)
, Forward(..)
, Reverse(..)
, Vector(..)
Expand All @@ -72,14 +79,15 @@ import Data.Traversable (for)
import Data.Vector.Generic qualified
import Data.Word (Word32, Word64)
import GHC.Exts (Constraint, Proxy#, TYPE, proxy#)
import GHC.Generics (Generic)
import GHC.TypeLits (ErrorMessage(..), KnownNat, Symbol, TypeError, natVal')
import Language.Haskell.TH qualified as TH
import Prelude hiding ((.), id)
import Proto3.Suite.Class (HasDefault(..), Primitive(..), zigZagEncode)
import Proto3.Suite.Form
(Association, NumberOf, Omission(..), OneOfOf,
Packing(..), RecoverProtoType, Repetition(..), RepetitionOf,
ProtoType(..), ProtoTypeOf, Wrap(..), Wrapper)
ProtoType(..), ProtoTypeOf, Wrapper)
import Proto3.Suite.Types (Enumerated(..), Fixed(..), Signed(..))
import Proto3.Wire.Class (ProtoEnum(..))
import Proto3.Wire.Encode qualified as Encode
Expand Down Expand Up @@ -475,6 +483,13 @@ instance ( repetition ~ 'Repeated 'Unpacked
rawField !fn es = foldBuilders (Encode.embedded fn . untypedMessageEncoder <$> es)
{-# INLINE rawField #-}

-- | Helps some type classes distinguish wrapped values from encodings of wrapper submessages.
--
-- See also 'Wrapper'.
newtype Wrap (a :: Type) = Wrap { unwrap :: a }
deriving stock (Foldable, Functor, Generic, Traversable)
deriving newtype (Bounded, Enum, Eq, Fractional, Integral, Ord, Num, Read, Real, Show)

instance ( omission ~ 'Alternative
, RawField ('Singular 'Implicit) protoType a
) =>
Expand Down
54 changes: 27 additions & 27 deletions tests/Test/Proto/ToEncoder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -302,101 +302,101 @@ instance ToEncoder TestProtoOneof.WithImported
instance ToEncoder TestProtoWrappers.TestDoubleValue
where
toEncoder (TestProtoWrappers.TestDoubleValue f1 f2 f3) = FormE.fieldsToMessage $
FormE.field @"wrapper" (fmap Form.Wrap f1) .
repeated @"many" Form.Wrap f2 .
FormE.field @"wrapper" (fmap FormE.Wrap f1) .
repeated @"many" FormE.Wrap f2 .
case f3 of
Nothing ->
FormE.omitted
Just (TestProtoWrappers.TestDoubleValuePickOneOne v) ->
FormE.field @"one" (Form.Wrap v)
FormE.field @"one" (FormE.Wrap v)

instance ToEncoder TestProtoWrappers.TestFloatValue
where
toEncoder (TestProtoWrappers.TestFloatValue f1 f2 f3) = FormE.fieldsToMessage $
FormE.field @"wrapper" (fmap Form.Wrap f1) .
repeated @"many" Form.Wrap f2 .
FormE.field @"wrapper" (fmap FormE.Wrap f1) .
repeated @"many" FormE.Wrap f2 .
case f3 of
Nothing ->
FormE.omitted
Just (TestProtoWrappers.TestFloatValuePickOneOne v) ->
FormE.field @"one" (Form.Wrap v)
FormE.field @"one" (FormE.Wrap v)

instance ToEncoder TestProtoWrappers.TestInt64Value
where
toEncoder (TestProtoWrappers.TestInt64Value f1 f2 f3) = FormE.fieldsToMessage $
FormE.field @"wrapper" (fmap Form.Wrap f1) .
repeated @"many" Form.Wrap f2 .
FormE.field @"wrapper" (fmap FormE.Wrap f1) .
repeated @"many" FormE.Wrap f2 .
case f3 of
Nothing ->
FormE.omitted
Just (TestProtoWrappers.TestInt64ValuePickOneOne v) ->
FormE.field @"one" (Form.Wrap v)
FormE.field @"one" (FormE.Wrap v)

instance ToEncoder TestProtoWrappers.TestUInt64Value
where
toEncoder (TestProtoWrappers.TestUInt64Value f1 f2 f3) = FormE.fieldsToMessage $
FormE.field @"wrapper" (fmap Form.Wrap f1) .
repeated @"many" Form.Wrap f2 .
FormE.field @"wrapper" (fmap FormE.Wrap f1) .
repeated @"many" FormE.Wrap f2 .
case f3 of
Nothing ->
FormE.omitted
Just (TestProtoWrappers.TestUInt64ValuePickOneOne v) ->
FormE.field @"one" (Form.Wrap v)
FormE.field @"one" (FormE.Wrap v)

instance ToEncoder TestProtoWrappers.TestInt32Value
where
toEncoder (TestProtoWrappers.TestInt32Value f1 f2 f3) = FormE.fieldsToMessage $
FormE.field @"wrapper" (fmap Form.Wrap f1) .
repeated @"many" Form.Wrap f2 .
FormE.field @"wrapper" (fmap FormE.Wrap f1) .
repeated @"many" FormE.Wrap f2 .
case f3 of
Nothing ->
FormE.omitted
Just (TestProtoWrappers.TestInt32ValuePickOneOne v) ->
FormE.field @"one" (Form.Wrap v)
FormE.field @"one" (FormE.Wrap v)

instance ToEncoder TestProtoWrappers.TestUInt32Value
where
toEncoder (TestProtoWrappers.TestUInt32Value f1 f2 f3) = FormE.fieldsToMessage $
FormE.field @"wrapper" (fmap Form.Wrap f1) .
repeated @"many" Form.Wrap f2 .
FormE.field @"wrapper" (fmap FormE.Wrap f1) .
repeated @"many" FormE.Wrap f2 .
case f3 of
Nothing ->
FormE.omitted
Just (TestProtoWrappers.TestUInt32ValuePickOneOne v) ->
FormE.field @"one" (Form.Wrap v)
FormE.field @"one" (FormE.Wrap v)

instance ToEncoder TestProtoWrappers.TestBoolValue
where
toEncoder (TestProtoWrappers.TestBoolValue f1 f2 f3) = FormE.fieldsToMessage $
FormE.field @"wrapper" (fmap Form.Wrap f1) .
repeated @"many" Form.Wrap f2 .
FormE.field @"wrapper" (fmap FormE.Wrap f1) .
repeated @"many" FormE.Wrap f2 .
case f3 of
Nothing ->
FormE.omitted
Just (TestProtoWrappers.TestBoolValuePickOneOne v) ->
FormE.field @"one" (Form.Wrap v)
FormE.field @"one" (FormE.Wrap v)

instance ToEncoder TestProtoWrappers.TestStringValue
where
toEncoder (TestProtoWrappers.TestStringValue f1 f2 f3) = FormE.fieldsToMessage $
FormE.field @"wrapper" (fmap Form.Wrap f1) .
repeated @"many" Form.Wrap f2 .
FormE.field @"wrapper" (fmap FormE.Wrap f1) .
repeated @"many" FormE.Wrap f2 .
case f3 of
Nothing ->
FormE.omitted
Just (TestProtoWrappers.TestStringValuePickOneOne v) ->
FormE.field @"one" (Form.Wrap v)
FormE.field @"one" (FormE.Wrap v)

instance ToEncoder TestProtoWrappers.TestBytesValue
where
toEncoder (TestProtoWrappers.TestBytesValue f1 f2 f3) = FormE.fieldsToMessage $
FormE.field @"wrapper" (fmap Form.Wrap f1) .
repeated @"many" Form.Wrap f2 .
FormE.field @"wrapper" (fmap FormE.Wrap f1) .
repeated @"many" FormE.Wrap f2 .
case f3 of
Nothing ->
FormE.omitted
Just (TestProtoWrappers.TestBytesValuePickOneOne v) ->
FormE.field @"one" (Form.Wrap v)
FormE.field @"one" (FormE.Wrap v)

instance ToEncoder WrappedTrivial
where
Expand Down

0 comments on commit 1f35910

Please sign in to comment.