{-# LANGUAGE BangPatterns, DeriveDataTypeable, DeriveGeneric, FlexibleInstances, MultiParamTypeClasses, OverloadedStrings #-}
{-# OPTIONS_GHC  -w #-}
module Text.DescriptorProtos.FileOptions (FileOptions(..)) where
import Prelude ((+), (/), (++), (.), (==), (<=), (&&))
import qualified Prelude as Prelude'
import qualified Data.List as Prelude'
import qualified Data.Typeable as Prelude'
import qualified GHC.Generics as Prelude'
import qualified Data.Data as Prelude'
import qualified Text.ProtocolBuffers.Header as P'
import qualified Text.DescriptorProtos.FileOptions.OptimizeMode as DescriptorProtos.FileOptions (OptimizeMode)
import qualified Text.DescriptorProtos.UninterpretedOption as DescriptorProtos (UninterpretedOption)

data FileOptions = FileOptions{FileOptions -> Maybe Utf8
java_package :: !(P'.Maybe P'.Utf8), FileOptions -> Maybe Utf8
java_outer_classname :: !(P'.Maybe P'.Utf8),
                               FileOptions -> Maybe Bool
java_multiple_files :: !(P'.Maybe P'.Bool), FileOptions -> Maybe Bool
java_generate_equals_and_hash :: !(P'.Maybe P'.Bool),
                               FileOptions -> Maybe Bool
java_string_check_utf8 :: !(P'.Maybe P'.Bool),
                               FileOptions -> Maybe OptimizeMode
optimize_for :: !(P'.Maybe DescriptorProtos.FileOptions.OptimizeMode),
                               FileOptions -> Maybe Utf8
go_package :: !(P'.Maybe P'.Utf8), FileOptions -> Maybe Bool
cc_generic_services :: !(P'.Maybe P'.Bool),
                               FileOptions -> Maybe Bool
java_generic_services :: !(P'.Maybe P'.Bool), FileOptions -> Maybe Bool
py_generic_services :: !(P'.Maybe P'.Bool),
                               FileOptions -> Maybe Bool
deprecated :: !(P'.Maybe P'.Bool), FileOptions -> Maybe Bool
cc_enable_arenas :: !(P'.Maybe P'.Bool),
                               FileOptions -> Maybe Utf8
objc_class_prefix :: !(P'.Maybe P'.Utf8), FileOptions -> Maybe Utf8
csharp_namespace :: !(P'.Maybe P'.Utf8),
                               FileOptions -> Maybe Bool
javanano_use_deprecated_package :: !(P'.Maybe P'.Bool),
                               FileOptions -> Seq UninterpretedOption
uninterpreted_option :: !(P'.Seq DescriptorProtos.UninterpretedOption), FileOptions -> ExtField
ext'field :: !(P'.ExtField),
                               FileOptions -> UnknownField
unknown'field :: !(P'.UnknownField)}
                   deriving (Int -> FileOptions -> ShowS
[FileOptions] -> ShowS
FileOptions -> String
(Int -> FileOptions -> ShowS)
-> (FileOptions -> String)
-> ([FileOptions] -> ShowS)
-> Show FileOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileOptions] -> ShowS
$cshowList :: [FileOptions] -> ShowS
show :: FileOptions -> String
$cshow :: FileOptions -> String
showsPrec :: Int -> FileOptions -> ShowS
$cshowsPrec :: Int -> FileOptions -> ShowS
Prelude'.Show, FileOptions -> FileOptions -> Bool
(FileOptions -> FileOptions -> Bool)
-> (FileOptions -> FileOptions -> Bool) -> Eq FileOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileOptions -> FileOptions -> Bool
$c/= :: FileOptions -> FileOptions -> Bool
== :: FileOptions -> FileOptions -> Bool
$c== :: FileOptions -> FileOptions -> Bool
Prelude'.Eq, Eq FileOptions
Eq FileOptions
-> (FileOptions -> FileOptions -> Ordering)
-> (FileOptions -> FileOptions -> Bool)
-> (FileOptions -> FileOptions -> Bool)
-> (FileOptions -> FileOptions -> Bool)
-> (FileOptions -> FileOptions -> Bool)
-> (FileOptions -> FileOptions -> FileOptions)
-> (FileOptions -> FileOptions -> FileOptions)
-> Ord FileOptions
FileOptions -> FileOptions -> Bool
FileOptions -> FileOptions -> Ordering
FileOptions -> FileOptions -> FileOptions
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FileOptions -> FileOptions -> FileOptions
$cmin :: FileOptions -> FileOptions -> FileOptions
max :: FileOptions -> FileOptions -> FileOptions
$cmax :: FileOptions -> FileOptions -> FileOptions
>= :: FileOptions -> FileOptions -> Bool
$c>= :: FileOptions -> FileOptions -> Bool
> :: FileOptions -> FileOptions -> Bool
$c> :: FileOptions -> FileOptions -> Bool
<= :: FileOptions -> FileOptions -> Bool
$c<= :: FileOptions -> FileOptions -> Bool
< :: FileOptions -> FileOptions -> Bool
$c< :: FileOptions -> FileOptions -> Bool
compare :: FileOptions -> FileOptions -> Ordering
$ccompare :: FileOptions -> FileOptions -> Ordering
$cp1Ord :: Eq FileOptions
Prelude'.Ord, Prelude'.Typeable, Typeable FileOptions
DataType
Constr
Typeable FileOptions
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> FileOptions -> c FileOptions)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c FileOptions)
-> (FileOptions -> Constr)
-> (FileOptions -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c FileOptions))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c FileOptions))
-> ((forall b. Data b => b -> b) -> FileOptions -> FileOptions)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> FileOptions -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> FileOptions -> r)
-> (forall u. (forall d. Data d => d -> u) -> FileOptions -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> FileOptions -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> FileOptions -> m FileOptions)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> FileOptions -> m FileOptions)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> FileOptions -> m FileOptions)
-> Data FileOptions
FileOptions -> DataType
FileOptions -> Constr
(forall b. Data b => b -> b) -> FileOptions -> FileOptions
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FileOptions -> c FileOptions
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FileOptions
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> FileOptions -> u
forall u. (forall d. Data d => d -> u) -> FileOptions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FileOptions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FileOptions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FileOptions -> m FileOptions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FileOptions -> m FileOptions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FileOptions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FileOptions -> c FileOptions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FileOptions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FileOptions)
$cFileOptions :: Constr
$tFileOptions :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> FileOptions -> m FileOptions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FileOptions -> m FileOptions
gmapMp :: (forall d. Data d => d -> m d) -> FileOptions -> m FileOptions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FileOptions -> m FileOptions
gmapM :: (forall d. Data d => d -> m d) -> FileOptions -> m FileOptions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FileOptions -> m FileOptions
gmapQi :: Int -> (forall d. Data d => d -> u) -> FileOptions -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FileOptions -> u
gmapQ :: (forall d. Data d => d -> u) -> FileOptions -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FileOptions -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FileOptions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FileOptions -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FileOptions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FileOptions -> r
gmapT :: (forall b. Data b => b -> b) -> FileOptions -> FileOptions
$cgmapT :: (forall b. Data b => b -> b) -> FileOptions -> FileOptions
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FileOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FileOptions)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FileOptions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FileOptions)
dataTypeOf :: FileOptions -> DataType
$cdataTypeOf :: FileOptions -> DataType
toConstr :: FileOptions -> Constr
$ctoConstr :: FileOptions -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FileOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FileOptions
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FileOptions -> c FileOptions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FileOptions -> c FileOptions
$cp1Data :: Typeable FileOptions
Prelude'.Data, (forall x. FileOptions -> Rep FileOptions x)
-> (forall x. Rep FileOptions x -> FileOptions)
-> Generic FileOptions
forall x. Rep FileOptions x -> FileOptions
forall x. FileOptions -> Rep FileOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FileOptions x -> FileOptions
$cfrom :: forall x. FileOptions -> Rep FileOptions x
Prelude'.Generic)

