1
1
mirror of https://github.com/github/semantic.git synced 2024-12-28 09:21:35 +03:00

Pull in upstream proto3-suite and kill the Exts module.

This commit is contained in:
Patrick Thomson 2019-01-24 13:13:47 -05:00
parent 92b5549d01
commit 46969defce
7 changed files with 1 additions and 53 deletions

View File

@ -180,7 +180,6 @@ library
, Parsing.TreeSitter
, Paths_semantic
, Proto3.Google.Wrapped
, Proto3.Suite.Exts
-- Rendering formats
, Rendering.Graph
, Rendering.JSON

View File

@ -25,3 +25,4 @@ newtype SHA = SHA Text
nullSHA :: SHA
nullSHA = SHA mempty

View File

@ -7,7 +7,6 @@ module Data.GitHub.Auth
import Prologue
import Proto3.Suite
import Proto3.Suite.Exts
data AuthTypes
= Unknown

View File

@ -7,7 +7,6 @@ module Data.GitHub.IPVersion
import Prologue
import Proto3.Suite
import Proto3.Suite.Exts
data IPVersion
= Unknown

View File

@ -7,7 +7,6 @@ module Data.GitHub.Spamurai
import Prologue
import Proto3.Suite
import Proto3.Suite.Exts
data SpamuraiClassification
= Unknown

View File

@ -1,48 +0,0 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, DerivingVia, PatternSynonyms, ScopedTypeVariables, UndecidableInstances #-}
module Proto3.Suite.Exts
( PrimitiveEnum (..)
, pattern Present
, pattern Absent
, toByteString
) where
import Prologue
import Data.Either
import Proto3.Suite
import qualified Proto3.Wire.Encode as Encode
import qualified Proto3.Wire.Decode as Decode
import Data.ByteString.Lazy (toStrict)
-- * The Nested newtype from proto3-suite is a useful type to represent
-- protobuf messages nested inside each other. Because all nested
-- fields are implicitly optional in proto3, Nested is a newtype over
-- Maybe—which is fine, except for the fact that it makes
-- pattern-matching a little tedious. Building pattern synonyms to
-- abstract over Nested Just and Nested Nothing values gives us
-- syntactic convenience while helping us avoid Maybe-blindness.
-- | Equivalent to @Nested (Just a)).
pattern Present :: a -> Nested a
pattern Present t = Nested (Just t)
-- | Equivalent to @Nested Nothing@.
pattern Absent :: Nested a
pattern Absent = Nested Nothing
{-# COMPLETE Present, Absent #-}
newtype PrimitiveEnum a = PrimitiveEnum a
deriving (Eq, Ord, Bounded, Named, Enum, HasDefault)
-- | Provides a DerivingVia hook to opt into a sensible definition of 'Primitive'
-- for a given 'Enum'. Should the decoding fail, the 'HasDefault' instance is used
-- as a fallback.
instance (Enum a, Bounded a, Named a, HasDefault a) => Primitive (PrimitiveEnum a) where
primType _ = Named (Single (nameOf (Proxy @a)))
encodePrimitive = Encode.enum
decodePrimitive = fromRight def <$> Decode.enum
toByteString :: Message a => a -> ByteString
toByteString = toStrict . toLazyByteString

View File

@ -6,7 +6,6 @@ module Data.GitHub.Spec
import SpecHelpers
import Proto3.Suite
import Proto3.Suite.Exts
import Proto3.GitHub.Envelope
import Proto3.GitHub.Event.RepositoryPush