instance P'.ExtendMessage FileOptions where
  getExtField :: FileOptions -> ExtField
getExtField = FileOptions -> ExtField
ext'field
  putExtField :: ExtField -> FileOptions -> FileOptions
putExtField ExtField
e'f FileOptions
msg = FileOptions
msg{ext'field :: ExtField
ext'field = ExtField
e'f}
  validExtRanges :: FileOptions -> [(FieldId, FieldId)]
validExtRanges FileOptions
msg = DescriptorInfo -> [(FieldId, FieldId)]
P'.extRanges (FileOptions -> DescriptorInfo
forall m. ReflectDescriptor m => m -> DescriptorInfo
P'.reflectDescriptorInfo FileOptions
msg)

instance P'.UnknownMessage FileOptions where
  getUnknownField :: FileOptions -> UnknownField
getUnknownField = FileOptions -> UnknownField
unknown'field
  putUnknownField :: UnknownField -> FileOptions -> FileOptions
putUnknownField UnknownField
u'f FileOptions
msg = FileOptions
msg{unknown'field :: UnknownField
unknown'field = UnknownField
u'f}

instance P'.Mergeable FileOptions where
  mergeAppend :: FileOptions -> FileOptions -> FileOptions
mergeAppend (FileOptions Maybe Utf8
x'1 Maybe Utf8
x'2 Maybe Bool
x'3 Maybe Bool
x'4 Maybe Bool
x'5 Maybe OptimizeMode
x'6 Maybe Utf8
x'7 Maybe Bool
x'8 Maybe Bool
x'9 Maybe Bool
x'10 Maybe Bool
x'11 Maybe Bool
x'12 Maybe Utf8
x'13 Maybe Utf8
x'14 Maybe Bool
x'15 Seq UninterpretedOption
x'16 ExtField
x'17 UnknownField
x'18)
   (FileOptions Maybe Utf8
y'1 Maybe Utf8
y'2 Maybe Bool
y'3 Maybe Bool
y'4 Maybe Bool
y'5 Maybe OptimizeMode
y'6 Maybe Utf8
y'7 Maybe Bool
y'8 Maybe Bool
y'9 Maybe Bool
y'10 Maybe Bool
y'11 Maybe Bool
y'12 Maybe Utf8
y'13 Maybe Utf8
y'14 Maybe Bool
y'15 Seq UninterpretedOption
y'16 ExtField
y'17 UnknownField
y'18)
   = let !z'1 :: Maybe Utf8
z'1 = Maybe Utf8 -> Maybe Utf8 -> Maybe Utf8
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Utf8
x'1 Maybe Utf8
y'1
         !z'2 :: Maybe Utf8
z'2 = Maybe Utf8 -> Maybe Utf8 -> Maybe Utf8
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Utf8
x'2 Maybe Utf8
y'2
         !z'3 :: Maybe Bool
z'3 = Maybe Bool -> Maybe Bool -> Maybe Bool
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Bool
x'3 Maybe Bool
y'3
         !z'4 :: Maybe Bool
z'4 = Maybe Bool -> Maybe Bool -> Maybe Bool
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Bool
x'4 Maybe Bool
y'4
         !z'5 :: Maybe Bool
z'5 = Maybe Bool -> Maybe Bool -> Maybe Bool
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Bool
x'5 Maybe Bool
y'5
         !z'6 :: Maybe OptimizeMode
z'6 = Maybe OptimizeMode -> Maybe OptimizeMode -> Maybe OptimizeMode
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe OptimizeMode
x'6 Maybe OptimizeMode
y'6
         !z'7 :: Maybe Utf8
z'7 = Maybe Utf8 -> Maybe Utf8 -> Maybe Utf8
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Utf8
x'7 Maybe Utf8
y'7
         !z'8 :: Maybe Bool
z'8 = Maybe Bool -> Maybe Bool -> Maybe Bool
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Bool
x'8 Maybe Bool
y'8
         !z'9 :: Maybe Bool
z'9 = Maybe Bool -> Maybe Bool -> Maybe Bool
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Bool
x'9 Maybe Bool
y'9
         !z'10 :: Maybe Bool
z'10 = Maybe Bool -> Maybe Bool -> Maybe Bool
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Bool
x'10 Maybe Bool
y'10
         !z'11 :: Maybe Bool
z'11 = Maybe Bool -> Maybe Bool -> Maybe Bool
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Bool
x'11 Maybe Bool
y'11
         !z'12 :: Maybe Bool
z'12 = Maybe Bool -> Maybe Bool -> Maybe Bool
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Bool
x'12 Maybe Bool
y'12
         !z'13 :: Maybe Utf8
z'13 = Maybe Utf8 -> Maybe Utf8 -> Maybe Utf8
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Utf8
x'13 Maybe Utf8
y'13
         !z'14 :: Maybe Utf8
z'14 = Maybe Utf8 -> Maybe Utf8 -> Maybe Utf8
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Utf8
x'14 Maybe Utf8
y'14
         !z'15 :: Maybe Bool
z'15 = Maybe Bool -> Maybe Bool -> Maybe Bool
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Maybe Bool
x'15 Maybe Bool
y'15
         !z'16 :: Seq UninterpretedOption
z'16 = Seq UninterpretedOption
-> Seq UninterpretedOption -> Seq UninterpretedOption
forall a. Mergeable a => a -> a -> a
P'.mergeAppend Seq UninterpretedOption
x'16 Seq UninterpretedOption
y'16
         !z'17 :: ExtField
z'17 = ExtField -> ExtField -> ExtField
forall a. Mergeable a => a -> a -> a
P'.mergeAppend ExtField
x'17 ExtField
y'17
         !z'18 :: UnknownField
z'18 = UnknownField -> UnknownField -> UnknownField
forall a. Mergeable a => a -> a -> a
P'.mergeAppend UnknownField
x'18 UnknownField
y'18
      in Maybe Utf8
-> Maybe Utf8
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe OptimizeMode
-> Maybe Utf8
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Utf8
-> Maybe Utf8
-> Maybe Bool
-> Seq UninterpretedOption
-> ExtField
-> UnknownField
-> FileOptions
FileOptions Maybe Utf8
z'1 Maybe Utf8
z'2 Maybe Bool
z'3 Maybe Bool
z'4 Maybe Bool
z'5 Maybe OptimizeMode
z'6 Maybe Utf8
z'7 Maybe Bool
z'8 Maybe Bool
z'9 Maybe Bool
z'10 Maybe Bool
z'11 Maybe Bool
z'12 Maybe Utf8
z'13 Maybe Utf8
z'14 Maybe Bool
z'15 Seq UninterpretedOption
z'16 ExtField
z'17 UnknownField
z'18

instance P'.Default FileOptions where
  defaultValue :: FileOptions
defaultValue
   = Maybe Utf8
-> Maybe Utf8
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe OptimizeMode
-> Maybe Utf8
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Utf8
-> Maybe Utf8
-> Maybe Bool
-> Seq UninterpretedOption
-> ExtField
-> UnknownField
-> FileOptions
FileOptions Maybe Utf8
forall a. Default a => a
P'.defaultValue Maybe Utf8
forall a. Default a => a
P'.defaultValue (Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
Prelude'.False) (Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
Prelude'.False)
      (Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
Prelude'.False)
      (OptimizeMode -> Maybe OptimizeMode
forall a. a -> Maybe a
Prelude'.Just (String -> OptimizeMode
forall a. Read a => String -> a
Prelude'.read String
"SPEED"))
      Maybe Utf8
forall a. Default a => a
P'.defaultValue
      (Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
Prelude'.False)
      (Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
Prelude'.False)
      (Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
Prelude'.False)
      (Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
Prelude'.False)
      (Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
Prelude'.False)
      Maybe Utf8
forall a. Default a => a
P'.defaultValue
      Maybe Utf8
forall a. Default a => a
P'.defaultValue
      Maybe Bool
forall a. Default a => a
P'.defaultValue
      Seq UninterpretedOption
forall a. Default a => a
P'.defaultValue
      ExtField
forall a. Default a => a
P'.defaultValue
      UnknownField
forall a. Default a => a
P'.defaultValue

instance P'.Wire FileOptions where
  wireSize :: FieldType -> FileOptions -> WireSize
wireSize FieldType
ft' self' :: FileOptions
self'@(FileOptions Maybe Utf8
x'1 Maybe Utf8
x'2 Maybe Bool
x'3 Maybe Bool
x'4 Maybe Bool
x'5 Maybe OptimizeMode
x'6 Maybe Utf8
x'7 Maybe Bool
x'8 Maybe Bool
x'9 Maybe Bool
x'10 Maybe Bool
x'11 Maybe Bool
x'12 Maybe Utf8
x'13 Maybe Utf8
x'14 Maybe Bool
x'15 Seq UninterpretedOption
x'16 ExtField
x'17 UnknownField
x'18)
   = case FieldType
ft' of
       FieldType
10 -> WireSize
calc'Size
       FieldType
11 -> WireSize -> WireSize
P'.prependMessageSize WireSize
calc'Size
       FieldType
_ -> FieldType -> FileOptions -> WireSize
forall a. Typeable a => FieldType -> a -> WireSize
P'.wireSizeErr FieldType
ft' FileOptions
self'
    where
        calc'Size :: WireSize
calc'Size
         = (WireSize -> FieldType -> Maybe Utf8 -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
1 FieldType
9 Maybe Utf8
x'1 WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Utf8 -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
1 FieldType
9 Maybe Utf8
x'2 WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Bool -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
1 FieldType
8 Maybe Bool
x'3 WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Bool -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
2 FieldType
8 Maybe Bool
x'4 WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+
             WireSize -> FieldType -> Maybe Bool -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
2 FieldType
8 Maybe Bool
x'5
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe OptimizeMode -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
1 FieldType
14 Maybe OptimizeMode
x'6
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Utf8 -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
1 FieldType
9 Maybe Utf8
x'7
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Bool -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
2 FieldType
8 Maybe Bool
x'8
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Bool -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
2 FieldType
8 Maybe Bool
x'9
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Bool -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
2 FieldType
8 Maybe Bool
x'10
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Bool -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
2 FieldType
8 Maybe Bool
x'11
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Bool -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
2 FieldType
8 Maybe Bool
x'12
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Utf8 -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
2 FieldType
9 Maybe Utf8
x'13
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Utf8 -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
2 FieldType
9 Maybe Utf8
x'14
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Maybe Bool -> WireSize
forall v. Wire v => WireSize -> FieldType -> Maybe v -> WireSize
P'.wireSizeOpt WireSize
2 FieldType
8 Maybe Bool
x'15
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ WireSize -> FieldType -> Seq UninterpretedOption -> WireSize
forall v. Wire v => WireSize -> FieldType -> Seq v -> WireSize
P'.wireSizeRep WireSize
2 FieldType
11 Seq UninterpretedOption
x'16
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ ExtField -> WireSize
P'.wireSizeExtField ExtField
x'17
             WireSize -> WireSize -> WireSize
forall a. Num a => a -> a -> a
+ UnknownField -> WireSize
P'.wireSizeUnknownField UnknownField
x'18)
  wirePutWithSize :: FieldType -> FileOptions -> PutM WireSize
wirePutWithSize FieldType
ft' self' :: FileOptions
self'@(FileOptions Maybe Utf8
x'1 Maybe Utf8
x'2 Maybe Bool
x'3 Maybe Bool
x'4 Maybe Bool
x'5 Maybe OptimizeMode
x'6 Maybe Utf8
x'7 Maybe Bool
x'8 Maybe Bool
x'9 Maybe Bool
x'10 Maybe Bool
x'11 Maybe Bool
x'12 Maybe Utf8
x'13 Maybe Utf8
x'14 Maybe Bool
x'15 Seq UninterpretedOption
x'16 ExtField
x'17 UnknownField
x'18)
   = case FieldType
ft' of
       FieldType
10 -> PutM WireSize
put'Fields
       FieldType
11 -> PutM WireSize
put'FieldsSized
       FieldType
_ -> FieldType -> FileOptions -> PutM WireSize
forall a b. Typeable a => FieldType -> a -> PutM b
P'.wirePutErr FieldType
ft' FileOptions
self'
    where
        put'Fields :: PutM WireSize
put'Fields
         = [PutM WireSize] -> PutM WireSize
forall (f :: * -> *).
Foldable f =>
f (PutM WireSize) -> PutM WireSize
P'.sequencePutWithSize
            [WireTag -> FieldType -> Maybe Utf8 -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
10 FieldType
9 Maybe Utf8
x'1, WireTag -> FieldType -> Maybe Utf8 -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
66 FieldType
9 Maybe Utf8
x'2, WireTag -> FieldType -> Maybe OptimizeMode -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
72 FieldType
14 Maybe OptimizeMode
x'6,
             WireTag -> FieldType -> Maybe Bool -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
80 FieldType
8 Maybe Bool
x'3, WireTag -> FieldType -> Maybe Utf8 -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
90 FieldType
9 Maybe Utf8
x'7, WireTag -> FieldType -> Maybe Bool -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
128 FieldType
8 Maybe Bool
x'8,
             WireTag -> FieldType -> Maybe Bool -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
136 FieldType
8 Maybe Bool
x'9, WireTag -> FieldType -> Maybe Bool -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
144 FieldType
8 Maybe Bool
x'10, WireTag -> FieldType -> Maybe Bool -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
160 FieldType
8 Maybe Bool
x'4,
             WireTag -> FieldType -> Maybe Bool -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
184 FieldType
8 Maybe Bool
x'11, WireTag -> FieldType -> Maybe Bool -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
216 FieldType
8 Maybe Bool
x'5, WireTag -> FieldType -> Maybe Bool -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
248 FieldType
8 Maybe Bool
x'12,
             WireTag -> FieldType -> Maybe Utf8 -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
290 FieldType
9 Maybe Utf8
x'13, WireTag -> FieldType -> Maybe Utf8 -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
298 FieldType
9 Maybe Utf8
x'14, WireTag -> FieldType -> Maybe Bool -> PutM WireSize
forall v.
Wire v =>
WireTag -> FieldType -> Maybe v -> PutM WireSize
P'.wirePutOptWithSize WireTag
304 FieldType
8 Maybe Bool
x'15,
             WireTag -> FieldType -> Seq UninterpretedOption -> PutM WireSize
forall v. Wire v => WireTag -> FieldType -> Seq v -> PutM WireSize
P'.wirePutRepWithSize WireTag
7994 FieldType
11 Seq UninterpretedOption
x'16, ExtField -> PutM WireSize
P'.wirePutExtFieldWithSize ExtField
x'17, UnknownField -> PutM WireSize
P'.wirePutUnknownFieldWithSize UnknownField
x'18]
        put'FieldsSized :: PutM WireSize
put'FieldsSized
         = let size' :: WireSize
size' = (WireSize, ByteString) -> WireSize
forall a b. (a, b) -> a
Prelude'.fst (PutM WireSize -> (WireSize, ByteString)
forall a. PutM a -> (a, ByteString)
P'.runPutM PutM WireSize
put'Fields)
               put'Size :: PutM WireSize
put'Size
                = do
                    WireSize -> Put
P'.putSize WireSize
size'
                    WireSize -> PutM WireSize
forall (m :: * -> *) a. Monad m => a -> m a
Prelude'.return (WireSize -> WireSize
P'.size'WireSize WireSize
size')
            in [PutM WireSize] -> PutM WireSize
forall (f :: * -> *).
Foldable f =>
f (PutM WireSize) -> PutM WireSize
P'.sequencePutWithSize [PutM WireSize
put'Size, PutM WireSize
put'Fields]
  wireGet :: FieldType -> Get FileOptions
wireGet FieldType
ft'
   = case FieldType
ft' of
       FieldType
10 -> (WireTag -> FileOptions -> Get FileOptions) -> Get FileOptions
forall message.
(Default message, ReflectDescriptor message) =>
(WireTag -> message -> Get message) -> Get message
P'.getBareMessageWith ((WireTag -> FileOptions -> Get FileOptions)
-> (WireTag -> FileOptions -> Get FileOptions)
-> WireTag
-> FileOptions
-> Get FileOptions
forall a.
(WireTag -> a -> Get a)
-> (WireTag -> a -> Get a) -> WireTag -> a -> Get a
P'.catch'Unknown' WireTag -> FileOptions -> Get FileOptions
forall a. UnknownMessage a => WireTag -> a -> Get a
P'.loadUnknown WireTag -> FileOptions -> Get FileOptions
update'Self)
       FieldType
11 -> (WireTag -> FileOptions -> Get FileOptions) -> Get FileOptions
forall message.
(Default message, ReflectDescriptor message) =>
(WireTag -> message -> Get message) -> Get message
P'.getMessageWith ((WireTag -> FileOptions -> Get FileOptions)
-> (WireTag -> FileOptions -> Get FileOptions)
-> WireTag
-> FileOptions
-> Get FileOptions
forall a.
(WireTag -> a -> Get a)
-> (WireTag -> a -> Get a) -> WireTag -> a -> Get a
P'.catch'Unknown' WireTag -> FileOptions -> Get FileOptions
forall a. UnknownMessage a => WireTag -> a -> Get a
P'.loadUnknown WireTag -> FileOptions -> Get FileOptions
update'Self)
       FieldType
_ -> FieldType -> Get FileOptions
forall a. Typeable a => FieldType -> Get a
P'.wireGetErr FieldType
ft'
    where
        update'Self :: WireTag -> FileOptions -> Get FileOptions
update'Self WireTag
wire'Tag FileOptions
old'Self
         = case WireTag
wire'Tag of
             WireTag
10 -> (Utf8 -> FileOptions) -> Get Utf8 -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Utf8
new'Field -> FileOptions
old'Self{java_package :: Maybe Utf8
java_package = Utf8 -> Maybe Utf8
forall a. a -> Maybe a
Prelude'.Just Utf8
new'Field}) (FieldType -> Get Utf8
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
9)
             WireTag
66 -> (Utf8 -> FileOptions) -> Get Utf8 -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Utf8
new'Field -> FileOptions
old'Self{java_outer_classname :: Maybe Utf8
java_outer_classname = Utf8 -> Maybe Utf8
forall a. a -> Maybe a
Prelude'.Just Utf8
new'Field}) (FieldType -> Get Utf8
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
9)
             WireTag
80 -> (Bool -> FileOptions) -> Get Bool -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Bool
new'Field -> FileOptions
old'Self{java_multiple_files :: Maybe Bool
java_multiple_files = Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
new'Field}) (FieldType -> Get Bool
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
8)
             WireTag
160 -> (Bool -> FileOptions) -> Get Bool -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Bool
new'Field -> FileOptions
old'Self{java_generate_equals_and_hash :: Maybe Bool
java_generate_equals_and_hash = Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
new'Field}) (FieldType -> Get Bool
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
8)
             WireTag
216 -> (Bool -> FileOptions) -> Get Bool -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Bool
new'Field -> FileOptions
old'Self{java_string_check_utf8 :: Maybe Bool
java_string_check_utf8 = Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
new'Field}) (FieldType -> Get Bool
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
8)
             WireTag
72 -> (OptimizeMode -> FileOptions)
-> Get OptimizeMode -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !OptimizeMode
new'Field -> FileOptions
old'Self{optimize_for :: Maybe OptimizeMode
optimize_for = OptimizeMode -> Maybe OptimizeMode
forall a. a -> Maybe a
Prelude'.Just OptimizeMode
new'Field}) (FieldType -> Get OptimizeMode
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
14)
             WireTag
90 -> (Utf8 -> FileOptions) -> Get Utf8 -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Utf8
new'Field -> FileOptions
old'Self{go_package :: Maybe Utf8
go_package = Utf8 -> Maybe Utf8
forall a. a -> Maybe a
Prelude'.Just Utf8
new'Field}) (FieldType -> Get Utf8
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
9)
             WireTag
128 -> (Bool -> FileOptions) -> Get Bool -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Bool
new'Field -> FileOptions
old'Self{cc_generic_services :: Maybe Bool
cc_generic_services = Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
new'Field}) (FieldType -> Get Bool
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
8)
             WireTag
136 -> (Bool -> FileOptions) -> Get Bool -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Bool
new'Field -> FileOptions
old'Self{java_generic_services :: Maybe Bool
java_generic_services = Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
new'Field}) (FieldType -> Get Bool
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
8)
             WireTag
144 -> (Bool -> FileOptions) -> Get Bool -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Bool
new'Field -> FileOptions
old'Self{py_generic_services :: Maybe Bool
py_generic_services = Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
new'Field}) (FieldType -> Get Bool
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
8)
             WireTag
184 -> (Bool -> FileOptions) -> Get Bool -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Bool
new'Field -> FileOptions
old'Self{deprecated :: Maybe Bool
deprecated = Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
new'Field}) (FieldType -> Get Bool
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
8)
             WireTag
248 -> (Bool -> FileOptions) -> Get Bool -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Bool
new'Field -> FileOptions
old'Self{cc_enable_arenas :: Maybe Bool
cc_enable_arenas = Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
new'Field}) (FieldType -> Get Bool
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
8)
             WireTag
290 -> (Utf8 -> FileOptions) -> Get Utf8 -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Utf8
new'Field -> FileOptions
old'Self{objc_class_prefix :: Maybe Utf8
objc_class_prefix = Utf8 -> Maybe Utf8
forall a. a -> Maybe a
Prelude'.Just Utf8
new'Field}) (FieldType -> Get Utf8
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
9)
             WireTag
298 -> (Utf8 -> FileOptions) -> Get Utf8 -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Utf8
new'Field -> FileOptions
old'Self{csharp_namespace :: Maybe Utf8
csharp_namespace = Utf8 -> Maybe Utf8
forall a. a -> Maybe a
Prelude'.Just Utf8
new'Field}) (FieldType -> Get Utf8
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
9)
             WireTag
304 -> (Bool -> FileOptions) -> Get Bool -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ !Bool
new'Field -> FileOptions
old'Self{javanano_use_deprecated_package :: Maybe Bool
javanano_use_deprecated_package = Bool -> Maybe Bool
forall a. a -> Maybe a
Prelude'.Just Bool
new'Field})
                     (FieldType -> Get Bool
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
8)
             WireTag
7994 -> (UninterpretedOption -> FileOptions)
-> Get UninterpretedOption -> Get FileOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap
                      (\ !UninterpretedOption
new'Field -> FileOptions
old'Self{uninterpreted_option :: Seq UninterpretedOption
uninterpreted_option = Seq UninterpretedOption
-> UninterpretedOption -> Seq UninterpretedOption
forall a. Seq a -> a -> Seq a
P'.append (FileOptions -> Seq UninterpretedOption
uninterpreted_option FileOptions
old'Self) UninterpretedOption
new'Field})
                      (FieldType -> Get UninterpretedOption
forall b. Wire b => FieldType -> Get b
P'.wireGet FieldType
11)
             WireTag
_ -> let (FieldId
field'Number, WireType
wire'Type) = WireTag -> (FieldId, WireType)
P'.splitWireTag WireTag
wire'Tag in
                   if [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
Prelude'.or [FieldId
1000 FieldId -> FieldId -> Bool
forall a. Ord a => a -> a -> Bool
<= FieldId
field'Number Bool -> Bool -> Bool
&& FieldId
field'Number FieldId -> FieldId -> Bool
forall a. Ord a => a -> a -> Bool
<= FieldId
18999, FieldId
20000 FieldId -> FieldId -> Bool
forall a. Ord a => a -> a -> Bool
<= FieldId
field'Number] then
                    FieldId -> WireType -> FileOptions -> Get FileOptions
forall a.
(ReflectDescriptor a, ExtendMessage a) =>
FieldId -> WireType -> a -> Get a
P'.loadExtension FieldId
field'Number WireType
wire'Type FileOptions
old'Self else FieldId -> WireType -> FileOptions -> Get FileOptions
forall a.
(Typeable a, ReflectDescriptor a) =>
FieldId -> WireType -> a -> Get a
P'.unknown FieldId
field'Number WireType
wire'Type FileOptions
old'Self

instance P'.MessageAPI msg' (msg' -> FileOptions) FileOptions where
  getVal :: msg' -> (msg' -> FileOptions) -> FileOptions
getVal msg'
m' msg' -> FileOptions
f' = msg' -> FileOptions
f' msg'
m'

instance P'.GPB FileOptions

instance P'.ReflectDescriptor FileOptions where
  getMessageInfo :: FileOptions -> GetMessageInfo
getMessageInfo FileOptions
_
   = Set WireTag -> Set WireTag -> GetMessageInfo
P'.GetMessageInfo ([WireTag] -> Set WireTag
forall a. [a] -> Set a
P'.fromDistinctAscList [])
      ([WireTag] -> Set WireTag
forall a. [a] -> Set a
P'.fromDistinctAscList [WireTag
10, WireTag
66, WireTag
72, WireTag
80, WireTag
90, WireTag
128, WireTag
136, WireTag
144, WireTag
160, WireTag
184, WireTag
216, WireTag
248, WireTag
290, WireTag
298, WireTag
304, WireTag
7994])
  reflectDescriptorInfo :: FileOptions -> DescriptorInfo
reflectDescriptorInfo FileOptions
_
   = String -> DescriptorInfo
forall a. Read a => String -> a
Prelude'.read
      String
"DescriptorInfo {descName = ProtoName {protobufName = FIName \".google.protobuf.FileOptions\", haskellPrefix = [MName \"Text\"], parentModule = [MName \"DescriptorProtos\"], baseName = MName \"FileOptions\"}, descFilePath = [\"Text\",\"DescriptorProtos\",\"FileOptions.hs\"], isGroup = False, fields = fromList [FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.java_package\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"java_package\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 1}, wireTag = WireTag {getWireTag = 10}, packedTag = Nothing, wireTagLength = 1, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 9}, typeName = Nothing, hsRawDefault = Nothing, hsDefault = Nothing},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.java_outer_classname\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"java_outer_classname\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 8}, wireTag = WireTag {getWireTag = 66}, packedTag = Nothing, wireTagLength = 1, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 9}, typeName = Nothing, hsRawDefault = Nothing, hsDefault = Nothing},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.java_multiple_files\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"java_multiple_files\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 10}, wireTag = WireTag {getWireTag = 80}, packedTag = Nothing, wireTagLength = 1, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 8}, typeName = Nothing, hsRawDefault = Just \"false\", hsDefault = Just (HsDef'Bool False)},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.java_generate_equals_and_hash\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"java_generate_equals_and_hash\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 20}, wireTag = WireTag {getWireTag = 160}, packedTag = Nothing, wireTagLength = 2, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 8}, typeName = Nothing, hsRawDefault = Just \"false\", hsDefault = Just (HsDef'Bool False)},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.java_string_check_utf8\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"java_string_check_utf8\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 27}, wireTag = WireTag {getWireTag = 216}, packedTag = Nothing, wireTagLength = 2, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 8}, typeName = Nothing, hsRawDefault = Just \"false\", hsDefault = Just (HsDef'Bool False)},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.optimize_for\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"optimize_for\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 9}, wireTag = WireTag {getWireTag = 72}, packedTag = Nothing, wireTagLength = 1, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 14}, typeName = Just (ProtoName {protobufName = FIName \".google.protobuf.FileOptions.OptimizeMode\", haskellPrefix = [MName \"Text\"], parentModule = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName = MName \"OptimizeMode\"}), hsRawDefault = Just \"SPEED\", hsDefault = Just (HsDef'Enum \"SPEED\")},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.go_package\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"go_package\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 11}, wireTag = WireTag {getWireTag = 90}, packedTag = Nothing, wireTagLength = 1, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 9}, typeName = Nothing, hsRawDefault = Nothing, hsDefault = Nothing},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.cc_generic_services\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"cc_generic_services\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 16}, wireTag = WireTag {getWireTag = 128}, packedTag = Nothing, wireTagLength = 2, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 8}, typeName = Nothing, hsRawDefault = Just \"false\", hsDefault = Just (HsDef'Bool False)},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.java_generic_services\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"java_generic_services\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 17}, wireTag = WireTag {getWireTag = 136}, packedTag = Nothing, wireTagLength = 2, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 8}, typeName = Nothing, hsRawDefault = Just \"false\", hsDefault = Just (HsDef'Bool False)},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.py_generic_services\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"py_generic_services\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 18}, wireTag = WireTag {getWireTag = 144}, packedTag = Nothing, wireTagLength = 2, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 8}, typeName = Nothing, hsRawDefault = Just \"false\", hsDefault = Just (HsDef'Bool False)},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.deprecated\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"deprecated\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 23}, wireTag = WireTag {getWireTag = 184}, packedTag = Nothing, wireTagLength = 2, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 8}, typeName = Nothing, hsRawDefault = Just \"false\", hsDefault = Just (HsDef'Bool False)},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.cc_enable_arenas\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"cc_enable_arenas\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 31}, wireTag = WireTag {getWireTag = 248}, packedTag = Nothing, wireTagLength = 2, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 8}, typeName = Nothing, hsRawDefault = Just \"false\", hsDefault = Just (HsDef'Bool False)},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.objc_class_prefix\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"objc_class_prefix\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 36}, wireTag = WireTag {getWireTag = 290}, packedTag = Nothing, wireTagLength = 2, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 9}, typeName = Nothing, hsRawDefault = Nothing, hsDefault = Nothing},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.csharp_namespace\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"csharp_namespace\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 37}, wireTag = WireTag {getWireTag = 298}, packedTag = Nothing, wireTagLength = 2, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 9}, typeName = Nothing, hsRawDefault = Nothing, hsDefault = Nothing},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.javanano_use_deprecated_package\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"javanano_use_deprecated_package\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 38}, wireTag = WireTag {getWireTag = 304}, packedTag = Nothing, wireTagLength = 2, isPacked = False, isRequired = False, canRepeat = False, mightPack = False, typeCode = FieldType {getFieldType = 8}, typeName = Nothing, hsRawDefault = Nothing, hsDefault = Nothing},FieldInfo {fieldName = ProtoFName {protobufName' = FIName \".google.protobuf.FileOptions.uninterpreted_option\", haskellPrefix' = [MName \"Text\"], parentModule' = [MName \"DescriptorProtos\",MName \"FileOptions\"], baseName' = FName \"uninterpreted_option\", baseNamePrefix' = \"\"}, fieldNumber = FieldId {getFieldId = 999}, wireTag = WireTag {getWireTag = 7994}, packedTag = Nothing, wireTagLength = 2, isPacked = False, isRequired = False, canRepeat = True, mightPack = False, typeCode = FieldType {getFieldType = 11}, typeName = Just (ProtoName {protobufName = FIName \".google.protobuf.UninterpretedOption\", haskellPrefix = [MName \"Text\"], parentModule = [MName \"DescriptorProtos\"], baseName = MName \"UninterpretedOption\"}), hsRawDefault = Nothing, hsDefault = Nothing}], descOneofs = fromList [], keys = fromList [], extRanges = [(FieldId {getFieldId = 1000},FieldId {getFieldId = 18999}),(FieldId {getFieldId = 20000},FieldId {getFieldId = 536870911})], knownKeys = fromList [], storeUnknown = True, lazyFields = False, makeLenses = False, jsonInstances = False}"

instance P'.TextType FileOptions where
  tellT :: String -> FileOptions -> Output
tellT = String -> FileOptions -> Output
forall a. TextMsg a => String -> a -> Output
P'.tellSubMessage
  getT :: String -> Parsec s () FileOptions
getT = String -> Parsec s () FileOptions
forall s a.
(Stream s Identity Char, TextMsg a) =>
String -> Parsec s () a
P'.getSubMessage

instance P'.TextMsg FileOptions where
  textPut :: FileOptions -> Output
textPut FileOptions
msg
   = do
       String -> Maybe Utf8 -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"java_package" (FileOptions -> Maybe Utf8
java_package FileOptions
msg)
       String -> Maybe Utf8 -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"java_outer_classname" (FileOptions -> Maybe Utf8
java_outer_classname FileOptions
msg)
       String -> Maybe Bool -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"java_multiple_files" (FileOptions -> Maybe Bool
java_multiple_files FileOptions
msg)
       String -> Maybe Bool -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"java_generate_equals_and_hash" (FileOptions -> Maybe Bool
java_generate_equals_and_hash FileOptions
msg)
       String -> Maybe Bool -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"java_string_check_utf8" (FileOptions -> Maybe Bool
java_string_check_utf8 FileOptions
msg)
       String -> Maybe OptimizeMode -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"optimize_for" (FileOptions -> Maybe OptimizeMode
optimize_for FileOptions
msg)
       String -> Maybe Utf8 -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"go_package" (FileOptions -> Maybe Utf8
go_package FileOptions
msg)
       String -> Maybe Bool -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"cc_generic_services" (FileOptions -> Maybe Bool
cc_generic_services FileOptions
msg)
       String -> Maybe Bool -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"java_generic_services" (FileOptions -> Maybe Bool
java_generic_services FileOptions
msg)
       String -> Maybe Bool -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"py_generic_services" (FileOptions -> Maybe Bool
py_generic_services FileOptions
msg)
       String -> Maybe Bool -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"deprecated" (FileOptions -> Maybe Bool
deprecated FileOptions
msg)
       String -> Maybe Bool -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"cc_enable_arenas" (FileOptions -> Maybe Bool
cc_enable_arenas FileOptions
msg)
       String -> Maybe Utf8 -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"objc_class_prefix" (FileOptions -> Maybe Utf8
objc_class_prefix FileOptions
msg)
       String -> Maybe Utf8 -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"csharp_namespace" (FileOptions -> Maybe Utf8
csharp_namespace FileOptions
msg)
       String -> Maybe Bool -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"javanano_use_deprecated_package" (FileOptions -> Maybe Bool
javanano_use_deprecated_package FileOptions
msg)
       String -> Seq UninterpretedOption -> Output
forall a. TextType a => String -> a -> Output
P'.tellT String
"uninterpreted_option" (FileOptions -> Seq UninterpretedOption
uninterpreted_option FileOptions
msg)
  textGet :: Parsec s () FileOptions
textGet
   = do
       [FileOptions -> FileOptions]
mods <- ParsecT s () Identity (FileOptions -> FileOptions)
-> ParsecT s () Identity ()
-> ParsecT s () Identity [FileOptions -> FileOptions]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
P'.sepEndBy
                ([ParsecT s () Identity (FileOptions -> FileOptions)]
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
P'.choice
                  [ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_package, ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_outer_classname, ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_multiple_files, ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_generate_equals_and_hash,
                   ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_string_check_utf8, ParsecT s () Identity (FileOptions -> FileOptions)
parse'optimize_for, ParsecT s () Identity (FileOptions -> FileOptions)
parse'go_package, ParsecT s () Identity (FileOptions -> FileOptions)
parse'cc_generic_services,
                   ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_generic_services, ParsecT s () Identity (FileOptions -> FileOptions)
parse'py_generic_services, ParsecT s () Identity (FileOptions -> FileOptions)
parse'deprecated, ParsecT s () Identity (FileOptions -> FileOptions)
parse'cc_enable_arenas,
                   ParsecT s () Identity (FileOptions -> FileOptions)
parse'objc_class_prefix, ParsecT s () Identity (FileOptions -> FileOptions)
parse'csharp_namespace, ParsecT s () Identity (FileOptions -> FileOptions)
parse'javanano_use_deprecated_package,
                   ParsecT s () Identity (FileOptions -> FileOptions)
parse'uninterpreted_option])
                ParsecT s () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
P'.spaces
       FileOptions -> Parsec s () FileOptions
forall (m :: * -> *) a. Monad m => a -> m a
Prelude'.return ((FileOptions -> (FileOptions -> FileOptions) -> FileOptions)
-> FileOptions -> [FileOptions -> FileOptions] -> FileOptions
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Prelude'.foldl' (\ FileOptions
v FileOptions -> FileOptions
f -> FileOptions -> FileOptions
f FileOptions
v) FileOptions
forall a. Default a => a
P'.defaultValue [FileOptions -> FileOptions]
mods)
    where
        parse'java_package :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_package = (Maybe Utf8 -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Utf8)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Utf8
v FileOptions
o -> FileOptions
o{java_package :: Maybe Utf8
java_package = Maybe Utf8
v}) (ParsecT s () Identity (Maybe Utf8)
-> ParsecT s () Identity (Maybe Utf8)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Utf8)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"java_package"))
        parse'java_outer_classname :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_outer_classname = (Maybe Utf8 -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Utf8)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Utf8
v FileOptions
o -> FileOptions
o{java_outer_classname :: Maybe Utf8
java_outer_classname = Maybe Utf8
v}) (ParsecT s () Identity (Maybe Utf8)
-> ParsecT s () Identity (Maybe Utf8)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Utf8)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"java_outer_classname"))
        parse'java_multiple_files :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_multiple_files = (Maybe Bool -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Bool
v FileOptions
o -> FileOptions
o{java_multiple_files :: Maybe Bool
java_multiple_files = Maybe Bool
v}) (ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (Maybe Bool)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Bool)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"java_multiple_files"))
        parse'java_generate_equals_and_hash :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_generate_equals_and_hash
         = (Maybe Bool -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Bool
v FileOptions
o -> FileOptions
o{java_generate_equals_and_hash :: Maybe Bool
java_generate_equals_and_hash = Maybe Bool
v}) (ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (Maybe Bool)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Bool)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"java_generate_equals_and_hash"))
        parse'java_string_check_utf8 :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_string_check_utf8
         = (Maybe Bool -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Bool
v FileOptions
o -> FileOptions
o{java_string_check_utf8 :: Maybe Bool
java_string_check_utf8 = Maybe Bool
v}) (ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (Maybe Bool)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Bool)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"java_string_check_utf8"))
        parse'optimize_for :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'optimize_for = (Maybe OptimizeMode -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe OptimizeMode)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe OptimizeMode
v FileOptions
o -> FileOptions
o{optimize_for :: Maybe OptimizeMode
optimize_for = Maybe OptimizeMode
v}) (ParsecT s () Identity (Maybe OptimizeMode)
-> ParsecT s () Identity (Maybe OptimizeMode)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe OptimizeMode)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"optimize_for"))
        parse'go_package :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'go_package = (Maybe Utf8 -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Utf8)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Utf8
v FileOptions
o -> FileOptions
o{go_package :: Maybe Utf8
go_package = Maybe Utf8
v}) (ParsecT s () Identity (Maybe Utf8)
-> ParsecT s () Identity (Maybe Utf8)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Utf8)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"go_package"))
        parse'cc_generic_services :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'cc_generic_services = (Maybe Bool -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Bool
v FileOptions
o -> FileOptions
o{cc_generic_services :: Maybe Bool
cc_generic_services = Maybe Bool
v}) (ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (Maybe Bool)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Bool)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"cc_generic_services"))
        parse'java_generic_services :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'java_generic_services
         = (Maybe Bool -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Bool
v FileOptions
o -> FileOptions
o{java_generic_services :: Maybe Bool
java_generic_services = Maybe Bool
v}) (ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (Maybe Bool)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Bool)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"java_generic_services"))
        parse'py_generic_services :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'py_generic_services = (Maybe Bool -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Bool
v FileOptions
o -> FileOptions
o{py_generic_services :: Maybe Bool
py_generic_services = Maybe Bool
v}) (ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (Maybe Bool)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Bool)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"py_generic_services"))
        parse'deprecated :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'deprecated = (Maybe Bool -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Bool
v FileOptions
o -> FileOptions
o{deprecated :: Maybe Bool
deprecated = Maybe Bool
v}) (ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (Maybe Bool)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Bool)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"deprecated"))
        parse'cc_enable_arenas :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'cc_enable_arenas = (Maybe Bool -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Bool
v FileOptions
o -> FileOptions
o{cc_enable_arenas :: Maybe Bool
cc_enable_arenas = Maybe Bool
v}) (ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (Maybe Bool)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Bool)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"cc_enable_arenas"))
        parse'objc_class_prefix :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'objc_class_prefix = (Maybe Utf8 -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Utf8)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Utf8
v FileOptions
o -> FileOptions
o{objc_class_prefix :: Maybe Utf8
objc_class_prefix = Maybe Utf8
v}) (ParsecT s () Identity (Maybe Utf8)
-> ParsecT s () Identity (Maybe Utf8)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Utf8)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"objc_class_prefix"))
        parse'csharp_namespace :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'csharp_namespace = (Maybe Utf8 -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Utf8)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Utf8
v FileOptions
o -> FileOptions
o{csharp_namespace :: Maybe Utf8
csharp_namespace = Maybe Utf8
v}) (ParsecT s () Identity (Maybe Utf8)
-> ParsecT s () Identity (Maybe Utf8)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Utf8)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"csharp_namespace"))
        parse'javanano_use_deprecated_package :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'javanano_use_deprecated_package
         = (Maybe Bool -> FileOptions -> FileOptions)
-> ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ Maybe Bool
v FileOptions
o -> FileOptions
o{javanano_use_deprecated_package :: Maybe Bool
javanano_use_deprecated_package = Maybe Bool
v}) (ParsecT s () Identity (Maybe Bool)
-> ParsecT s () Identity (Maybe Bool)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity (Maybe Bool)
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"javanano_use_deprecated_package"))
        parse'uninterpreted_option :: ParsecT s () Identity (FileOptions -> FileOptions)
parse'uninterpreted_option
         = (UninterpretedOption -> FileOptions -> FileOptions)
-> ParsecT s () Identity UninterpretedOption
-> ParsecT s () Identity (FileOptions -> FileOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude'.fmap (\ UninterpretedOption
v FileOptions
o -> FileOptions
o{uninterpreted_option :: Seq UninterpretedOption
uninterpreted_option = Seq UninterpretedOption
-> UninterpretedOption -> Seq UninterpretedOption
forall a. Seq a -> a -> Seq a
P'.append (FileOptions -> Seq UninterpretedOption
uninterpreted_option FileOptions
o) UninterpretedOption
v})
            (ParsecT s () Identity UninterpretedOption
-> ParsecT s () Identity UninterpretedOption
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P'.try (String -> ParsecT s () Identity UninterpretedOption
forall a s.
(TextType a, Stream s Identity Char) =>
String -> Parsec s () a
P'.getT String
"uninterpreted_option"))