{-# LANGUAGE CPP                       #-}
{-# LANGUAGE DataKinds                 #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts          #-}
{-# LANGUAGE FlexibleInstances         #-}
{-# LANGUAGE LambdaCase                #-}
{-# LANGUAGE MultiWayIf                #-}
{-# LANGUAGE NamedFieldPuns            #-}
{-# LANGUAGE OverloadedStrings         #-}
{-# LANGUAGE QuasiQuotes               #-}
{-# LANGUAGE RecordWildCards           #-}
{-# LANGUAGE ScopedTypeVariables       #-}
{-# LANGUAGE StandaloneDeriving        #-}
{-# LANGUAGE TupleSections             #-}
{-# LANGUAGE TypeApplications          #-}
{-# LANGUAGE TypeOperators             #-}
{-# LANGUAGE ViewPatterns              #-}

{-| This module provides functions to generate Haskell declarations for protobuf
    messages
-}

module Proto3.Suite.DotProto.Generate
  ( CompileError(..)
  , TypeContext
  , CompileArgs(..)
  , compileDotProtoFile
  , compileDotProtoFileOrDie
  , renameProtoFile
  , hsModuleForDotProto
  , renderHsModuleForDotProto
  , readDotProtoWithContext
  ) where

import           Control.Applicative
import           Control.Lens                   ((&), ix, over, has, filtered)
import           Control.Monad.Except
import           Data.Char
import           Data.Coerce
import           Data.Either                    (partitionEithers)
import           Data.List                      (find, intercalate, nub, sortBy, stripPrefix)
import qualified Data.List.NonEmpty             as NE
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.Map                       as M
import           Data.Maybe                     (fromMaybe)
import           Data.Monoid
import           Data.Ord                       (comparing)
import qualified Data.Set                       as S
import           Data.String                    (fromString)
import qualified Data.Text                      as T
import           Language.Haskell.Parser        (ParseResult(..), parseModule)
import           Language.Haskell.Pretty
import           Language.Haskell.Syntax
import qualified NeatInterpolation              as Neat
import           Prelude                        hiding (FilePath)
import           Proto3.Suite.DotProto
import           Proto3.Suite.DotProto.AST.Lens
import           Proto3.Suite.DotProto.Internal
import           Proto3.Wire.Types              (FieldNumber (..))
import Text.Parsec (Parsec, alphaNum, eof, parse, satisfy, try)
import qualified Text.Parsec as Parsec
import qualified Turtle
import           Turtle                         (FilePath, (</>), (<.>))

--------------------------------------------------------------------------------

--
-- * Public interface
--
data CompileArgs = CompileArgs
  { CompileArgs -> [FilePath]
includeDir         :: [FilePath]
  , CompileArgs -> [FilePath]
extraInstanceFiles :: [FilePath]
  , CompileArgs -> FilePath
inputProto         :: FilePath
  , CompileArgs -> FilePath
outputDir          :: FilePath
  }

-- | Generate a Haskell module corresponding to a @.proto@ file
compileDotProtoFile :: CompileArgs -> IO (Either CompileError ())
compileDotProtoFile :: CompileArgs -> IO (Either CompileError ())
compileDotProtoFile CompileArgs{FilePath
[FilePath]
outputDir :: FilePath
inputProto :: FilePath
extraInstanceFiles :: [FilePath]
includeDir :: [FilePath]
outputDir :: CompileArgs -> FilePath
inputProto :: CompileArgs -> FilePath
extraInstanceFiles :: CompileArgs -> [FilePath]
includeDir :: CompileArgs -> [FilePath]
..} = ExceptT CompileError IO () -> IO (Either CompileError ())
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT CompileError IO () -> IO (Either CompileError ()))
-> ExceptT CompileError IO () -> IO (Either CompileError ())
forall a b. (a -> b) -> a -> b
$ do
  (DotProto
dotProto, TypeContext
importTypeContext) <- [FilePath]
-> FilePath -> ExceptT CompileError IO (DotProto, TypeContext)
forall (m :: * -> *).
(MonadError CompileError m, MonadIO m) =>
[FilePath] -> FilePath -> m (DotProto, TypeContext)
readDotProtoWithContext [FilePath]
includeDir FilePath
inputProto
  NonEmpty FilePath
modulePathPieces <- (FilePath -> ExceptT CompileError IO FilePath)
-> NonEmpty FilePath -> ExceptT CompileError IO (NonEmpty FilePath)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse FilePath -> ExceptT CompileError IO FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> m FilePath
renameProtoFile (DotProto -> NonEmpty FilePath
toModuleComponents DotProto
dotProto)

  let relativePath :: FilePath
relativePath = (FilePath -> FilePath -> FilePath)
-> FilePath -> [FilePath] -> FilePath
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr FilePath -> FilePath -> FilePath
combine FilePath
forall a. Monoid a => a
mempty ((FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath
forall a. IsString a => FilePath -> a
fromString ([FilePath] -> [FilePath]) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ NonEmpty FilePath -> [FilePath]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty FilePath
modulePathPieces) FilePath -> FilePath -> FilePath
<.> FilePath
"hs"
      combine :: FilePath -> FilePath -> FilePath
combine FilePath
p1 FilePath
p2 | FilePath
p2 FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
forall a. Monoid a => a
mempty = FilePath
p1
      combine FilePath
p1 FilePath
p2 = FilePath
p1 FilePath -> FilePath -> FilePath
</> FilePath
p2
  let modulePath :: FilePath
modulePath = FilePath
outputDir FilePath -> FilePath -> FilePath
</> FilePath
relativePath

  FilePath -> ExceptT CompileError IO ()
forall (io :: * -> *). MonadIO io => FilePath -> io ()
Turtle.mktree (FilePath -> FilePath
Turtle.directory FilePath
modulePath)

  ([HsImportDecl], [HsDecl])
extraInstances <- (FilePath -> ExceptT CompileError IO ([HsImportDecl], [HsDecl]))
-> [FilePath] -> ExceptT CompileError IO ([HsImportDecl], [HsDecl])
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m, Monoid b, Semigroup b) =>
(a -> m b) -> t a -> m b
foldMapM FilePath -> ExceptT CompileError IO ([HsImportDecl], [HsDecl])
forall (m :: * -> *).
(MonadIO m, MonadError CompileError m) =>
FilePath -> m ([HsImportDecl], [HsDecl])
getExtraInstances [FilePath]
extraInstanceFiles
  FilePath
haskellModule <- ([HsImportDecl], [HsDecl])
-> DotProto -> TypeContext -> ExceptT CompileError IO FilePath
forall (m :: * -> *).
MonadError CompileError m =>
([HsImportDecl], [HsDecl]) -> DotProto -> TypeContext -> m FilePath
renderHsModuleForDotProto ([HsImportDecl], [HsDecl])
extraInstances DotProto
dotProto TypeContext
importTypeContext

  IO () -> ExceptT CompileError IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (FilePath -> FilePath -> IO ()
writeFile (FilePath -> FilePath
Turtle.encodeString FilePath
modulePath) FilePath
haskellModule)
  where
    toModuleComponents :: DotProto -> NonEmpty String
    toModuleComponents :: DotProto -> NonEmpty FilePath
toModuleComponents = Path -> NonEmpty FilePath
components (Path -> NonEmpty FilePath)
-> (DotProto -> Path) -> DotProto -> NonEmpty FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotProtoMeta -> Path
metaModulePath (DotProtoMeta -> Path)
-> (DotProto -> DotProtoMeta) -> DotProto -> Path
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotProto -> DotProtoMeta
protoMeta

-- | Same as 'compileDotProtoFile', except terminates the program with an error
-- message on failure.
compileDotProtoFileOrDie :: CompileArgs -> IO ()
compileDotProtoFileOrDie :: CompileArgs -> IO ()
compileDotProtoFileOrDie CompileArgs
args = CompileArgs -> IO (Either CompileError ())
compileDotProtoFile CompileArgs
args IO (Either CompileError ())
-> (Either CompileError () -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
  Left CompileError
e -> do
    -- TODO: pretty print the error messages
    let errText :: Text
errText          = Format Text (CompileError -> Text) -> CompileError -> Text
forall r. Format Text r -> r
Turtle.format Format Text (CompileError -> Text)
forall a r. Show a => Format r (a -> r)
Turtle.w  CompileError
e
    let dotProtoPathText :: Text
dotProtoPathText = Format Text (FilePath -> Text) -> FilePath -> Text
forall r. Format Text r -> r
Turtle.format Format Text (FilePath -> Text)
forall r. Format r (FilePath -> r)
Turtle.fp (CompileArgs -> FilePath
inputProto CompileArgs
args)
    Text -> IO ()
forall (m :: * -> *) a. MonadIO m => Text -> m a
dieLines [Neat.text|
      Error: failed to compile "${dotProtoPathText}":

      ${errText}
    |]
  Either CompileError ()
_ -> () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

-- | Renaming protobuf file names to valid Haskell module names.
--
-- By convention, protobuf filenames are snake case. 'rnProtoFile' renames
-- snake-cased protobuf filenames by:
--
-- * Replacing occurrences of one or more underscores followed by an
-- alphabetical character with one less underscore.
--
-- * Capitalizing the first character following the string of underscores.
--
-- ==== __Examples__
--
-- >>> renameProtoFile @(Either CompileError) "abc_xyz"
-- Right "AbcXyz"
--
-- >>> renameProtoFile @(Either CompileError) "abc_1bc"
-- Left (InvalidModuleName "abc_1bc")
--
-- >>> renameProtoFile @(Either CompileError) "_"
-- Left (InvalidModuleName "_")
renameProtoFile :: MonadError CompileError m => String -> m String
renameProtoFile :: FilePath -> m FilePath
renameProtoFile FilePath
filename =
  case Parsec FilePath () (FilePath, [(FilePath, FilePath)], FilePath)
-> FilePath
-> FilePath
-> Either ParseError (FilePath, [(FilePath, FilePath)], FilePath)
forall s t a.
Stream s Identity t =>
Parsec s () a -> FilePath -> s -> Either ParseError a
parse Parsec FilePath () (FilePath, [(FilePath, FilePath)], FilePath)
parser FilePath
"" FilePath
filename of
    Left {} -> CompileError -> m FilePath
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (FilePath -> CompileError
InvalidModuleName FilePath
filename)
    Right (FilePath
nm, [(FilePath, FilePath)]
ps, FilePath
sn) -> FilePath -> m FilePath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> FilePath
toUpperFirst FilePath
nm FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [(FilePath, FilePath)] -> FilePath
rename [(FilePath, FilePath)]
ps FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
sn)
  where
    rename :: [(String, String)] -> String
    rename :: [(FilePath, FilePath)] -> FilePath
rename = ((FilePath, FilePath) -> FilePath)
-> [(FilePath, FilePath)] -> FilePath
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (((FilePath, FilePath) -> FilePath)
 -> [(FilePath, FilePath)] -> FilePath)
-> ((FilePath, FilePath) -> FilePath)
-> [(FilePath, FilePath)]
-> FilePath
forall a b. (a -> b) -> a -> b
$ \(FilePath
us, FilePath
nm) ->
      Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
drop Int
1 FilePath
us FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
toUpperFirst FilePath
nm

    parser :: Parsec String () (String, [(String, String)], String)
    parser :: Parsec FilePath () (FilePath, [(FilePath, FilePath)], FilePath)
parser = do
      FilePath
nm <- Parsec FilePath () FilePath
pName
      [(FilePath, FilePath)]
ps <- ParsecT FilePath () Identity (FilePath, FilePath)
-> ParsecT FilePath () Identity [(FilePath, FilePath)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
Parsec.many (ParsecT FilePath () Identity (FilePath, FilePath)
-> ParsecT FilePath () Identity (FilePath, FilePath)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT FilePath () Identity (FilePath, FilePath)
pNamePart)
      FilePath
sn <- ParsecT FilePath () Identity Char -> Parsec FilePath () FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
Parsec.many ((Char -> Bool) -> ParsecT FilePath () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_'))
      (FilePath, [(FilePath, FilePath)], FilePath)
-> Parsec FilePath () (FilePath, [(FilePath, FilePath)], FilePath)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath
nm, [(FilePath, FilePath)]
ps, FilePath
sn) Parsec FilePath () (FilePath, [(FilePath, FilePath)], FilePath)
-> ParsecT FilePath () Identity ()
-> Parsec FilePath () (FilePath, [(FilePath, FilePath)], FilePath)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT FilePath () Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof

    pNamePart :: Parsec String () (String, String)
    pNamePart :: ParsecT FilePath () Identity (FilePath, FilePath)
pNamePart = (FilePath -> FilePath -> (FilePath, FilePath))
-> Parsec FilePath () FilePath
-> Parsec FilePath () FilePath
-> ParsecT FilePath () Identity (FilePath, FilePath)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) (ParsecT FilePath () Identity Char -> Parsec FilePath () FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
Parsec.many1 ((Char -> Bool) -> ParsecT FilePath () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_'))) Parsec FilePath () FilePath
pName

    pName :: Parsec String () String
    pName :: Parsec FilePath () FilePath
pName = (Char -> FilePath -> FilePath)
-> ParsecT FilePath () Identity Char
-> Parsec FilePath () FilePath
-> Parsec FilePath () FilePath
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:) ((Char -> Bool) -> ParsecT FilePath () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
satisfy Char -> Bool
isAlpha) (ParsecT FilePath () Identity Char -> Parsec FilePath () FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
Parsec.many ParsecT FilePath () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
alphaNum)

-- | Compile a 'DotProto' AST into a 'String' representing the Haskell
--   source of a module implementing types and instances for the .proto
--   messages and enums.
renderHsModuleForDotProto
    :: MonadError CompileError m
    => ([HsImportDecl],[HsDecl]) -> DotProto -> TypeContext -> m String
renderHsModuleForDotProto :: ([HsImportDecl], [HsDecl]) -> DotProto -> TypeContext -> m FilePath
renderHsModuleForDotProto ([HsImportDecl], [HsDecl])
extraInstanceFiles DotProto
dotProto TypeContext
importCtxt = do
    HsModule
haskellModule <- ([HsImportDecl], [HsDecl]) -> DotProto -> TypeContext -> m HsModule
forall (m :: * -> *).
MonadError CompileError m =>
([HsImportDecl], [HsDecl]) -> DotProto -> TypeContext -> m HsModule
hsModuleForDotProto ([HsImportDecl], [HsDecl])
extraInstanceFiles DotProto
dotProto TypeContext
importCtxt
    FilePath -> m FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> FilePath
T.unpack Text
header FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ HsModule -> FilePath
forall a. Pretty a => a -> FilePath
prettyPrint HsModule
haskellModule)
  where
    header :: Text
header = [Neat.text|
      {-# LANGUAGE DeriveGeneric     #-}
      {-# LANGUAGE DeriveAnyClass    #-}
      {-# LANGUAGE DataKinds         #-}
      {-# LANGUAGE GADTs             #-}
      {-# LANGUAGE TypeApplications  #-}
      {-# LANGUAGE OverloadedStrings #-}
      {-# OPTIONS_GHC -fno-warn-unused-imports       #-}
      {-# OPTIONS_GHC -fno-warn-name-shadowing       #-}
      {-# OPTIONS_GHC -fno-warn-unused-matches       #-}
      {-# OPTIONS_GHC -fno-warn-missing-export-lists #-}

      -- | Generated by Haskell protocol buffer compiler. DO NOT EDIT!
    |]

-- | Compile a Haskell module AST given a 'DotProto' package AST.
-- Instances given in @eis@ override those otherwise generated.
hsModuleForDotProto
    :: MonadError CompileError m
    => ([HsImportDecl], [HsDecl])
    -- ^ Extra user-define instances that override default generated instances
    -> DotProto
    -- ^
    -> TypeContext
    -- ^
    -> m HsModule
hsModuleForDotProto :: ([HsImportDecl], [HsDecl]) -> DotProto -> TypeContext -> m HsModule
hsModuleForDotProto
    ([HsImportDecl]
extraImports, [HsDecl]
extraInstances)
    dotProto :: DotProto
dotProto@DotProto{ protoMeta :: DotProto -> DotProtoMeta
protoMeta = DotProtoMeta { metaModulePath :: DotProtoMeta -> Path
metaModulePath = Path
modulePath }
                     , DotProtoPackageSpec
protoPackage :: DotProto -> DotProtoPackageSpec
protoPackage :: DotProtoPackageSpec
protoPackage
                     , [DotProtoDefinition]
protoDefinitions :: DotProto -> [DotProtoDefinition]
protoDefinitions :: [DotProtoDefinition]
protoDefinitions
                     }
    TypeContext
importTypeContext
  = do
       DotProtoIdentifier
packageIdentifier <- DotProtoPackageSpec -> m DotProtoIdentifier
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoPackageSpec -> m DotProtoIdentifier
protoPackageName DotProtoPackageSpec
protoPackage
       Module
moduleName <- Path -> m Module
forall (m :: * -> *). MonadError CompileError m => Path -> m Module
modulePathModName Path
modulePath

       [HsImportDecl]
typeContextImports <- TypeContext -> m [HsImportDecl]
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> m [HsImportDecl]
ctxtImports TypeContext
importTypeContext

       let hasService :: Bool
hasService = Getting
  Any
  [DotProtoDefinition]
  (FilePath, DotProtoIdentifier, [DotProtoServicePart])
-> [DotProtoDefinition] -> Bool
forall s a. Getting Any s a -> s -> Bool
has ((DotProtoDefinition -> Const Any DotProtoDefinition)
-> [DotProtoDefinition] -> Const Any [DotProtoDefinition]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse((DotProtoDefinition -> Const Any DotProtoDefinition)
 -> [DotProtoDefinition] -> Const Any [DotProtoDefinition])
-> (((FilePath, DotProtoIdentifier, [DotProtoServicePart])
     -> Const Any (FilePath, DotProtoIdentifier, [DotProtoServicePart]))
    -> DotProtoDefinition -> Const Any DotProtoDefinition)
-> Getting
     Any
     [DotProtoDefinition]
     (FilePath, DotProtoIdentifier, [DotProtoServicePart])
forall b c a. (b -> c) -> (a -> b) -> a -> c
.((FilePath, DotProtoIdentifier, [DotProtoServicePart])
 -> Const Any (FilePath, DotProtoIdentifier, [DotProtoServicePart]))
-> DotProtoDefinition -> Const Any DotProtoDefinition
Prism'
  DotProtoDefinition
  (FilePath, DotProtoIdentifier, [DotProtoServicePart])
_DotProtoService) [DotProtoDefinition]
protoDefinitions

       let importDeclarations :: [HsImportDecl]
importDeclarations = [[HsImportDecl]] -> [HsImportDecl]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ Bool -> [HsImportDecl]
defaultImports Bool
hasService, [HsImportDecl]
extraImports, [HsImportDecl]
typeContextImports ]

       TypeContext
typeContext <- DotProto -> m TypeContext
forall (m :: * -> *).
MonadError CompileError m =>
DotProto -> m TypeContext
dotProtoTypeContext DotProto
dotProto

       let toDotProtoDeclaration :: DotProtoDefinition -> m [HsDecl]
toDotProtoDeclaration =
             DotProtoIdentifier
-> TypeContext -> DotProtoDefinition -> m [HsDecl]
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier
-> TypeContext -> DotProtoDefinition -> m [HsDecl]
dotProtoDefinitionD DotProtoIdentifier
packageIdentifier (TypeContext
typeContext TypeContext -> TypeContext -> TypeContext
forall a. Semigroup a => a -> a -> a
<> TypeContext
importTypeContext)

       let extraInstances' :: [HsDecl]
extraInstances' = Module -> [HsDecl] -> [HsDecl]
instancesForModule Module
moduleName [HsDecl]
extraInstances

       [HsDecl]
decls <- [HsDecl] -> [HsDecl] -> [HsDecl]
replaceHsInstDecls [HsDecl]
extraInstances' ([HsDecl] -> [HsDecl]) -> m [HsDecl] -> m [HsDecl]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                (DotProtoDefinition -> m [HsDecl])
-> [DotProtoDefinition] -> m [HsDecl]
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m, Monoid b, Semigroup b) =>
(a -> m b) -> t a -> m b
foldMapM DotProtoDefinition -> m [HsDecl]
toDotProtoDeclaration [DotProtoDefinition]
protoDefinitions

       HsModule -> m HsModule
forall (m :: * -> *) a. Monad m => a -> m a
return (Module
-> Maybe [HsExportSpec] -> [HsImportDecl] -> [HsDecl] -> HsModule
module_ Module
moduleName Maybe [HsExportSpec]
forall a. Maybe a
Nothing [HsImportDecl]
importDeclarations [HsDecl]
decls)

getExtraInstances
    :: (MonadIO m, MonadError CompileError m)
    => FilePath -> m ([HsImportDecl], [HsDecl])
getExtraInstances :: FilePath -> m ([HsImportDecl], [HsDecl])
getExtraInstances FilePath
extraInstanceFile = do

  FilePath
contents <- IO FilePath -> m FilePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (FilePath -> IO FilePath
readFile (FilePath -> FilePath
Turtle.encodeString FilePath
extraInstanceFile))

  case FilePath -> ParseResult HsModule
parseModule FilePath
contents of
    ParseOk (HsModule SrcLoc
_srcloc Module
_mod Maybe [HsExportSpec]
_es [HsImportDecl]
idecls [HsDecl]
decls) -> do
      let isInstDecl :: HsDecl -> Bool
isInstDecl HsInstDecl{} = Bool
True
          isInstDecl HsDecl
_            = Bool
False

      ([HsImportDecl], [HsDecl]) -> m ([HsImportDecl], [HsDecl])
forall (m :: * -> *) a. Monad m => a -> m a
return ([HsImportDecl]
idecls, (HsDecl -> Bool) -> [HsDecl] -> [HsDecl]
forall a. (a -> Bool) -> [a] -> [a]
filter HsDecl -> Bool
isInstDecl [HsDecl]
decls) --TODO give compile result

    ParseFailed SrcLoc
srcLoc FilePath
err -> do
      let srcLocText :: Text
srcLocText = Format Text (SrcLoc -> Text) -> SrcLoc -> Text
forall r. Format Text r -> r
Turtle.format Format Text (SrcLoc -> Text)
forall a r. Show a => Format r (a -> r)
Turtle.w SrcLoc
srcLoc

      let errText :: Text
errText = FilePath -> Text
T.pack FilePath
err

      let message :: Text
message = [Neat.text|
            Error: Failed to parse instance file

            ${srcLocText}: ${errText}
          |]

      FilePath -> m ([HsImportDecl], [HsDecl])
forall (m :: * -> *) a.
MonadError CompileError m =>
FilePath -> m a
internalError (Text -> FilePath
T.unpack Text
message)

-- | This very specific function will only work for the qualification on the very first type
-- in the object of an instance declaration. Those are the only sort of instance declarations
-- generated within this code, so it suffices.
instancesForModule :: Module -> [HsDecl] -> [HsDecl]
instancesForModule :: Module -> [HsDecl] -> [HsDecl]
instancesForModule Module
m = (HsDecl -> [HsDecl] -> [HsDecl])
-> [HsDecl] -> [HsDecl] -> [HsDecl]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr HsDecl -> [HsDecl] -> [HsDecl]
go []
   where go :: HsDecl -> [HsDecl] -> [HsDecl]
go HsDecl
x [HsDecl]
xs = case HsDecl
x of
             HsInstDecl SrcLoc
a HsContext
b HsQName
c (HsTyCon (Qual Module
tm  HsName
i):[HsType]
ts) [HsDecl]
d ->
                        if Module
m Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
tm then SrcLoc -> HsContext -> HsQName -> [HsType] -> [HsDecl] -> HsDecl
HsInstDecl SrcLoc
a HsContext
b HsQName
c (HsQName -> HsType
HsTyCon (HsName -> HsQName
UnQual HsName
i)HsType -> [HsType] -> [HsType]
forall a. a -> [a] -> [a]
:[HsType]
ts) [HsDecl]
dHsDecl -> [HsDecl] -> [HsDecl]
forall a. a -> [a] -> [a]
:[HsDecl]
xs else [HsDecl]
xs
             HsDecl
_ -> [HsDecl]
xs

-- | For each thing in @base@ replaces it if it finds a matching @override@
replaceHsInstDecls :: [HsDecl] -> [HsDecl] -> [HsDecl]
replaceHsInstDecls :: [HsDecl] -> [HsDecl] -> [HsDecl]
replaceHsInstDecls [HsDecl]
overrides [HsDecl]
base = (HsDecl -> [HsDecl]) -> [HsDecl] -> [HsDecl]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap HsDecl -> [HsDecl]
mbReplace [HsDecl]
base
  where
    -- instances defined separately from data type definition:
    mbReplace :: HsDecl -> [HsDecl]
mbReplace hid :: HsDecl
hid@(HsInstDecl SrcLoc
_ HsContext
_ HsQName
qn [HsType]
tys [HsDecl]
_) =
        (HsDecl -> [HsDecl] -> [HsDecl]
forall a. a -> [a] -> [a]
: []) (HsDecl -> [HsDecl])
-> (Maybe HsDecl -> HsDecl) -> Maybe HsDecl -> [HsDecl]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsDecl -> Maybe HsDecl -> HsDecl
forall a. a -> Maybe a -> a
fromMaybe HsDecl
hid (Maybe HsDecl -> [HsDecl]) -> Maybe HsDecl -> [HsDecl]
forall a b. (a -> b) -> a -> b
$ HsQName -> [HsType] -> Maybe HsDecl
search HsQName
qn [HsType]
tys

    -- instances listed in "deriving" clause of data type definition:
    mbReplace (HsDataDecl SrcLoc
loc HsContext
ctx HsName
tyn [HsName]
names [HsConDecl]
def [HsQName]
insts) =
        let ([HsQName]
uncustomized, [HsDecl]
customized) = [Either HsQName HsDecl] -> ([HsQName], [HsDecl])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ((HsQName -> Either HsQName HsDecl)
-> [HsQName] -> [Either HsQName HsDecl]
forall a b. (a -> b) -> [a] -> [b]
map (HsName -> HsQName -> Either HsQName HsDecl
deriv HsName
tyn) [HsQName]
insts)
        in SrcLoc
-> HsContext
-> HsName
-> [HsName]
-> [HsConDecl]
-> [HsQName]
-> HsDecl
HsDataDecl SrcLoc
loc HsContext
ctx HsName
tyn [HsName]
names [HsConDecl]
def [HsQName]
uncustomized HsDecl -> [HsDecl] -> [HsDecl]
forall a. a -> [a] -> [a]
: [HsDecl]
customized

    -- instances listed in "deriving" clause of newtype definition:
    mbReplace (HsNewTypeDecl SrcLoc
loc HsContext
ctx HsName
tyn [HsName]
names HsConDecl
def [HsQName]
insts) =
        let ([HsQName]
uncustomized, [HsDecl]
customized) = [Either HsQName HsDecl] -> ([HsQName], [HsDecl])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ((HsQName -> Either HsQName HsDecl)
-> [HsQName] -> [Either HsQName HsDecl]
forall a b. (a -> b) -> [a] -> [b]
map (HsName -> HsQName -> Either HsQName HsDecl
deriv HsName
tyn) [HsQName]
insts)
        in SrcLoc
-> HsContext
-> HsName
-> [HsName]
-> HsConDecl
-> [HsQName]
-> HsDecl
HsNewTypeDecl SrcLoc
loc HsContext
ctx HsName
tyn [HsName]
names HsConDecl
def [HsQName]
uncustomized HsDecl -> [HsDecl] -> [HsDecl]
forall a. a -> [a] -> [a]
: [HsDecl]
customized

    -- irrelevant declarations remain unchanged:
    mbReplace HsDecl
hid = [HsDecl
hid]

    deriv :: HsName -> HsQName -> Either HsQName HsDecl
deriv HsName
tyn HsQName
qn = Either HsQName HsDecl
-> (HsDecl -> Either HsQName HsDecl)
-> Maybe HsDecl
-> Either HsQName HsDecl
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (HsQName -> Either HsQName HsDecl
forall a b. a -> Either a b
Left HsQName
qn) HsDecl -> Either HsQName HsDecl
forall a b. b -> Either a b
Right (Maybe HsDecl -> Either HsQName HsDecl)
-> Maybe HsDecl -> Either HsQName HsDecl
forall a b. (a -> b) -> a -> b
$ HsQName -> [HsType] -> Maybe HsDecl
search HsQName
qn [HsQName -> HsType
HsTyCon (HsName -> HsQName
UnQual HsName
tyn)]

    search :: HsQName -> [HsType] -> Maybe HsDecl
search HsQName
qn [HsType]
tys = (HsDecl -> Bool) -> [HsDecl] -> Maybe HsDecl
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\HsDecl
x -> (Maybe HsName, [HsType]) -> Maybe (Maybe HsName, [HsType])
forall a. a -> Maybe a
Just (HsQName -> Maybe HsName
unQual HsQName
qn,[HsType]
tys) Maybe (Maybe HsName, [HsType])
-> Maybe (Maybe HsName, [HsType]) -> Bool
forall a. Eq a => a -> a -> Bool
== HsDecl -> Maybe (Maybe HsName, [HsType])
getSig HsDecl
x) [HsDecl]
overrides

    getSig :: HsDecl -> Maybe (Maybe HsName, [HsType])
getSig (HsInstDecl SrcLoc
_ HsContext
_ HsQName
qn [HsType]
tys [HsDecl]
_) = (Maybe HsName, [HsType]) -> Maybe (Maybe HsName, [HsType])
forall a. a -> Maybe a
Just (HsQName -> Maybe HsName
unQual HsQName
qn,[HsType]
tys)
    getSig HsDecl
_ = Maybe (Maybe HsName, [HsType])
forall a. Maybe a
Nothing

    unQual :: HsQName -> Maybe HsName
unQual (Qual Module
_ HsName
n) = HsName -> Maybe HsName
forall a. a -> Maybe a
Just HsName
n
    unQual (UnQual HsName
n) = HsName -> Maybe HsName
forall a. a -> Maybe a
Just HsName
n
    unQual (Special HsSpecialCon
_) = Maybe HsName
forall a. Maybe a
Nothing

-- | Parses the file at the given path and produces an AST along with a
-- 'TypeContext' representing all types from imported @.proto@ files, using the
-- first parameter as a list of paths to search for imported files. Terminates
-- with exit code 1 when an included file cannot be found in the search path.
readDotProtoWithContext
    :: (MonadError CompileError m, MonadIO m)
    => [FilePath]
    -> FilePath
    -> m (DotProto, TypeContext)
readDotProtoWithContext :: [FilePath] -> FilePath -> m (DotProto, TypeContext)
readDotProtoWithContext [] FilePath
toplevelProto = do
  -- If we're not given a search path, default to using the current working
  -- directory, as `protoc` does
  FilePath
cwd <- m FilePath
forall (io :: * -> *). MonadIO io => io FilePath
Turtle.pwd
  [FilePath] -> FilePath -> m (DotProto, TypeContext)
forall (m :: * -> *).
(MonadError CompileError m, MonadIO m) =>
[FilePath] -> FilePath -> m (DotProto, TypeContext)
readDotProtoWithContext [FilePath
cwd] FilePath
toplevelProto

readDotProtoWithContext [FilePath]
searchPaths FilePath
toplevelProto = do
  DotProto
dp <- [FilePath] -> FilePath -> FilePath -> m DotProto
forall (m :: * -> *).
(MonadIO m, MonadError CompileError m) =>
[FilePath] -> FilePath -> FilePath -> m DotProto
importProto [FilePath]
searchPaths FilePath
toplevelProto FilePath
toplevelProto
  let importIt :: DotProtoImport -> m TypeContext
importIt = [FilePath]
-> FilePath -> Set FilePath -> DotProtoImport -> m TypeContext
forall (m :: * -> *).
(MonadError CompileError m, MonadIO m) =>
[FilePath]
-> FilePath -> Set FilePath -> DotProtoImport -> m TypeContext
readImportTypeContext [FilePath]
searchPaths FilePath
toplevelProto (FilePath -> Set FilePath
forall a. a -> Set a
S.singleton FilePath
toplevelProto)
  TypeContext
tc <- (DotProtoImport -> m TypeContext)
-> [DotProtoImport] -> m TypeContext
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m, Monoid b, Semigroup b) =>
(a -> m b) -> t a -> m b
foldMapM DotProtoImport -> m TypeContext
importIt (DotProto -> [DotProtoImport]
protoImports DotProto
dp)
  (DotProto, TypeContext) -> m (DotProto, TypeContext)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DotProto
dp, TypeContext
tc)

-- | Build the type context for an import, resolving transitive imports.
readImportTypeContext
    :: (MonadError CompileError m, MonadIO m)
    => [FilePath]
    -> FilePath
    -> S.Set FilePath
    -> DotProtoImport
    -> m TypeContext
readImportTypeContext :: [FilePath]
-> FilePath -> Set FilePath -> DotProtoImport -> m TypeContext
readImportTypeContext [FilePath]
searchPaths FilePath
toplevelFP Set FilePath
alreadyRead (DotProtoImport DotProtoImportQualifier
_ FilePath
path)
  | FilePath
path FilePath -> Set FilePath -> Bool
forall a. Ord a => a -> Set a -> Bool
`S.member` Set FilePath
alreadyRead = CompileError -> m TypeContext
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (FilePath -> CompileError
CircularImport FilePath
path)
  | Bool
otherwise = do
      DotProto
import_ <- [FilePath] -> FilePath -> FilePath -> m DotProto
forall (m :: * -> *).
(MonadIO m, MonadError CompileError m) =>
[FilePath] -> FilePath -> FilePath -> m DotProto
importProto [FilePath]
searchPaths FilePath
toplevelFP FilePath
path
      DotProtoIdentifier
importPkg <- DotProtoPackageSpec -> m DotProtoIdentifier
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoPackageSpec -> m DotProtoIdentifier
protoPackageName (DotProto -> DotProtoPackageSpec
protoPackage DotProto
import_)

      let fixImportTyInfo :: DotProtoTypeInfo -> DotProtoTypeInfo
fixImportTyInfo DotProtoTypeInfo
tyInfo =
             DotProtoTypeInfo
tyInfo { dotProtoTypeInfoPackage :: DotProtoPackageSpec
dotProtoTypeInfoPackage    = DotProtoIdentifier -> DotProtoPackageSpec
DotProtoPackageSpec DotProtoIdentifier
importPkg
                    , dotProtoTypeInfoModulePath :: Path
dotProtoTypeInfoModulePath = DotProtoMeta -> Path
metaModulePath (DotProtoMeta -> Path)
-> (DotProto -> DotProtoMeta) -> DotProto -> Path
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotProto -> DotProtoMeta
protoMeta (DotProto -> Path) -> DotProto -> Path
forall a b. (a -> b) -> a -> b
$ DotProto
import_
                    }
      TypeContext
importTypeContext <- (DotProtoTypeInfo -> DotProtoTypeInfo)
-> TypeContext -> TypeContext
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DotProtoTypeInfo -> DotProtoTypeInfo
fixImportTyInfo (TypeContext -> TypeContext) -> m TypeContext -> m TypeContext
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DotProto -> m TypeContext
forall (m :: * -> *).
MonadError CompileError m =>
DotProto -> m TypeContext
dotProtoTypeContext DotProto
import_

      TypeContext
qualifiedTypeContext <- (DotProtoIdentifier -> m DotProtoIdentifier)
-> TypeContext -> m TypeContext
forall (m :: * -> *) k2 k1 a.
(Monad m, Ord k2) =>
(k1 -> m k2) -> Map k1 a -> m (Map k2 a)
mapKeysM (DotProtoIdentifier -> DotProtoIdentifier -> m DotProtoIdentifier
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> DotProtoIdentifier -> m DotProtoIdentifier
concatDotProtoIdentifier DotProtoIdentifier
importPkg) TypeContext
importTypeContext

      let isPublic :: DotProtoImport -> Bool
isPublic (DotProtoImport DotProtoImportQualifier
q FilePath
_) = DotProtoImportQualifier
q DotProtoImportQualifier -> DotProtoImportQualifier -> Bool
forall a. Eq a => a -> a -> Bool
== DotProtoImportQualifier
DotProtoImportPublic
      TypeContext
transitiveImportsTC <-
        GettingM TypeContext [DotProtoImport] DotProtoImport
-> (DotProtoImport -> m TypeContext)
-> [DotProtoImport]
-> m TypeContext
forall (m :: * -> *) r s a.
(Applicative m, Monoid r) =>
GettingM r s a -> (a -> m r) -> s -> m r
foldMapOfM ((DotProtoImport -> Compose m (Const TypeContext) DotProtoImport)
-> [DotProtoImport]
-> Compose m (Const TypeContext) [DotProtoImport]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((DotProtoImport -> Compose m (Const TypeContext) DotProtoImport)
 -> [DotProtoImport]
 -> Compose m (Const TypeContext) [DotProtoImport])
-> ((DotProtoImport
     -> Compose m (Const TypeContext) DotProtoImport)
    -> DotProtoImport -> Compose m (Const TypeContext) DotProtoImport)
-> (DotProtoImport -> Compose m (Const TypeContext) DotProtoImport)
-> [DotProtoImport]
-> Compose m (Const TypeContext) [DotProtoImport]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DotProtoImport -> Bool)
-> (DotProtoImport -> Compose m (Const TypeContext) DotProtoImport)
-> DotProtoImport
-> Compose m (Const TypeContext) DotProtoImport
forall (p :: * -> * -> *) (f :: * -> *) a.
(Choice p, Applicative f) =>
(a -> Bool) -> Optic' p f a a
filtered DotProtoImport -> Bool
isPublic)
                   ([FilePath]
-> FilePath -> Set FilePath -> DotProtoImport -> m TypeContext
forall (m :: * -> *).
(MonadError CompileError m, MonadIO m) =>
[FilePath]
-> FilePath -> Set FilePath -> DotProtoImport -> m TypeContext
readImportTypeContext [FilePath]
searchPaths FilePath
toplevelFP (FilePath -> Set FilePath -> Set FilePath
forall a. Ord a => a -> Set a -> Set a
S.insert FilePath
path Set FilePath
alreadyRead))
                   (DotProto -> [DotProtoImport]
protoImports DotProto
import_)

      TypeContext -> m TypeContext
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TypeContext -> m TypeContext) -> TypeContext -> m TypeContext
forall a b. (a -> b) -> a -> b
$ TypeContext
importTypeContext TypeContext -> TypeContext -> TypeContext
forall a. Semigroup a => a -> a -> a
<> TypeContext
qualifiedTypeContext TypeContext -> TypeContext -> TypeContext
forall a. Semigroup a => a -> a -> a
<> TypeContext
transitiveImportsTC

-- | Given a type context, generates the Haskell import statements necessary
--   to import all the required types.
ctxtImports :: MonadError CompileError m => TypeContext -> m [HsImportDecl]
ctxtImports :: TypeContext -> m [HsImportDecl]
ctxtImports = ([Module] -> [HsImportDecl]) -> m [Module] -> m [HsImportDecl]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Module -> HsImportDecl) -> [Module] -> [HsImportDecl]
forall a b. (a -> b) -> [a] -> [b]
map Module -> HsImportDecl
mkImport ([Module] -> [HsImportDecl])
-> ([Module] -> [Module]) -> [Module] -> [HsImportDecl]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Module] -> [Module]
forall a. Eq a => [a] -> [a]
nub)
            (m [Module] -> m [HsImportDecl])
-> (TypeContext -> m [Module]) -> TypeContext -> m [HsImportDecl]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DotProtoTypeInfo -> m Module) -> [DotProtoTypeInfo] -> m [Module]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Path -> m Module
forall (m :: * -> *). MonadError CompileError m => Path -> m Module
modulePathModName (Path -> m Module)
-> (DotProtoTypeInfo -> Path) -> DotProtoTypeInfo -> m Module
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotProtoTypeInfo -> Path
dotProtoTypeInfoModulePath)
            ([DotProtoTypeInfo] -> m [Module])
-> (TypeContext -> [DotProtoTypeInfo]) -> TypeContext -> m [Module]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeContext -> [DotProtoTypeInfo]
forall k a. Map k a -> [a]
M.elems
  where
    mkImport :: Module -> HsImportDecl
mkImport Module
modName = Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ Module
modName Bool
True Maybe Module
forall a. Maybe a
Nothing Maybe (Bool, [HsImportSpec])
forall a. Maybe a
Nothing

--------------------------------------------------------------------------------
--
-- * Helper functions for Haskell code generation
--

-- ** Names

-- | Generate the Haskell type name for a 'DotProtoTypeInfo' for a message /
--   enumeration being compiled. NB: We ignore the 'dotProtoTypeInfoPackage'
--   field of the 'DotProtoTypeInfo' parameter, instead demanding that we have
--   been provided with a valid module path in its 'dotProtoTypeInfoModulePath'
--   field. The latter describes the name of the Haskell module being generated.
msgTypeFromDpTypeInfo :: MonadError CompileError m
                      => TypeContext -> DotProtoTypeInfo -> DotProtoIdentifier -> m HsType
msgTypeFromDpTypeInfo :: TypeContext -> DotProtoTypeInfo -> DotProtoIdentifier -> m HsType
msgTypeFromDpTypeInfo TypeContext
ctxt DotProtoTypeInfo{TypeContext
DotProtoPackageSpec
DotProtoIdentifier
Path
DotProtoKind
dotProtoTypeInfoKind :: DotProtoTypeInfo -> DotProtoKind
dotProtoTypeChildContext :: DotProtoTypeInfo -> TypeContext
dotProtoTypeInfoParent :: DotProtoTypeInfo -> DotProtoIdentifier
dotProtoTypeInfoModulePath :: Path
dotProtoTypeInfoKind :: DotProtoKind
dotProtoTypeChildContext :: TypeContext
dotProtoTypeInfoParent :: DotProtoIdentifier
dotProtoTypeInfoPackage :: DotProtoPackageSpec
dotProtoTypeInfoModulePath :: DotProtoTypeInfo -> Path
dotProtoTypeInfoPackage :: DotProtoTypeInfo -> DotProtoPackageSpec
..} DotProtoIdentifier
ident = do
    Module
modName   <- Path -> m Module
forall (m :: * -> *). MonadError CompileError m => Path -> m Module
modulePathModName Path
dotProtoTypeInfoModulePath
    FilePath
identName <- TypeContext
-> DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext
-> DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
qualifiedMessageTypeName TypeContext
ctxt DotProtoIdentifier
dotProtoTypeInfoParent DotProtoIdentifier
ident
    HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ HsQName -> HsType
HsTyCon (Module -> HsName -> HsQName
Qual Module
modName (FilePath -> HsName
HsIdent FilePath
identName))

haskellName, jsonpbName, grpcName, protobufName, protobufWrapperName, proxyName :: String -> HsQName
haskellName :: FilePath -> HsQName
haskellName  FilePath
name = Module -> HsName -> HsQName
Qual (FilePath -> Module
Module FilePath
"Hs")         (FilePath -> HsName
HsIdent FilePath
name)
jsonpbName :: FilePath -> HsQName
jsonpbName   FilePath
name = Module -> HsName -> HsQName
Qual (FilePath -> Module
Module FilePath
"HsJSONPB")   (FilePath -> HsName
HsIdent FilePath
name)
grpcName :: FilePath -> HsQName
grpcName     FilePath
name = Module -> HsName -> HsQName
Qual (FilePath -> Module
Module FilePath
"HsGRPC")     (FilePath -> HsName
HsIdent FilePath
name)
protobufName :: FilePath -> HsQName
protobufName FilePath
name = Module -> HsName -> HsQName
Qual (FilePath -> Module
Module FilePath
"HsProtobuf") (FilePath -> HsName
HsIdent FilePath
name)
proxyName :: FilePath -> HsQName
proxyName    FilePath
name = Module -> HsName -> HsQName
Qual (FilePath -> Module
Module FilePath
"Proxy")      (FilePath -> HsName
HsIdent FilePath
name)
protobufWrapperName :: FilePath -> HsQName
protobufWrapperName FilePath
name = Module -> HsName -> HsQName
Qual (FilePath -> Module
Module FilePath
"Google.Protobuf.Wrappers") (FilePath -> HsName
HsIdent FilePath
name)

modulePathModName :: MonadError CompileError m => Path -> m Module
modulePathModName :: Path -> m Module
modulePathModName (Path NonEmpty FilePath
comps) = FilePath -> Module
Module (FilePath -> Module)
-> ([FilePath] -> FilePath) -> [FilePath] -> Module
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
"." ([FilePath] -> Module) -> m [FilePath] -> m Module
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (FilePath -> m FilePath) -> [FilePath] -> m [FilePath]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> m FilePath
typeLikeName (NonEmpty FilePath -> [FilePath]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty FilePath
comps)

_pkgIdentModName :: MonadError CompileError m => DotProtoIdentifier -> m Module
_pkgIdentModName :: DotProtoIdentifier -> m Module
_pkgIdentModName (Single FilePath
s)  = FilePath -> Module
Module (FilePath -> Module) -> m FilePath -> m Module
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> m FilePath
typeLikeName FilePath
s
_pkgIdentModName (Dots Path
path) = Path -> m Module
forall (m :: * -> *). MonadError CompileError m => Path -> m Module
modulePathModName Path
path
_pkgIdentModName DotProtoIdentifier
x           = CompileError -> m Module
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (DotProtoIdentifier -> CompileError
InvalidPackageName DotProtoIdentifier
x)


-- ** Dhall

#ifdef DHALL
hsDhallPB :: String
hsDhallPB = "HsDhallPb"

dhallPBName :: String -> HsQName
dhallPBName name = Qual (Module hsDhallPB) (HsIdent name)

-- *** Generate Dhall Interpret and Inject generic instances

fromDhall, toDhall :: String
(fromDhall, toDhall) =
#if MIN_VERSION_dhall(1,27,0)
  ("FromDhall", "ToDhall")
#else
  ("Interpret", "Inject")
#endif

dhallInterpretInstDecl :: String -> HsDecl
dhallInterpretInstDecl typeName =
  instDecl_ (dhallPBName fromDhall)
            [ type_ typeName ]
            [ ]

dhallInjectInstDecl :: String -> HsDecl
dhallInjectInstDecl typeName =
  instDecl_ (dhallPBName toDhall)
            [ type_ typeName ]
            [ ]
#endif

-- ** Helpers to wrap/unwrap types for protobuf (de-)serialization

coerceE :: Bool -> HsType -> HsType -> Maybe HsExp
coerceE :: Bool -> HsType -> HsType -> Maybe HsExp
coerceE Bool
_ HsType
from HsType
to | HsType
from HsType -> HsType -> Bool
forall a. Eq a => a -> a -> Bool
== HsType
to = Maybe HsExp
forall a. Maybe a
Nothing
coerceE Bool
unsafe HsType
from HsType
to = HsExp -> Maybe HsExp
forall a. a -> Maybe a
Just (HsExp -> Maybe HsExp) -> HsExp -> Maybe HsExp
forall a b. (a -> b) -> a -> b
$ HsExp -> HsExp -> HsExp
HsApp (HsExp -> HsExp -> HsExp
HsApp HsExp
coerceF (HsType -> HsExp
typeApp HsType
from)) (HsType -> HsExp
typeApp HsType
to)
  where
    -- Do not add linebreaks to typeapps as that causes parse errors
    pp :: HsType -> FilePath
pp = Style -> PPHsMode -> HsType -> FilePath
forall a. Pretty a => Style -> PPHsMode -> a -> FilePath
prettyPrintStyleMode Style
style{mode :: Mode
mode=Mode
OneLineMode} PPHsMode
defaultMode
    typeApp :: HsType -> HsExp
typeApp HsType
ty = FilePath -> HsExp
uvar_ (FilePath
"@("FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ HsType -> FilePath
pp HsType
ty FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
")")
    coerceF :: HsExp
coerceF | Bool
unsafe = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"unsafeCoerce")
            | Bool
otherwise  = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"coerce")

wrapE :: MonadError CompileError m => TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
wrapE :: TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
wrapE TypeContext
ctxt [DotProtoOption]
opts DotProtoType
dpt HsExp
e = HsExp -> (HsExp -> HsExp) -> Maybe HsExp -> HsExp
forall b a. b -> (a -> b) -> Maybe a -> b
maybe HsExp
e (\HsExp
f -> HsExp -> [HsExp] -> HsExp
apply HsExp
f [HsExp
e]) (Maybe HsExp -> HsExp) -> m (Maybe HsExp) -> m HsExp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
  (Bool -> HsType -> HsType -> Maybe HsExp
coerceE (DotProtoType -> Bool
isMap DotProtoType
dpt) (HsType -> HsType -> Maybe HsExp)
-> m HsType -> m (HsType -> Maybe HsExp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TypeContext -> DotProtoType -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoType -> m HsType
dptToHsType TypeContext
ctxt DotProtoType
dpt m (HsType -> Maybe HsExp) -> m HsType -> m (Maybe HsExp)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [DotProtoOption] -> TypeContext -> DotProtoType -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
[DotProtoOption] -> TypeContext -> DotProtoType -> m HsType
dptToHsTypeWrapped [DotProtoOption]
opts TypeContext
ctxt DotProtoType
dpt)

unwrapE :: MonadError CompileError m => TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
unwrapE :: TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
unwrapE TypeContext
ctxt [DotProtoOption]
opts DotProtoType
dpt HsExp
e = HsExp -> (HsExp -> HsExp) -> Maybe HsExp -> HsExp
forall b a. b -> (a -> b) -> Maybe a -> b
maybe HsExp
e (\HsExp
f -> HsExp -> [HsExp] -> HsExp
apply HsExp
f [HsExp
e]) (Maybe HsExp -> HsExp) -> m (Maybe HsExp) -> m HsExp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
   (Bool -> HsType -> HsType -> Maybe HsExp
coerceE (DotProtoType -> Bool
isMap DotProtoType
dpt) (HsType -> HsType -> Maybe HsExp)
-> m HsType -> m (HsType -> Maybe HsExp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
     m HsType -> m HsType
overParser ([DotProtoOption] -> TypeContext -> DotProtoType -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
[DotProtoOption] -> TypeContext -> DotProtoType -> m HsType
dptToHsTypeWrapped [DotProtoOption]
opts TypeContext
ctxt DotProtoType
dpt) m (HsType -> Maybe HsExp) -> m HsType -> m (Maybe HsExp)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
       m HsType -> m HsType
overParser (TypeContext -> DotProtoType -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoType -> m HsType
dptToHsType TypeContext
ctxt DotProtoType
dpt))
  where
    overParser :: m HsType -> m HsType
overParser = (HsType -> HsType) -> m HsType -> m HsType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((HsType -> HsType) -> m HsType -> m HsType)
-> (HsType -> HsType) -> m HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ HsType -> HsType -> HsType
HsTyApp (HsName -> HsType
HsTyVar (FilePath -> HsName
HsIdent FilePath
"_"))


--------------------------------------------------------------------------------
--
-- * Functions to convert 'DotProtoType' into Haskell types
--

-- | Convert a dot proto type to a Haskell type
dptToHsType :: MonadError CompileError m => TypeContext -> DotProtoType -> m HsType
dptToHsType :: TypeContext -> DotProtoType -> m HsType
dptToHsType = (TypeContext -> DotProtoType -> HsType -> HsType)
-> (TypeContext -> DotProtoPrimType -> m HsType)
-> TypeContext
-> DotProtoType
-> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
(TypeContext -> DotProtoType -> HsType -> HsType)
-> (TypeContext -> DotProtoPrimType -> m HsType)
-> TypeContext
-> DotProtoType
-> m HsType
foldDPT TypeContext -> DotProtoType -> HsType -> HsType
dptToHsContType TypeContext -> DotProtoPrimType -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoPrimType -> m HsType
dpptToHsType

-- | Convert a dot proto type to a wrapped Haskell type
dptToHsTypeWrapped :: MonadError CompileError m => [DotProtoOption] -> TypeContext -> DotProtoType -> m HsType
dptToHsTypeWrapped :: [DotProtoOption] -> TypeContext -> DotProtoType -> m HsType
dptToHsTypeWrapped [DotProtoOption]
opts =
   (TypeContext -> DotProtoType -> HsType -> HsType)
-> (TypeContext -> DotProtoPrimType -> m HsType)
-> TypeContext
-> DotProtoType
-> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
(TypeContext -> DotProtoType -> HsType -> HsType)
-> (TypeContext -> DotProtoPrimType -> m HsType)
-> TypeContext
-> DotProtoType
-> m HsType
foldDPT
     -- The wrapper for the collection type replaces the native haskell
     -- collection type, so try that first.
     (\TypeContext
ctxt DotProtoType
ty -> (HsType -> HsType)
-> ((HsType -> HsType) -> HsType -> HsType)
-> Maybe (HsType -> HsType)
-> HsType
-> HsType
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (TypeContext -> DotProtoType -> HsType -> HsType
dptToHsContType TypeContext
ctxt DotProtoType
ty) (HsType -> HsType) -> HsType -> HsType
forall a. a -> a
id (TypeContext
-> [DotProtoOption] -> DotProtoType -> Maybe (HsType -> HsType)
dptToHsWrappedContType TypeContext
ctxt [DotProtoOption]
opts DotProtoType
ty))
     -- Always wrap the primitive type.
     (\TypeContext
ctxt DotProtoPrimType
ty -> DotProtoPrimType -> HsType -> HsType
dpptToHsTypeWrapper DotProtoPrimType
ty (HsType -> HsType) -> m HsType -> m HsType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TypeContext -> DotProtoPrimType -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoPrimType -> m HsType
dpptToHsType' TypeContext
ctxt DotProtoPrimType
ty)
  where
    dpptToHsType' :: MonadError CompileError m
                  => TypeContext
                  -> DotProtoPrimType
                  -> m HsType
    dpptToHsType' :: TypeContext -> DotProtoPrimType -> m HsType
dpptToHsType' TypeContext
ctxt =  \case
      DotProtoPrimType
Int32    -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int32"
      DotProtoPrimType
Int64    -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int64"
      DotProtoPrimType
SInt32   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int32"
      DotProtoPrimType
SInt64   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int64"
      DotProtoPrimType
UInt32   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Word32"
      DotProtoPrimType
UInt64   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Word64"
      DotProtoPrimType
Fixed32  -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Word32"
      DotProtoPrimType
Fixed64  -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Word64"
      DotProtoPrimType
SFixed32 -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int32"
      DotProtoPrimType
SFixed64 -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int64"
      DotProtoPrimType
String   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Text"
      DotProtoPrimType
Bytes    -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"ByteString"
      DotProtoPrimType
Bool     -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Bool"
      DotProtoPrimType
Float    -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Float"
      DotProtoPrimType
Double   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Double"
      Named (Dots (Path (FilePath
"google" :| [FilePath
"protobuf", FilePath
x])))
        | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"Int32Value" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
protobufWrapperType_ FilePath
x
        | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"Int64Value" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
protobufWrapperType_ FilePath
x
        | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"UInt32Value" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
protobufWrapperType_ FilePath
x
        | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"UInt64Value" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
protobufWrapperType_ FilePath
x
        | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"StringValue" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
protobufWrapperType_ FilePath
x
        | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"BytesValue" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
protobufWrapperType_ FilePath
x
        | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"BoolValue" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
protobufWrapperType_ FilePath
x
        | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"FloatValue" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
protobufWrapperType_ FilePath
x
        | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"DoubleValue" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
protobufWrapperType_ FilePath
x
      Named DotProtoIdentifier
msgName ->
        case DotProtoIdentifier -> TypeContext -> Maybe DotProtoTypeInfo
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup DotProtoIdentifier
msgName TypeContext
ctxt of
          Just ty :: DotProtoTypeInfo
ty@(DotProtoTypeInfo { dotProtoTypeInfoKind :: DotProtoTypeInfo -> DotProtoKind
dotProtoTypeInfoKind = DotProtoKind
DotProtoKindEnum }) ->
              HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"Enumerated") (HsType -> HsType) -> m HsType -> m HsType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TypeContext -> DotProtoTypeInfo -> DotProtoIdentifier -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoTypeInfo -> DotProtoIdentifier -> m HsType
msgTypeFromDpTypeInfo TypeContext
ctxt DotProtoTypeInfo
ty DotProtoIdentifier
msgName
          Just DotProtoTypeInfo
ty -> TypeContext -> DotProtoTypeInfo -> DotProtoIdentifier -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoTypeInfo -> DotProtoIdentifier -> m HsType
msgTypeFromDpTypeInfo TypeContext
ctxt DotProtoTypeInfo
ty DotProtoIdentifier
msgName
          Maybe DotProtoTypeInfo
Nothing -> DotProtoIdentifier -> m HsType
forall (m :: * -> *) a.
MonadError CompileError m =>
DotProtoIdentifier -> m a
noSuchTypeError DotProtoIdentifier
msgName

foldDPT :: MonadError CompileError m
        => (TypeContext -> DotProtoType -> HsType -> HsType)
        -> (TypeContext -> DotProtoPrimType -> m HsType)
        -> TypeContext
        -> DotProtoType
        -> m HsType
foldDPT :: (TypeContext -> DotProtoType -> HsType -> HsType)
-> (TypeContext -> DotProtoPrimType -> m HsType)
-> TypeContext
-> DotProtoType
-> m HsType
foldDPT TypeContext -> DotProtoType -> HsType -> HsType
dptToHsCont TypeContext -> DotProtoPrimType -> m HsType
foldPrim TypeContext
ctxt DotProtoType
dpt =
  let
      prim :: DotProtoPrimType -> m HsType
prim = TypeContext -> DotProtoPrimType -> m HsType
foldPrim TypeContext
ctxt
      go :: DotProtoType -> m HsType
go = (TypeContext -> DotProtoType -> HsType -> HsType)
-> (TypeContext -> DotProtoPrimType -> m HsType)
-> TypeContext
-> DotProtoType
-> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
(TypeContext -> DotProtoType -> HsType -> HsType)
-> (TypeContext -> DotProtoPrimType -> m HsType)
-> TypeContext
-> DotProtoType
-> m HsType
foldDPT TypeContext -> DotProtoType -> HsType -> HsType
dptToHsCont TypeContext -> DotProtoPrimType -> m HsType
foldPrim TypeContext
ctxt
      cont :: HsType -> HsType
cont = TypeContext -> DotProtoType -> HsType -> HsType
dptToHsCont TypeContext
ctxt DotProtoType
dpt
  in
    case DotProtoType
dpt of
      Prim DotProtoPrimType
pType           -> HsType -> HsType
cont (HsType -> HsType) -> m HsType -> m HsType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DotProtoPrimType -> m HsType
prim DotProtoPrimType
pType
      Repeated DotProtoPrimType
pType       -> HsType -> HsType
cont (HsType -> HsType) -> m HsType -> m HsType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DotProtoPrimType -> m HsType
prim DotProtoPrimType
pType
      NestedRepeated DotProtoPrimType
pType -> HsType -> HsType
cont (HsType -> HsType) -> m HsType -> m HsType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DotProtoPrimType -> m HsType
prim DotProtoPrimType
pType
      Map DotProtoPrimType
k DotProtoPrimType
v  | DotProtoPrimType -> Bool
validMapKey DotProtoPrimType
k -> HsType -> HsType -> HsType
HsTyApp (HsType -> HsType -> HsType)
-> (HsType -> HsType) -> HsType -> HsType -> HsType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsType -> HsType
cont (HsType -> HsType -> HsType) -> m HsType -> m (HsType -> HsType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DotProtoPrimType -> m HsType
prim DotProtoPrimType
k m (HsType -> HsType) -> m HsType -> m HsType
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DotProtoType -> m HsType
go (DotProtoPrimType -> DotProtoType
Prim DotProtoPrimType
v) -- need to 'Nest' message types
               | Bool
otherwise -> CompileError -> m HsType
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (CompileError -> m HsType) -> CompileError -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> CompileError
InvalidMapKeyType (Doc -> FilePath
forall a. Show a => a -> FilePath
show (Doc -> FilePath) -> Doc -> FilePath
forall a b. (a -> b) -> a -> b
$ DotProtoPrimType -> Doc
forall a. Pretty a => a -> Doc
pPrint DotProtoPrimType
k)

-- | Translate DotProtoType constructors to wrapped Haskell container types
-- (for Message serde instances).
dptToHsWrappedContType :: TypeContext -> [DotProtoOption] -> DotProtoType -> Maybe (HsType -> HsType)
dptToHsWrappedContType :: TypeContext
-> [DotProtoOption] -> DotProtoType -> Maybe (HsType -> HsType)
dptToHsWrappedContType TypeContext
ctxt [DotProtoOption]
opts = \case
  Prim (Named DotProtoIdentifier
tyName)
    | TypeContext -> DotProtoIdentifier -> Bool
isMessage TypeContext
ctxt DotProtoIdentifier
tyName -> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a. a -> Maybe a
Just ((HsType -> HsType) -> Maybe (HsType -> HsType))
-> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a b. (a -> b) -> a -> b
$ HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"Nested")
  Repeated (Named DotProtoIdentifier
tyName)
    | TypeContext -> DotProtoIdentifier -> Bool
isMessage TypeContext
ctxt DotProtoIdentifier
tyName -> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a. a -> Maybe a
Just ((HsType -> HsType) -> Maybe (HsType -> HsType))
-> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a b. (a -> b) -> a -> b
$ HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"NestedVec")
  Repeated DotProtoPrimType
ty
    | [DotProtoOption] -> Bool
isUnpacked [DotProtoOption]
opts       -> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a. a -> Maybe a
Just ((HsType -> HsType) -> Maybe (HsType -> HsType))
-> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a b. (a -> b) -> a -> b
$ HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"UnpackedVec")
    | [DotProtoOption] -> Bool
isPacked [DotProtoOption]
opts         -> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a. a -> Maybe a
Just ((HsType -> HsType) -> Maybe (HsType -> HsType))
-> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a b. (a -> b) -> a -> b
$ HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"PackedVec")
    | TypeContext -> DotProtoPrimType -> Bool
isPackable TypeContext
ctxt DotProtoPrimType
ty    -> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a. a -> Maybe a
Just ((HsType -> HsType) -> Maybe (HsType -> HsType))
-> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a b. (a -> b) -> a -> b
$ HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"PackedVec")
    | Bool
otherwise             -> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a. a -> Maybe a
Just ((HsType -> HsType) -> Maybe (HsType -> HsType))
-> (HsType -> HsType) -> Maybe (HsType -> HsType)
forall a b. (a -> b) -> a -> b
$ HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"UnpackedVec")
  DotProtoType
_ -> Maybe (HsType -> HsType)
forall a. Maybe a
Nothing

-- | Translate DotProtoType to Haskell container types.
dptToHsContType :: TypeContext -> DotProtoType -> HsType -> HsType
dptToHsContType :: TypeContext -> DotProtoType -> HsType -> HsType
dptToHsContType TypeContext
ctxt = \case
  Prim (Named DotProtoIdentifier
tyName) | TypeContext -> DotProtoIdentifier -> Bool
isMessage TypeContext
ctxt DotProtoIdentifier
tyName
                     -> HsType -> HsType -> HsType
HsTyApp (HsType -> HsType -> HsType) -> HsType -> HsType -> HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Maybe"
  Repeated DotProtoPrimType
_         -> HsType -> HsType -> HsType
HsTyApp (HsType -> HsType -> HsType) -> HsType -> HsType -> HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Vector"
  NestedRepeated DotProtoPrimType
_   -> HsType -> HsType -> HsType
HsTyApp (HsType -> HsType -> HsType) -> HsType -> HsType -> HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Vector"
  Map DotProtoPrimType
_ DotProtoPrimType
_            -> HsType -> HsType -> HsType
HsTyApp (HsType -> HsType -> HsType) -> HsType -> HsType -> HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Map"
  DotProtoType
_                  -> HsType -> HsType
forall a. a -> a
id

-- | Haskell wrapper for primitive dot proto types
dpptToHsTypeWrapper :: DotProtoPrimType -> HsType -> HsType
dpptToHsTypeWrapper :: DotProtoPrimType -> HsType -> HsType
dpptToHsTypeWrapper = \case
  DotProtoPrimType
SInt32   -> HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"Signed")
  DotProtoPrimType
SInt64   -> HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"Signed")
  DotProtoPrimType
SFixed32 -> HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"Signed") (HsType -> HsType) -> (HsType -> HsType) -> HsType -> HsType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"Fixed")
  DotProtoPrimType
SFixed64 -> HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"Signed") (HsType -> HsType) -> (HsType -> HsType) -> HsType -> HsType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"Fixed")
  DotProtoPrimType
Fixed32  -> HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"Fixed")
  DotProtoPrimType
Fixed64  -> HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"Fixed")
  DotProtoPrimType
_        -> HsType -> HsType
forall a. a -> a
id

-- | Convert a dot proto prim type to an unwrapped Haskell type
dpptToHsType :: MonadError CompileError m
             => TypeContext
             -> DotProtoPrimType
             -> m HsType
dpptToHsType :: TypeContext -> DotProtoPrimType -> m HsType
dpptToHsType TypeContext
ctxt = \case
  DotProtoPrimType
Int32    -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int32"
  DotProtoPrimType
Int64    -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int64"
  DotProtoPrimType
SInt32   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int32"
  DotProtoPrimType
SInt64   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int64"
  DotProtoPrimType
UInt32   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Word32"
  DotProtoPrimType
UInt64   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Word64"
  DotProtoPrimType
Fixed32  -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Word32"
  DotProtoPrimType
Fixed64  -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Word64"
  DotProtoPrimType
SFixed32 -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int32"
  DotProtoPrimType
SFixed64 -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int64"
  DotProtoPrimType
String   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Text"
  DotProtoPrimType
Bytes    -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"ByteString"
  DotProtoPrimType
Bool     -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Bool"
  DotProtoPrimType
Float    -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Float"
  DotProtoPrimType
Double   -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Double"
  Named (Dots (Path (FilePath
"google" :| [FilePath
"protobuf", FilePath
x])))
    | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"Int32Value" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int32"
    | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"Int64Value" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Int64"
    | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"UInt32Value" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Word32"
    | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"UInt64Value" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Word64"
    | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"StringValue" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Text"
    | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"BytesValue" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"ByteString"
    | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"BoolValue" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Bool"
    | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"FloatValue" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Float"
    | FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"DoubleValue" -> HsType -> m HsType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsType -> m HsType) -> HsType -> m HsType
forall a b. (a -> b) -> a -> b
$ FilePath -> HsType
primType_ FilePath
"Double"
  Named DotProtoIdentifier
msgName ->
    case DotProtoIdentifier -> TypeContext -> Maybe DotProtoTypeInfo
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup DotProtoIdentifier
msgName TypeContext
ctxt of
      Just ty :: DotProtoTypeInfo
ty@(DotProtoTypeInfo { dotProtoTypeInfoKind :: DotProtoTypeInfo -> DotProtoKind
dotProtoTypeInfoKind = DotProtoKind
DotProtoKindEnum }) ->
          HsType -> HsType -> HsType
HsTyApp (FilePath -> HsType
protobufType_ FilePath
"Enumerated") (HsType -> HsType) -> m HsType -> m HsType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TypeContext -> DotProtoTypeInfo -> DotProtoIdentifier -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoTypeInfo -> DotProtoIdentifier -> m HsType
msgTypeFromDpTypeInfo TypeContext
ctxt DotProtoTypeInfo
ty DotProtoIdentifier
msgName
      Just DotProtoTypeInfo
ty -> TypeContext -> DotProtoTypeInfo -> DotProtoIdentifier -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoTypeInfo -> DotProtoIdentifier -> m HsType
msgTypeFromDpTypeInfo TypeContext
ctxt DotProtoTypeInfo
ty DotProtoIdentifier
msgName
      Maybe DotProtoTypeInfo
Nothing -> DotProtoIdentifier -> m HsType
forall (m :: * -> *) a.
MonadError CompileError m =>
DotProtoIdentifier -> m a
noSuchTypeError DotProtoIdentifier
msgName

validMapKey :: DotProtoPrimType -> Bool
validMapKey :: DotProtoPrimType -> Bool
validMapKey = (DotProtoPrimType -> [DotProtoPrimType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ DotProtoPrimType
Int32, DotProtoPrimType
Int64, DotProtoPrimType
SInt32, DotProtoPrimType
SInt64, DotProtoPrimType
UInt32, DotProtoPrimType
UInt64
                      , DotProtoPrimType
Fixed32, DotProtoPrimType
Fixed64, DotProtoPrimType
SFixed32, DotProtoPrimType
SFixed64
                      , DotProtoPrimType
String, DotProtoPrimType
Bool])


--------------------------------------------------------------------------------
--
-- * Code generation
--

-- ** Generate instances for a 'DotProto' package

dotProtoDefinitionD :: MonadError CompileError m
                    => DotProtoIdentifier -> TypeContext -> DotProtoDefinition -> m [HsDecl]
dotProtoDefinitionD :: DotProtoIdentifier
-> TypeContext -> DotProtoDefinition -> m [HsDecl]
dotProtoDefinitionD DotProtoIdentifier
pkgIdent TypeContext
ctxt = \case
  DotProtoMessage FilePath
_ DotProtoIdentifier
messageName [DotProtoMessagePart]
messageParts ->
    TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m [HsDecl]
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m [HsDecl]
dotProtoMessageD TypeContext
ctxt DotProtoIdentifier
Anonymous DotProtoIdentifier
messageName [DotProtoMessagePart]
messageParts

  DotProtoEnum FilePath
_ DotProtoIdentifier
enumName [DotProtoEnumPart]
enumParts ->
    DotProtoIdentifier
-> DotProtoIdentifier -> [DotProtoEnumPart] -> m [HsDecl]
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier
-> DotProtoIdentifier -> [DotProtoEnumPart] -> m [HsDecl]
dotProtoEnumD DotProtoIdentifier
Anonymous DotProtoIdentifier
enumName [DotProtoEnumPart]
enumParts

  DotProtoService FilePath
_ DotProtoIdentifier
serviceName [DotProtoServicePart]
serviceParts ->
    DotProtoIdentifier
-> TypeContext
-> DotProtoIdentifier
-> [DotProtoServicePart]
-> m [HsDecl]
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier
-> TypeContext
-> DotProtoIdentifier
-> [DotProtoServicePart]
-> m [HsDecl]
dotProtoServiceD DotProtoIdentifier
pkgIdent TypeContext
ctxt DotProtoIdentifier
serviceName [DotProtoServicePart]
serviceParts

-- | Generate 'Named' instance for a type in this package
namedInstD :: String -> HsDecl
namedInstD :: FilePath -> HsDecl
namedInstD FilePath
messageName =
  HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
protobufName FilePath
"Named")
      [ FilePath -> HsType
type_ FilePath
messageName ]
      [ [HsMatch] -> HsDecl
HsFunBind [HsMatch
nameOfDecl] ]
  where
    nameOfDecl :: HsMatch
nameOfDecl = HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"nameOf") [HsPat
HsPWildCard]
                        (HsExp -> HsRhs
HsUnGuardedRhs (HsExp -> [HsExp] -> HsExp
apply HsExp
fromStringE
                                               [ FilePath -> HsExp
str_ FilePath
messageName ]))
                        []

hasDefaultInstD :: String -> HsDecl
hasDefaultInstD :: FilePath -> HsDecl
hasDefaultInstD FilePath
messageName =
  HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
protobufName FilePath
"HasDefault")
      [ FilePath -> HsType
type_ FilePath
messageName ]
      [ ]

-- ** Generate types and instances for .proto messages

-- | Generate data types, 'Bounded', 'Enum', 'FromJSONPB', 'Named', 'Message',
--   'ToJSONPB' instances as appropriate for the given 'DotProtoMessagePart's
dotProtoMessageD
    :: forall m
     . MonadError CompileError m
    => TypeContext
    -> DotProtoIdentifier
    -> DotProtoIdentifier
    -> [DotProtoMessagePart]
    -> m [HsDecl]
dotProtoMessageD :: TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m [HsDecl]
dotProtoMessageD TypeContext
ctxt DotProtoIdentifier
parentIdent DotProtoIdentifier
messageIdent [DotProtoMessagePart]
messageParts = do
    FilePath
messageName <- DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
qualifiedMessageName DotProtoIdentifier
parentIdent DotProtoIdentifier
messageIdent

    let mkDataDecl :: [([HsName], HsBangType)] -> HsDecl
mkDataDecl [([HsName], HsBangType)]
flds =
          FilePath -> [HsConDecl] -> [HsQName] -> HsDecl
dataDecl_ FilePath
messageName
            [ HsName -> [([HsName], HsBangType)] -> HsConDecl
recDecl_ (FilePath -> HsName
HsIdent FilePath
messageName) [([HsName], HsBangType)]
flds ]
            [HsQName]
defaultMessageDeriving

    let getName :: DotProtoMessagePart -> [DotProtoIdentifier]
getName = \case
          DotProtoMessageField DotProtoField
fld     -> [DotProtoField -> DotProtoIdentifier
dotProtoFieldName DotProtoField
fld]
          DotProtoMessageOneOf DotProtoIdentifier
ident [DotProtoField]
_ -> [DotProtoIdentifier
ident]
          DotProtoMessagePart
_                            -> []

    (m [HsDecl] -> m [HsDecl]) -> [m [HsDecl]] -> m [HsDecl]
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m, Monoid b, Semigroup b) =>
(a -> m b) -> t a -> m b
foldMapM m [HsDecl] -> m [HsDecl]
forall a. a -> a
id
      [ [m HsDecl] -> m [HsDecl]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
          [ [([HsName], HsBangType)] -> HsDecl
mkDataDecl ([([HsName], HsBangType)] -> HsDecl)
-> m [([HsName], HsBangType)] -> m HsDecl
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DotProtoMessagePart -> m [([HsName], HsBangType)])
-> [DotProtoMessagePart] -> m [([HsName], HsBangType)]
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m, Monoid b, Semigroup b) =>
(a -> m b) -> t a -> m b
foldMapM (FilePath -> DotProtoMessagePart -> m [([HsName], HsBangType)]
messagePartFieldD FilePath
messageName) [DotProtoMessagePart]
messageParts
          , HsDecl -> m HsDecl
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> HsDecl
namedInstD FilePath
messageName)
          , HsDecl -> m HsDecl
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> HsDecl
hasDefaultInstD FilePath
messageName)
          , TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m HsDecl
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m HsDecl
messageInstD TypeContext
ctxt' DotProtoIdentifier
parentIdent DotProtoIdentifier
messageIdent [DotProtoMessagePart]
messageParts

          , TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m HsDecl
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m HsDecl
toJSONPBMessageInstD   TypeContext
ctxt' DotProtoIdentifier
parentIdent DotProtoIdentifier
messageIdent [DotProtoMessagePart]
messageParts
          , TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m HsDecl
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m HsDecl
fromJSONPBMessageInstD TypeContext
ctxt' DotProtoIdentifier
parentIdent DotProtoIdentifier
messageIdent [DotProtoMessagePart]
messageParts

            -- Generate Aeson instances in terms of JSONPB instances
          , HsDecl -> m HsDecl
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> HsDecl
toJSONInstDecl FilePath
messageName)
          , HsDecl -> m HsDecl
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> HsDecl
fromJSONInstDecl FilePath
messageName)

#ifdef SWAGGER
          -- And the Swagger ToSchema instance corresponding to JSONPB encodings
          , FilePath -> Maybe [HsName] -> [FilePath] -> m HsDecl
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> Maybe [HsName] -> [FilePath] -> m HsDecl
toSchemaInstanceDeclaration FilePath
messageName Maybe [HsName]
forall a. Maybe a
Nothing
              ([FilePath] -> m HsDecl) -> m [FilePath] -> m HsDecl
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (DotProtoMessagePart -> m [FilePath])
-> [DotProtoMessagePart] -> m [FilePath]
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m, Monoid b, Semigroup b) =>
(a -> m b) -> t a -> m b
foldMapM ((DotProtoIdentifier -> m FilePath)
-> [DotProtoIdentifier] -> m [FilePath]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> m FilePath
dpIdentUnqualName ([DotProtoIdentifier] -> m [FilePath])
-> (DotProtoMessagePart -> [DotProtoIdentifier])
-> DotProtoMessagePart
-> m [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotProtoMessagePart -> [DotProtoIdentifier]
getName) [DotProtoMessagePart]
messageParts
#endif

#ifdef DHALL
          -- Generate Dhall instances
          , pure (dhallInterpretInstDecl messageName)
          , pure (dhallInjectInstDecl messageName)
#endif
          ]

      -- Nested regular and oneof message decls
      , GettingM [HsDecl] [DotProtoMessagePart] DotProtoDefinition
-> (DotProtoDefinition -> m [HsDecl])
-> [DotProtoMessagePart]
-> m [HsDecl]
forall (m :: * -> *) r s a.
(Applicative m, Monoid r) =>
GettingM r s a -> (a -> m r) -> s -> m r
foldMapOfM ((DotProtoMessagePart
 -> Compose m (Const [HsDecl]) DotProtoMessagePart)
-> [DotProtoMessagePart]
-> Compose m (Const [HsDecl]) [DotProtoMessagePart]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((DotProtoMessagePart
  -> Compose m (Const [HsDecl]) DotProtoMessagePart)
 -> [DotProtoMessagePart]
 -> Compose m (Const [HsDecl]) [DotProtoMessagePart])
-> ((DotProtoDefinition
     -> Compose m (Const [HsDecl]) DotProtoDefinition)
    -> DotProtoMessagePart
    -> Compose m (Const [HsDecl]) DotProtoMessagePart)
-> (DotProtoDefinition
    -> Compose m (Const [HsDecl]) DotProtoDefinition)
-> [DotProtoMessagePart]
-> Compose m (Const [HsDecl]) [DotProtoMessagePart]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DotProtoDefinition
 -> Compose m (Const [HsDecl]) DotProtoDefinition)
-> DotProtoMessagePart
-> Compose m (Const [HsDecl]) DotProtoMessagePart
Prism' DotProtoMessagePart DotProtoDefinition
_DotProtoMessageDefinition)
                   DotProtoDefinition -> m [HsDecl]
nestedDecls
                   [DotProtoMessagePart]
messageParts

      , GettingM
  [HsDecl]
  [DotProtoMessagePart]
  (DotProtoIdentifier, [DotProtoField])
-> ((DotProtoIdentifier, [DotProtoField]) -> m [HsDecl])
-> [DotProtoMessagePart]
-> m [HsDecl]
forall (m :: * -> *) r s a.
(Applicative m, Monoid r) =>
GettingM r s a -> (a -> m r) -> s -> m r
foldMapOfM ((DotProtoMessagePart
 -> Compose m (Const [HsDecl]) DotProtoMessagePart)
-> [DotProtoMessagePart]
-> Compose m (Const [HsDecl]) [DotProtoMessagePart]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((DotProtoMessagePart
  -> Compose m (Const [HsDecl]) DotProtoMessagePart)
 -> [DotProtoMessagePart]
 -> Compose m (Const [HsDecl]) [DotProtoMessagePart])
-> (((DotProtoIdentifier, [DotProtoField])
     -> Compose
          m (Const [HsDecl]) (DotProtoIdentifier, [DotProtoField]))
    -> DotProtoMessagePart
    -> Compose m (Const [HsDecl]) DotProtoMessagePart)
-> ((DotProtoIdentifier, [DotProtoField])
    -> Compose
         m (Const [HsDecl]) (DotProtoIdentifier, [DotProtoField]))
-> [DotProtoMessagePart]
-> Compose m (Const [HsDecl]) [DotProtoMessagePart]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((DotProtoIdentifier, [DotProtoField])
 -> Compose
      m (Const [HsDecl]) (DotProtoIdentifier, [DotProtoField]))
-> DotProtoMessagePart
-> Compose m (Const [HsDecl]) DotProtoMessagePart
Prism' DotProtoMessagePart (DotProtoIdentifier, [DotProtoField])
_DotProtoMessageOneOf)
                   ((DotProtoIdentifier -> [DotProtoField] -> m [HsDecl])
-> (DotProtoIdentifier, [DotProtoField]) -> m [HsDecl]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((DotProtoIdentifier -> [DotProtoField] -> m [HsDecl])
 -> (DotProtoIdentifier, [DotProtoField]) -> m [HsDecl])
-> (DotProtoIdentifier -> [DotProtoField] -> m [HsDecl])
-> (DotProtoIdentifier, [DotProtoField])
-> m [HsDecl]
forall a b. (a -> b) -> a -> b
$ FilePath -> DotProtoIdentifier -> [DotProtoField] -> m [HsDecl]
nestedOneOfDecls FilePath
messageName)
                   [DotProtoMessagePart]
messageParts
      ]

  where
    ctxt' :: TypeContext
    ctxt' :: TypeContext
ctxt' = TypeContext
-> (DotProtoTypeInfo -> TypeContext)
-> Maybe DotProtoTypeInfo
-> TypeContext
forall b a. b -> (a -> b) -> Maybe a -> b
maybe TypeContext
forall a. Monoid a => a
mempty DotProtoTypeInfo -> TypeContext
dotProtoTypeChildContext (DotProtoIdentifier -> TypeContext -> Maybe DotProtoTypeInfo
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup DotProtoIdentifier
messageIdent TypeContext
ctxt)
                TypeContext -> TypeContext -> TypeContext
forall a. Semigroup a => a -> a -> a
<> TypeContext
ctxt

    messagePartFieldD :: String -> DotProtoMessagePart -> m [([HsName], HsBangType)]
    messagePartFieldD :: FilePath -> DotProtoMessagePart -> m [([HsName], HsBangType)]
messagePartFieldD FilePath
messageName (DotProtoMessageField DotProtoField{FilePath
[DotProtoOption]
FieldNumber
DotProtoType
DotProtoIdentifier
dotProtoFieldComment :: DotProtoField -> FilePath
dotProtoFieldOptions :: DotProtoField -> [DotProtoOption]
dotProtoFieldType :: DotProtoField -> DotProtoType
dotProtoFieldNumber :: DotProtoField -> FieldNumber
dotProtoFieldComment :: FilePath
dotProtoFieldOptions :: [DotProtoOption]
dotProtoFieldName :: DotProtoIdentifier
dotProtoFieldType :: DotProtoType
dotProtoFieldNumber :: FieldNumber
dotProtoFieldName :: DotProtoField -> DotProtoIdentifier
..}) = do
      FilePath
fullName <- FilePath -> FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> FilePath -> m FilePath
prefixedFieldName FilePath
messageName (FilePath -> m FilePath) -> m FilePath -> m FilePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> m FilePath
dpIdentUnqualName DotProtoIdentifier
dotProtoFieldName
      HsType
fullTy <- TypeContext -> DotProtoType -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoType -> m HsType
dptToHsType TypeContext
ctxt' DotProtoType
dotProtoFieldType
      [([HsName], HsBangType)] -> m [([HsName], HsBangType)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [ ([FilePath -> HsName
HsIdent FilePath
fullName], HsType -> HsBangType
HsUnBangedTy HsType
fullTy ) ]

    messagePartFieldD FilePath
messageName (DotProtoMessageOneOf DotProtoIdentifier
fieldName [DotProtoField]
_) = do
      FilePath
fullName <- FilePath -> FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> FilePath -> m FilePath
prefixedFieldName FilePath
messageName (FilePath -> m FilePath) -> m FilePath -> m FilePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> m FilePath
dpIdentUnqualName DotProtoIdentifier
fieldName
      FilePath
qualTyName <- FilePath -> FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> FilePath -> m FilePath
prefixedConName FilePath
messageName (FilePath -> m FilePath) -> m FilePath -> m FilePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> m FilePath
dpIdentUnqualName DotProtoIdentifier
fieldName
      let fullTy :: HsType
fullTy = HsType -> HsType -> HsType
HsTyApp (HsQName -> HsType
HsTyCon (FilePath -> HsQName
haskellName FilePath
"Maybe")) (HsType -> HsType) -> (FilePath -> HsType) -> FilePath -> HsType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsType
type_ (FilePath -> HsType) -> FilePath -> HsType
forall a b. (a -> b) -> a -> b
$ FilePath
qualTyName
      [([HsName], HsBangType)] -> m [([HsName], HsBangType)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [ ([FilePath -> HsName
HsIdent FilePath
fullName], HsType -> HsBangType
HsUnBangedTy HsType
fullTy) ]

    messagePartFieldD FilePath
_ DotProtoMessagePart
_ = [([HsName], HsBangType)] -> m [([HsName], HsBangType)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []

    nestedDecls :: DotProtoDefinition -> m [HsDecl]
    nestedDecls :: DotProtoDefinition -> m [HsDecl]
nestedDecls (DotProtoMessage FilePath
_ DotProtoIdentifier
subMsgName [DotProtoMessagePart]
subMessageDef) = do
      DotProtoIdentifier
parentIdent' <- DotProtoIdentifier -> DotProtoIdentifier -> m DotProtoIdentifier
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> DotProtoIdentifier -> m DotProtoIdentifier
concatDotProtoIdentifier DotProtoIdentifier
parentIdent DotProtoIdentifier
messageIdent
      TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m [HsDecl]
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m [HsDecl]
dotProtoMessageD TypeContext
ctxt' DotProtoIdentifier
parentIdent' DotProtoIdentifier
subMsgName [DotProtoMessagePart]
subMessageDef

    nestedDecls (DotProtoEnum FilePath
_ DotProtoIdentifier
subEnumName [DotProtoEnumPart]
subEnumDef) = do
      DotProtoIdentifier
parentIdent' <- DotProtoIdentifier -> DotProtoIdentifier -> m DotProtoIdentifier
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> DotProtoIdentifier -> m DotProtoIdentifier
concatDotProtoIdentifier DotProtoIdentifier
parentIdent DotProtoIdentifier
messageIdent
      DotProtoIdentifier
-> DotProtoIdentifier -> [DotProtoEnumPart] -> m [HsDecl]
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier
-> DotProtoIdentifier -> [DotProtoEnumPart] -> m [HsDecl]
dotProtoEnumD DotProtoIdentifier
parentIdent' DotProtoIdentifier
subEnumName [DotProtoEnumPart]
subEnumDef

    nestedDecls DotProtoDefinition
_ = [HsDecl] -> m [HsDecl]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []

    nestedOneOfDecls :: String -> DotProtoIdentifier -> [DotProtoField] -> m [HsDecl]
    nestedOneOfDecls :: FilePath -> DotProtoIdentifier -> [DotProtoField] -> m [HsDecl]
nestedOneOfDecls FilePath
messageName DotProtoIdentifier
identifier [DotProtoField]
fields = do
      FilePath
fullName <- FilePath -> FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> FilePath -> m FilePath
prefixedConName FilePath
messageName (FilePath -> m FilePath) -> m FilePath -> m FilePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> m FilePath
dpIdentUnqualName DotProtoIdentifier
identifier

      ([HsConDecl]
cons, [HsName]
idents) <- ([(HsConDecl, HsName)] -> ([HsConDecl], [HsName]))
-> m [(HsConDecl, HsName)] -> m ([HsConDecl], [HsName])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(HsConDecl, HsName)] -> ([HsConDecl], [HsName])
forall a b. [(a, b)] -> ([a], [b])
unzip ((DotProtoField -> m (HsConDecl, HsName))
-> [DotProtoField] -> m [(HsConDecl, HsName)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (FilePath -> DotProtoField -> m (HsConDecl, HsName)
oneOfCons FilePath
fullName) [DotProtoField]
fields)

#ifdef SWAGGER
      HsDecl
toSchemaInstance <- FilePath -> Maybe [HsName] -> [FilePath] -> m HsDecl
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> Maybe [HsName] -> [FilePath] -> m HsDecl
toSchemaInstanceDeclaration FilePath
fullName ([HsName] -> Maybe [HsName]
forall a. a -> Maybe a
Just [HsName]
idents)
                            ([FilePath] -> m HsDecl) -> m [FilePath] -> m HsDecl
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (DotProtoField -> m FilePath) -> [DotProtoField] -> m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> m FilePath
dpIdentUnqualName (DotProtoIdentifier -> m FilePath)
-> (DotProtoField -> DotProtoIdentifier)
-> DotProtoField
-> m FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotProtoField -> DotProtoIdentifier
dotProtoFieldName) [DotProtoField]
fields
#endif

      [HsDecl] -> m [HsDecl]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [ FilePath -> [HsConDecl] -> [HsQName] -> HsDecl
dataDecl_ FilePath
fullName [HsConDecl]
cons [HsQName]
defaultMessageDeriving
           , FilePath -> HsDecl
namedInstD FilePath
fullName
#ifdef SWAGGER
           , HsDecl
toSchemaInstance
#endif

#ifdef DHALL
           , dhallInterpretInstDecl fullName
           , dhallInjectInstDecl fullName
#endif
           ]

    oneOfCons :: String -> DotProtoField -> m (HsConDecl, HsName)
    oneOfCons :: FilePath -> DotProtoField -> m (HsConDecl, HsName)
oneOfCons FilePath
fullName DotProtoField{FilePath
[DotProtoOption]
FieldNumber
DotProtoType
DotProtoIdentifier
dotProtoFieldComment :: FilePath
dotProtoFieldOptions :: [DotProtoOption]
dotProtoFieldName :: DotProtoIdentifier
dotProtoFieldType :: DotProtoType
dotProtoFieldNumber :: FieldNumber
dotProtoFieldComment :: DotProtoField -> FilePath
dotProtoFieldOptions :: DotProtoField -> [DotProtoOption]
dotProtoFieldType :: DotProtoField -> DotProtoType
dotProtoFieldNumber :: DotProtoField -> FieldNumber
dotProtoFieldName :: DotProtoField -> DotProtoIdentifier
..} = do
       HsType
consTy <- case DotProtoType
dotProtoFieldType of
            Prim msg :: DotProtoPrimType
msg@(Named DotProtoIdentifier
msgName)
              | TypeContext -> DotProtoIdentifier -> Bool
isMessage TypeContext
ctxt' DotProtoIdentifier
msgName
                -> TypeContext -> DotProtoPrimType -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoPrimType -> m HsType
dpptToHsType TypeContext
ctxt' DotProtoPrimType
msg
            DotProtoType
_   -> TypeContext -> DotProtoType -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoType -> m HsType
dptToHsType TypeContext
ctxt' DotProtoType
dotProtoFieldType

       FilePath
consName <- FilePath -> FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> FilePath -> m FilePath
prefixedConName FilePath
fullName (FilePath -> m FilePath) -> m FilePath -> m FilePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> m FilePath
dpIdentUnqualName DotProtoIdentifier
dotProtoFieldName
       let ident :: HsName
ident = FilePath -> HsName
HsIdent FilePath
consName
       (HsConDecl, HsName) -> m (HsConDecl, HsName)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsName -> [HsBangType] -> HsConDecl
conDecl_ HsName
ident [HsType -> HsBangType
HsUnBangedTy HsType
consTy], HsName
ident)

    oneOfCons FilePath
_ DotProtoField
DotProtoEmptyField = FilePath -> m (HsConDecl, HsName)
forall (m :: * -> *) a.
MonadError CompileError m =>
FilePath -> m a
internalError FilePath
"field type : empty field"

-- *** Generate Protobuf 'Message' instances

messageInstD
    :: forall m
     . MonadError CompileError m
    => TypeContext
    -> DotProtoIdentifier
    -> DotProtoIdentifier
    -> [DotProtoMessagePart]
    -> m HsDecl
messageInstD :: TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m HsDecl
messageInstD TypeContext
ctxt DotProtoIdentifier
parentIdent DotProtoIdentifier
msgIdent [DotProtoMessagePart]
messageParts = do
     FilePath
msgName         <- DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
qualifiedMessageName DotProtoIdentifier
parentIdent DotProtoIdentifier
msgIdent
     [QualifiedField]
qualifiedFields <- FilePath -> [DotProtoMessagePart] -> m [QualifiedField]
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> [DotProtoMessagePart] -> m [QualifiedField]
getQualifiedFields FilePath
msgName [DotProtoMessagePart]
messageParts

     [HsExp]
encodedFields   <- (QualifiedField -> m HsExp) -> [QualifiedField] -> m [HsExp]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM QualifiedField -> m HsExp
encodeMessageField [QualifiedField]
qualifiedFields
     [HsExp]
decodedFields   <- (QualifiedField -> m HsExp) -> [QualifiedField] -> m [HsExp]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM QualifiedField -> m HsExp
decodeMessageField [QualifiedField]
qualifiedFields

     let encodeMessageDecl :: HsMatch
encodeMessageDecl = HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"encodeMessage")
                                    [HsPat
HsPWildCard, HsQName -> [HsPatField] -> HsPat
HsPRec (FilePath -> HsQName
unqual_ FilePath
msgName) [HsPatField]
punnedFieldsP]
                                    (HsExp -> HsRhs
HsUnGuardedRhs HsExp
encodeMessageE) []

         encodeMessageE :: HsExp
encodeMessageE = HsExp -> [HsExp] -> HsExp
apply HsExp
mconcatE [[HsExp] -> HsExp
HsList [HsExp]
encodedFields]

         punnedFieldsP :: [HsPatField]
punnedFieldsP = (QualifiedField -> HsPatField) -> [QualifiedField] -> [HsPatField]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> HsPatField
fp (FilePath -> HsPatField)
-> (QualifiedField -> FilePath) -> QualifiedField -> HsPatField
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldName -> FilePath
coerce (FieldName -> FilePath)
-> (QualifiedField -> FieldName) -> QualifiedField -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QualifiedField -> FieldName
recordFieldName) [QualifiedField]
qualifiedFields
           where fp :: FilePath -> HsPatField
fp FilePath
nm = HsQName -> HsPat -> HsPatField
HsPFieldPat (FilePath -> HsQName
unqual_ FilePath
nm) (HsName -> HsPat
HsPVar (FilePath -> HsName
HsIdent FilePath
nm))


     let decodeMessageDecl :: HsMatch
decodeMessageDecl = HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"decodeMessage") [ HsPat
HsPWildCard ]
                                    (HsExp -> HsRhs
HsUnGuardedRhs HsExp
decodeMessageE) []

         decodeMessageE :: HsExp
decodeMessageE = (HsExp -> HsExp -> HsExp) -> HsExp -> [HsExp] -> HsExp
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\HsExp
f -> HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp HsExp
f HsQOp
apOp)
                                (HsExp -> [HsExp] -> HsExp
apply HsExp
pureE [ FilePath -> HsExp
uvar_ FilePath
msgName ])
                                [HsExp]
decodedFields

     let dotProtoDecl :: HsMatch
dotProtoDecl = HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"dotProto") [HsPat
HsPWildCard]
                               (HsExp -> HsRhs
HsUnGuardedRhs HsExp
dotProtoE) []

         dotProtoE :: HsExp
dotProtoE = [HsExp] -> HsExp
HsList ([HsExp] -> HsExp) -> [HsExp] -> HsExp
forall a b. (a -> b) -> a -> b
$ do
           DotProtoMessageField DotProtoField{FilePath
[DotProtoOption]
FieldNumber
DotProtoType
DotProtoIdentifier
dotProtoFieldComment :: FilePath
dotProtoFieldOptions :: [DotProtoOption]
dotProtoFieldName :: DotProtoIdentifier
dotProtoFieldType :: DotProtoType
dotProtoFieldNumber :: FieldNumber
dotProtoFieldComment :: DotProtoField -> FilePath
dotProtoFieldOptions :: DotProtoField -> [DotProtoOption]
dotProtoFieldType :: DotProtoField -> DotProtoType
dotProtoFieldNumber :: DotProtoField -> FieldNumber
dotProtoFieldName :: DotProtoField -> DotProtoIdentifier
..} <- [DotProtoMessagePart]
messageParts
           HsExp -> [HsExp]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsExp -> [HsExp]) -> HsExp -> [HsExp]
forall a b. (a -> b) -> a -> b
$ HsExp -> [HsExp] -> HsExp
apply HsExp
dotProtoFieldC
                        [ FieldNumber -> HsExp
fieldNumberE FieldNumber
dotProtoFieldNumber
                        , DotProtoType -> HsExp
dpTypeE DotProtoType
dotProtoFieldType
                        , DotProtoIdentifier -> HsExp
dpIdentE DotProtoIdentifier
dotProtoFieldName
                        , [HsExp] -> HsExp
HsList ((DotProtoOption -> HsExp) -> [DotProtoOption] -> [HsExp]
forall a b. (a -> b) -> [a] -> [b]
map DotProtoOption -> HsExp
optionE [DotProtoOption]
dotProtoFieldOptions)
                        , FilePath -> HsExp
str_ FilePath
dotProtoFieldComment
                        ]


     HsDecl -> m HsDecl
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsDecl -> m HsDecl) -> HsDecl -> m HsDecl
forall a b. (a -> b) -> a -> b
$ HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
protobufName FilePath
"Message")
                      [ FilePath -> HsType
type_ FilePath
msgName ]
                      [ [HsMatch] -> HsDecl
HsFunBind [ HsMatch
encodeMessageDecl ]
                      , [HsMatch] -> HsDecl
HsFunBind [ HsMatch
decodeMessageDecl ]
                      , [HsMatch] -> HsDecl
HsFunBind [ HsMatch
dotProtoDecl ]
                      ]
  where
    encodeMessageField :: QualifiedField -> m HsExp
    encodeMessageField :: QualifiedField -> m HsExp
encodeMessageField QualifiedField{FieldName
recordFieldName :: FieldName
recordFieldName :: QualifiedField -> FieldName
recordFieldName, FieldInfo
fieldInfo :: QualifiedField -> FieldInfo
fieldInfo :: FieldInfo
fieldInfo} =
      let recordFieldName' :: HsExp
recordFieldName' = FilePath -> HsExp
uvar_ (FieldName -> FilePath
coerce FieldName
recordFieldName) in
      case FieldInfo
fieldInfo of
        FieldNormal FieldName
_fieldName FieldNumber
fieldNum DotProtoType
dpType [DotProtoOption]
options -> do
            HsExp
fieldE <- TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
wrapE TypeContext
ctxt [DotProtoOption]
options DotProtoType
dpType HsExp
recordFieldName'
            HsExp -> m HsExp
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsExp -> m HsExp) -> HsExp -> m HsExp
forall a b. (a -> b) -> a -> b
$ HsExp -> [HsExp] -> HsExp
apply HsExp
encodeMessageFieldE [ FieldNumber -> HsExp
fieldNumberE FieldNumber
fieldNum, HsExp
fieldE ]

        FieldOneOf OneofField{[OneofSubfield]
subfields :: OneofField -> [OneofSubfield]
subfields :: [OneofSubfield]
subfields} -> do
            [HsAlt]
alts <- (OneofSubfield -> m HsAlt) -> [OneofSubfield] -> m [HsAlt]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM OneofSubfield -> m HsAlt
forall (m :: * -> *).
MonadError CompileError m =>
OneofSubfield -> m HsAlt
mkAlt [OneofSubfield]
subfields
            HsExp -> m HsExp
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsExp -> m HsExp) -> HsExp -> m HsExp
forall a b. (a -> b) -> a -> b
$ HsExp -> [HsAlt] -> HsExp
HsCase HsExp
recordFieldName'
                    [ HsPat -> HsGuardedAlts -> [HsDecl] -> HsAlt
alt_ (HsQName -> [HsPat] -> HsPat
HsPApp (FilePath -> HsQName
haskellName FilePath
"Nothing") [])
                           (HsExp -> HsGuardedAlts
HsUnGuardedAlt HsExp
memptyE)
                           []
                    , HsPat -> HsGuardedAlts -> [HsDecl] -> HsAlt
alt_ (HsQName -> [HsPat] -> HsPat
HsPApp (FilePath -> HsQName
haskellName FilePath
"Just") [FilePath -> HsPat
patVar FilePath
"x"])
                           (HsExp -> HsGuardedAlts
HsUnGuardedAlt (HsExp -> [HsAlt] -> HsExp
HsCase (FilePath -> HsExp
uvar_ FilePath
"x") [HsAlt]
alts))
                           []
                    ]
          where
            -- Create all pattern match & expr for each constructor:
            --    Constructor y -> encodeMessageField num (Nested (Just y)) -- for embedded messages
            --    Constructor y -> encodeMessageField num (ForceEmit y)     -- for everything else
            mkAlt :: OneofSubfield -> m HsAlt
mkAlt (OneofSubfield FieldNumber
fieldNum FilePath
conName FieldName
_ DotProtoType
dpType [DotProtoOption]
options) = do
              let isMaybe :: Bool
isMaybe
                     | Prim (Named DotProtoIdentifier
tyName) <- DotProtoType
dpType
                     = TypeContext -> DotProtoIdentifier -> Bool
isMessage TypeContext
ctxt DotProtoIdentifier
tyName
                     | Bool
otherwise
                     = Bool
False

              let wrapJust :: HsExp -> HsExp
wrapJust = HsExp -> HsExp
HsParen (HsExp -> HsExp) -> (HsExp -> HsExp) -> HsExp -> HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsExp -> HsExp -> HsExp
HsApp (HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"Just"))

              HsExp
xE <- (if Bool
isMaybe then m HsExp -> m HsExp
forall a. a -> a
id else (HsExp -> HsExp) -> m HsExp -> m HsExp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HsExp -> HsExp
forceEmitE)
                     (m HsExp -> m HsExp) -> (HsExp -> m HsExp) -> HsExp -> m HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
wrapE TypeContext
ctxt [DotProtoOption]
options DotProtoType
dpType
                     (HsExp -> m HsExp) -> (HsExp -> HsExp) -> HsExp -> m HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Bool
isMaybe then HsExp -> HsExp
wrapJust else HsExp -> HsExp
forall a. a -> a
id)
                     (HsExp -> m HsExp) -> HsExp -> m HsExp
forall a b. (a -> b) -> a -> b
$ FilePath -> HsExp
uvar_ FilePath
"y"

              HsAlt -> m HsAlt
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsAlt -> m HsAlt) -> HsAlt -> m HsAlt
forall a b. (a -> b) -> a -> b
$ HsPat -> HsGuardedAlts -> [HsDecl] -> HsAlt
alt_ (HsQName -> [HsPat] -> HsPat
HsPApp (FilePath -> HsQName
unqual_ FilePath
conName) [FilePath -> HsPat
patVar FilePath
"y"])
                          (HsExp -> HsGuardedAlts
HsUnGuardedAlt (HsExp -> [HsExp] -> HsExp
apply HsExp
encodeMessageFieldE [FieldNumber -> HsExp
fieldNumberE FieldNumber
fieldNum, HsExp
xE]))
                          []


    decodeMessageField :: QualifiedField -> m HsExp
    decodeMessageField :: QualifiedField -> m HsExp
decodeMessageField QualifiedField{FieldInfo
fieldInfo :: FieldInfo
fieldInfo :: QualifiedField -> FieldInfo
fieldInfo} =
      case FieldInfo
fieldInfo of
        FieldNormal FieldName
_fieldName FieldNumber
fieldNum DotProtoType
dpType [DotProtoOption]
options ->
            TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
unwrapE TypeContext
ctxt [DotProtoOption]
options DotProtoType
dpType (HsExp -> m HsExp) -> HsExp -> m HsExp
forall a b. (a -> b) -> a -> b
$ HsExp -> [HsExp] -> HsExp
apply HsExp
atE [ HsExp
decodeMessageFieldE, FieldNumber -> HsExp
fieldNumberE FieldNumber
fieldNum ]

        FieldOneOf OneofField{[OneofSubfield]
subfields :: [OneofSubfield]
subfields :: OneofField -> [OneofSubfield]
subfields} -> do
            [HsExp]
parsers <- (OneofSubfield -> m HsExp) -> [OneofSubfield] -> m [HsExp]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM OneofSubfield -> m HsExp
forall (m :: * -> *).
MonadError CompileError m =>
OneofSubfield -> m HsExp
subfieldParserE [OneofSubfield]
subfields
            HsExp -> m HsExp
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsExp -> m HsExp) -> HsExp -> m HsExp
forall a b. (a -> b) -> a -> b
$  HsExp -> [HsExp] -> HsExp
apply HsExp
oneofE [ HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"Nothing")
                                 , [HsExp] -> HsExp
HsList [HsExp]
parsers
                                 ]
          where
            -- create a list of (fieldNumber, Cons <$> parser)
            subfieldParserE :: OneofSubfield -> m HsExp
subfieldParserE (OneofSubfield FieldNumber
fieldNumber FilePath
consName FieldName
_ DotProtoType
dpType [DotProtoOption]
options) = do
              let fE :: HsExp
fE | Prim (Named DotProtoIdentifier
tyName) <- DotProtoType
dpType, TypeContext -> DotProtoIdentifier -> Bool
isMessage TypeContext
ctxt DotProtoIdentifier
tyName
                     = HsExp -> HsExp
HsParen (HsExp -> HsExp -> HsExp
HsApp HsExp
fmapE (FilePath -> HsExp
uvar_ FilePath
consName))
                     | Bool
otherwise
                     = HsExp -> HsExp
HsParen (HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp (HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"Just"))
                                           HsQOp
composeOp
                                           (FilePath -> HsExp
uvar_ FilePath
consName))

              HsExp
alts <- TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> [DotProtoOption] -> DotProtoType -> HsExp -> m HsExp
unwrapE TypeContext
ctxt [DotProtoOption]
options DotProtoType
dpType HsExp
decodeMessageFieldE

              HsExp -> m HsExp
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsExp -> m HsExp) -> HsExp -> m HsExp
forall a b. (a -> b) -> a -> b
$ [HsExp] -> HsExp
HsTuple
                   [ FieldNumber -> HsExp
fieldNumberE FieldNumber
fieldNumber
                   , HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp (HsExp -> [HsExp] -> HsExp
apply HsExp
pureE [ HsExp
fE ]) HsQOp
apOp HsExp
alts
                   ]


-- *** Generate ToJSONPB/FromJSONPB instances

toJSONPBMessageInstD
    :: MonadError CompileError m
    => TypeContext
    -> DotProtoIdentifier
    -> DotProtoIdentifier
    -> [DotProtoMessagePart]
    -> m HsDecl
toJSONPBMessageInstD :: TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m HsDecl
toJSONPBMessageInstD TypeContext
_ctxt DotProtoIdentifier
parentIdent DotProtoIdentifier
msgIdent [DotProtoMessagePart]
messageParts = do
    FilePath
msgName    <- DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
qualifiedMessageName DotProtoIdentifier
parentIdent DotProtoIdentifier
msgIdent
    [QualifiedField]
qualFields <- FilePath -> [DotProtoMessagePart] -> m [QualifiedField]
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> [DotProtoMessagePart] -> m [QualifiedField]
getQualifiedFields FilePath
msgName [DotProtoMessagePart]
messageParts

    let applyE :: FilePath -> FilePath -> HsExp
applyE FilePath
nm FilePath
oneofNm =
          HsExp -> [HsExp] -> HsExp
apply (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
nm))
                [ [HsExp] -> HsExp
HsList ((FieldName -> FieldNumber -> HsExp)
-> (OneofField -> HsExp) -> QualifiedField -> HsExp
forall a.
(FieldName -> FieldNumber -> a)
-> (OneofField -> a) -> QualifiedField -> a
foldQF FieldName -> FieldNumber -> HsExp
forall a. Coercible a FilePath => a -> FieldNumber -> HsExp
defPairE (FilePath -> OneofField -> HsExp
oneofCaseE FilePath
oneofNm) (QualifiedField -> HsExp) -> [QualifiedField] -> [HsExp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [QualifiedField]
qualFields) ]

    let patBinder :: QualifiedField -> FilePath
patBinder = (FieldName -> FieldNumber -> FilePath)
-> (OneofField -> FilePath) -> QualifiedField -> FilePath
forall a.
(FieldName -> FieldNumber -> a)
-> (OneofField -> a) -> QualifiedField -> a
foldQF ((FieldNumber -> FilePath) -> FieldName -> FieldNumber -> FilePath
forall a b. a -> b -> a
const FieldNumber -> FilePath
fieldBinder) ([OneofSubfield] -> FilePath
oneofSubDisjunctBinder ([OneofSubfield] -> FilePath)
-> (OneofField -> [OneofSubfield]) -> OneofField -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OneofField -> [OneofSubfield]
subfields)
    let matchE :: FilePath -> FilePath -> FilePath -> HsMatch
matchE FilePath
nm FilePath
appNm FilePath
oneofAppNm =
          HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_
            (FilePath -> HsName
HsIdent FilePath
nm)
            [ HsQName -> [HsPat] -> HsPat
HsPApp (FilePath -> HsQName
unqual_ FilePath
msgName)
                     (FilePath -> HsPat
patVar (FilePath -> HsPat)
-> (QualifiedField -> FilePath) -> QualifiedField -> HsPat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QualifiedField -> FilePath
patBinder (QualifiedField -> HsPat) -> [QualifiedField] -> [HsPat]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [QualifiedField]
qualFields) ]
            (HsExp -> HsRhs
HsUnGuardedRhs (FilePath -> FilePath -> HsExp
applyE FilePath
appNm FilePath
oneofAppNm))
            []

    HsDecl -> m HsDecl
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsDecl -> m HsDecl) -> HsDecl -> m HsDecl
forall a b. (a -> b) -> a -> b
$ HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
jsonpbName FilePath
"ToJSONPB")
                     [ FilePath -> HsType
type_ FilePath
msgName ]
                     [ [HsMatch] -> HsDecl
HsFunBind [FilePath -> FilePath -> FilePath -> HsMatch
matchE FilePath
"toJSONPB"     FilePath
"object" FilePath
"objectOrNull"]
                     , [HsMatch] -> HsDecl
HsFunBind [FilePath -> FilePath -> FilePath -> HsMatch
matchE FilePath
"toEncodingPB" FilePath
"pairs"  FilePath
"pairsOrNull" ]
                     ]

  where
    -- E.g.
    -- "another" .= f2 -- always succeeds (produces default value on missing field)
    defPairE :: a -> FieldNumber -> HsExp
defPairE a
fldName FieldNumber
fldNum =
      HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp (FilePath -> HsExp
str_ (a -> FilePath
coerce a
fldName))
                 HsQOp
toJSONPBOp
                 (FilePath -> HsExp
uvar_ (FieldNumber -> FilePath
fieldBinder FieldNumber
fldNum))

    -- E.g.
    -- HsJSONPB.pair "name" f4 -- fails on missing field
    pairE :: a -> FilePath -> HsExp
pairE a
fldNm FilePath
varNm =
      HsExp -> [HsExp] -> HsExp
apply (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"pair"))
            [ FilePath -> HsExp
str_ (a -> FilePath
coerce a
fldNm) , FilePath -> HsExp
uvar_ FilePath
varNm]

    -- Suppose we have a sum type Foo, nested inside a message Bar.
    -- We want to generate the following:
    --
    -- > toJSONPB (Bar foo more stuff) =
    -- >   HsJSONPB.object
    -- >     [ (let encodeFoo = (<case expr scrutinising foo> :: Options -> Value)
    -- >        in \option -> if optEmitNamedOneof option
    -- >                      then ("Foo" .= (PB.objectOrNull [encodeFoo] option)) option
    -- >                      else encodeFoo option
    -- >       )
    -- >     , <encode more>
    -- >     , <encode stuff>
    -- >     ]
    oneofCaseE :: FilePath -> OneofField -> HsExp
oneofCaseE FilePath
retJsonCtor (OneofField FilePath
typeName [OneofSubfield]
subfields) =
        HsExp -> HsExp
HsParen
          (HsExp -> HsExp) -> HsExp -> HsExp
forall a b. (a -> b) -> a -> b
$ [HsDecl] -> HsExp -> HsExp
HsLet [ [HsMatch] -> HsDecl
HsFunBind [ HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
caseName) [] (HsExp -> HsRhs
HsUnGuardedRhs HsExp
caseExpr) [] ] ]
          (HsExp -> HsExp) -> HsExp -> HsExp
forall a b. (a -> b) -> a -> b
$ SrcLoc -> [HsPat] -> HsExp -> HsExp
HsLambda SrcLoc
defaultSrcLoc [FilePath -> HsPat
patVar FilePath
optsStr] (HsExp -> HsExp -> HsExp -> HsExp
HsIf HsExp
dontInline HsExp
noInline HsExp
yesInline)
      where
        optsStr :: FilePath
optsStr = FilePath
"options"
        opts :: HsExp
opts    = FilePath -> HsExp
uvar_ FilePath
optsStr

        caseName :: FilePath
caseName = FilePath
"encode" FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> ASetter FilePath FilePath Char Char
-> (Char -> Char) -> FilePath -> FilePath
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (Index FilePath -> Traversal' FilePath (IxValue FilePath)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index FilePath
0) Char -> Char
toUpper FilePath
typeName
        caseBnd :: HsExp
caseBnd = FilePath -> HsExp
uvar_ FilePath
caseName

        dontInline :: HsExp
dontInline = HsExp -> HsExp -> HsExp
HsApp (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"optEmitNamedOneof")) HsExp
opts

        noInline :: HsExp
noInline = HsExp -> HsExp -> HsExp
HsApp (HsExp -> HsExp
HsParen (HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp (FilePath -> HsExp
str_ FilePath
typeName)
                                              HsQOp
toJSONPBOp
                                              (HsExp -> [HsExp] -> HsExp
apply (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
retJsonCtor))
                                                     [ [HsExp] -> HsExp
HsList [HsExp
caseBnd], HsExp
opts ])))
                         HsExp
opts

        yesInline :: HsExp
yesInline = HsExp -> HsExp -> HsExp
HsApp HsExp
caseBnd HsExp
opts


        -- E.g.
        -- case f4_or_f9 of
        --   Just (SomethingPickOneName f4)
        --     -> HsJSONPB.pair "name" f4
        --   Just (SomethingPickOneSomeid f9)
        --     -> HsJSONPB.pair "someid" f9
        --   Nothing
        --     -> mempty
        caseExpr :: HsExp
caseExpr = HsExp -> HsExp
HsParen (HsExp -> HsExp) -> HsExp -> HsExp
forall a b. (a -> b) -> a -> b
$
            HsExp -> [HsAlt] -> HsExp
HsCase HsExp
disjunctName ([HsAlt]
altEs [HsAlt] -> [HsAlt] -> [HsAlt]
forall a. Semigroup a => a -> a -> a
<> [HsAlt
fallthroughE])
          where
            disjunctName :: HsExp
disjunctName = FilePath -> HsExp
uvar_ ([OneofSubfield] -> FilePath
oneofSubDisjunctBinder [OneofSubfield]
subfields)
            altEs :: [HsAlt]
altEs = do
              sub :: OneofSubfield
sub@(OneofSubfield FieldNumber
_ FilePath
conName FieldName
pbFldNm DotProtoType
_ [DotProtoOption]
_) <- [OneofSubfield]
subfields
              let patVarNm :: FilePath
patVarNm = OneofSubfield -> FilePath
oneofSubBinder OneofSubfield
sub
              HsAlt -> [HsAlt]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsAlt -> [HsAlt]) -> HsAlt -> [HsAlt]
forall a b. (a -> b) -> a -> b
$ HsPat -> HsGuardedAlts -> [HsDecl] -> HsAlt
alt_ (HsQName -> [HsPat] -> HsPat
HsPApp (FilePath -> HsQName
haskellName FilePath
"Just")
                                  [ HsPat -> HsPat
HsPParen
                                    (HsQName -> [HsPat] -> HsPat
HsPApp (FilePath -> HsQName
unqual_ FilePath
conName) [FilePath -> HsPat
patVar FilePath
patVarNm])
                                  ]
                          )
                          (HsExp -> HsGuardedAlts
HsUnGuardedAlt (FieldName -> FilePath -> HsExp
forall a. Coercible a FilePath => a -> FilePath -> HsExp
pairE FieldName
pbFldNm FilePath
patVarNm))
                          []
            fallthroughE :: HsAlt
fallthroughE =
              HsPat -> HsGuardedAlts -> [HsDecl] -> HsAlt
alt_ (HsQName -> [HsPat] -> HsPat
HsPApp (FilePath -> HsQName
haskellName FilePath
"Nothing") [])
                   (HsExp -> HsGuardedAlts
HsUnGuardedAlt HsExp
memptyE)
                   []

fromJSONPBMessageInstD
    :: MonadError CompileError m
    => TypeContext
    -> DotProtoIdentifier
    -> DotProtoIdentifier
    -> [DotProtoMessagePart]
    -> m HsDecl
fromJSONPBMessageInstD :: TypeContext
-> DotProtoIdentifier
-> DotProtoIdentifier
-> [DotProtoMessagePart]
-> m HsDecl
fromJSONPBMessageInstD TypeContext
_ctxt DotProtoIdentifier
parentIdent DotProtoIdentifier
msgIdent [DotProtoMessagePart]
messageParts = do
    FilePath
msgName    <- DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
qualifiedMessageName DotProtoIdentifier
parentIdent DotProtoIdentifier
msgIdent
    [QualifiedField]
qualFields <- FilePath -> [DotProtoMessagePart] -> m [QualifiedField]
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> [DotProtoMessagePart] -> m [QualifiedField]
getQualifiedFields FilePath
msgName [DotProtoMessagePart]
messageParts

    let parseJSONPBE :: HsExp
parseJSONPBE =
          HsExp -> [HsExp] -> HsExp
apply (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"withObject"))
                [ FilePath -> HsExp
str_ FilePath
msgName
                , HsExp -> HsExp
HsParen (SrcLoc -> [HsPat] -> HsExp -> HsExp
HsLambda SrcLoc
defaultSrcLoc [HsPat
lambdaPVar] HsExp
fieldAps)
                ]
          where
            fieldAps :: HsExp
fieldAps = (HsExp -> HsExp -> HsExp) -> HsExp -> [HsExp] -> HsExp
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\HsExp
f -> HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp HsExp
f HsQOp
apOp)
                             (HsExp -> [HsExp] -> HsExp
apply HsExp
pureE [ FilePath -> HsExp
uvar_ FilePath
msgName ])
                             ((FieldName -> FieldNumber -> HsExp)
-> (OneofField -> HsExp) -> QualifiedField -> HsExp
forall a.
(FieldName -> FieldNumber -> a)
-> (OneofField -> a) -> QualifiedField -> a
foldQF FieldName -> FieldNumber -> HsExp
forall a p. Coercible a FilePath => a -> p -> HsExp
normalParserE OneofField -> HsExp
oneofParserE (QualifiedField -> HsExp) -> [QualifiedField] -> [HsExp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [QualifiedField]
qualFields)

    let parseJSONPBDecl :: HsMatch
parseJSONPBDecl =
          HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"parseJSONPB") [] (HsExp -> HsRhs
HsUnGuardedRhs HsExp
parseJSONPBE) []

    HsDecl -> m HsDecl
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
jsonpbName FilePath
"FromJSONPB")
                   [ FilePath -> HsType
type_ FilePath
msgName ]
                   [ [HsMatch] -> HsDecl
HsFunBind [ HsMatch
parseJSONPBDecl ] ])
  where
    lambdaPVar :: HsPat
lambdaPVar = FilePath -> HsPat
patVar FilePath
"obj"
    lambdaVar :: HsExp
lambdaVar  = FilePath -> HsExp
uvar_ FilePath
"obj"

    -- E.g., for message
    --   message Something { oneof name_or_id { string name = _; int32 someid = _; } }
    --
    -- ==>
    --
    -- (let parseSomethingNameOrId parseObj = <FUNCTION, see tryParseDisjunctsE>
    --  in ((obj .: "nameOrId") Hs.>>=
    --      (HsJSONPB.withObject "nameOrId" parseSomethingNameOrId))
    --     <|>
    --     (parseSomethingNameOrId obj)
    -- )
    oneofParserE :: OneofField -> HsExp
oneofParserE (OneofField FilePath
oneofType [OneofSubfield]
fields) =
        HsExp -> HsExp
HsParen (HsExp -> HsExp) -> HsExp -> HsExp
forall a b. (a -> b) -> a -> b
$
          [HsDecl] -> HsExp -> HsExp
HsLet [ [HsMatch] -> HsDecl
HsFunBind [ HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
letBndStr) [FilePath -> HsPat
patVar FilePath
letArgStr ]
                                     (HsExp -> HsRhs
HsUnGuardedRhs HsExp
tryParseDisjunctsE) []
                            ]
                ]
                (HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp HsExp
parseWrapped HsQOp
altOp HsExp
parseUnwrapped)
      where
        oneofTyLit :: HsExp
oneofTyLit = FilePath -> HsExp
str_ FilePath
oneofType -- FIXME

        letBndStr :: FilePath
letBndStr  = FilePath
"parse" FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> ASetter FilePath FilePath Char Char
-> (Char -> Char) -> FilePath -> FilePath
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (Index FilePath -> Traversal' FilePath (IxValue FilePath)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index FilePath
0) Char -> Char
toUpper FilePath
oneofType
        letBndName :: HsExp
letBndName = FilePath -> HsExp
uvar_ FilePath
letBndStr
        letArgStr :: FilePath
letArgStr  = FilePath
"parseObj"
        letArgName :: HsExp
letArgName = FilePath -> HsExp
uvar_ FilePath
letArgStr

        parseWrapped :: HsExp
parseWrapped = HsExp -> HsExp
HsParen (HsExp -> HsExp) -> HsExp -> HsExp
forall a b. (a -> b) -> a -> b
$
          HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp (HsExp -> HsExp
HsParen (HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp HsExp
lambdaVar HsQOp
parseJSONPBOp HsExp
oneofTyLit))
                     HsQOp
bindOp
                     (HsExp -> [HsExp] -> HsExp
apply (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"withObject")) [ HsExp
oneofTyLit , HsExp
letBndName ])

        parseUnwrapped :: HsExp
parseUnwrapped = HsExp -> HsExp
HsParen (HsExp -> HsExp -> HsExp
HsApp HsExp
letBndName HsExp
lambdaVar)

        -- parseSomethingNameOrId parseObj =
        --   Hs.msum
        --     [ (Just . SomethingPickOneName) <$> (HsJSONPB.parseField parseObj "name")
        --     , (Just . SomethingPickOneSomeid) <$> (HsJSONPB.parseField parseObj "someid")
        --     , pure Nothing
        --     ]
        tryParseDisjunctsE :: HsExp
tryParseDisjunctsE =
            HsExp -> HsExp -> HsExp
HsApp HsExp
msumE ([HsExp] -> HsExp
HsList ((OneofSubfield -> HsExp) -> [OneofSubfield] -> [HsExp]
forall a b. (a -> b) -> [a] -> [b]
map OneofSubfield -> HsExp
subParserE [OneofSubfield]
fields [HsExp] -> [HsExp] -> [HsExp]
forall a. Semigroup a => a -> a -> a
<> [HsExp]
fallThruE))
          where
            fallThruE :: [HsExp]
fallThruE
              = [ HsExp -> HsExp -> HsExp
HsApp HsExp
pureE (HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"Nothing")) ]
            subParserE :: OneofSubfield -> HsExp
subParserE OneofSubfield{FilePath
subfieldConsName :: OneofSubfield -> FilePath
subfieldConsName :: FilePath
subfieldConsName, FieldName
subfieldName :: OneofSubfield -> FieldName
subfieldName :: FieldName
subfieldName}
              = HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp
                  (HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp (HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"Just"))
                              HsQOp
composeOp
                              (FilePath -> HsExp
uvar_ FilePath
subfieldConsName))
                  HsQOp
fmapOp
                  (HsExp -> [HsExp] -> HsExp
apply (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"parseField"))
                         [ HsExp
letArgName
                         , FilePath -> HsExp
str_ (FieldName -> FilePath
coerce FieldName
subfieldName)])

    -- E.g. obj .: "someid"
    normalParserE :: a -> p -> HsExp
normalParserE a
fldNm p
_ =
      HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp HsExp
lambdaVar
                 HsQOp
parseJSONPBOp
                 (FilePath -> HsExp
str_(a -> FilePath
coerce a
fldNm))

-- *** Generate default Aeson To/FromJSON and Swagger ToSchema instances
-- (These are defined in terms of ToJSONPB)

toJSONInstDecl :: String -> HsDecl
toJSONInstDecl :: FilePath -> HsDecl
toJSONInstDecl FilePath
typeName =
  HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
jsonpbName FilePath
"ToJSON")
            [ FilePath -> HsType
type_ FilePath
typeName ]
            [ [HsMatch] -> HsDecl
HsFunBind [ HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"toJSON") []
                                 (HsExp -> HsRhs
HsUnGuardedRhs (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"toAesonValue"))) []
                        ]
            , [HsMatch] -> HsDecl
HsFunBind [ HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"toEncoding") []
                                 (HsExp -> HsRhs
HsUnGuardedRhs (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"toAesonEncoding"))) []
                        ]
            ]

fromJSONInstDecl :: String -> HsDecl
fromJSONInstDecl :: FilePath -> HsDecl
fromJSONInstDecl FilePath
typeName =
  HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
jsonpbName FilePath
"FromJSON")
            [ FilePath -> HsType
type_ FilePath
typeName ]
            [ [HsMatch] -> HsDecl
HsFunBind [HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"parseJSON") []
                                (HsExp -> HsRhs
HsUnGuardedRhs (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"parseJSONPB"))) []
                        ]
            ]


-- *** Generate `ToSchema` instance

toSchemaInstanceDeclaration
    :: MonadError CompileError m
    => String
    -- ^ Name of the message type to create an instance for
    -> Maybe [HsName]
    -- ^ Oneof constructors
    -> [String]
    -- ^ Field names
    -> m HsDecl
toSchemaInstanceDeclaration :: FilePath -> Maybe [HsName] -> [FilePath] -> m HsDecl
toSchemaInstanceDeclaration FilePath
messageName Maybe [HsName]
maybeConstructors [FilePath]
fieldNames = do
  [FilePath]
qualifiedFieldNames <- (FilePath -> m FilePath) -> [FilePath] -> m [FilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (FilePath -> FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> FilePath -> m FilePath
prefixedFieldName FilePath
messageName) [FilePath]
fieldNames

  let messageConstructor :: HsExp
messageConstructor = HsQName -> HsExp
HsCon (HsName -> HsQName
UnQual (FilePath -> HsName
HsIdent FilePath
messageName))

  let _namedSchemaNameExpression :: HsExp
_namedSchemaNameExpression = HsExp -> HsExp -> HsExp
HsApp HsExp
justC (FilePath -> HsExp
str_ FilePath
messageName)

#ifdef SWAGGER
      -- { _paramSchemaType = HsJSONPB.SwaggerObject
      -- }
  let paramSchemaUpdates :: [HsFieldUpdate]
paramSchemaUpdates =
        [ HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate HsQName
_paramSchemaType HsExp
_paramSchemaTypeExpression
        ]
        where
          _paramSchemaType :: HsQName
_paramSchemaType = FilePath -> HsQName
jsonpbName FilePath
"_paramSchemaType"

#if MIN_VERSION_swagger2(2,4,0)
          _paramSchemaTypeExpression :: HsExp
_paramSchemaTypeExpression = HsExp -> HsExp -> HsExp
HsApp HsExp
justC (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"SwaggerObject"))
#else
          _paramSchemaTypeExpression = HsVar (jsonpbName "SwaggerObject")
#endif
#else
  let paramSchemaUpdates = []
#endif

  let _schemaParamSchemaExpression :: HsExp
_schemaParamSchemaExpression = HsExp -> [HsFieldUpdate] -> HsExp
HsRecUpdate HsExp
memptyE [HsFieldUpdate]
paramSchemaUpdates

      -- [ ("fieldName0", qualifiedFieldName0)
      -- , ("fieldName1", qualifiedFieldName1)
      -- ...
      -- ]
  let properties :: HsExp
properties = [HsExp] -> HsExp
HsList ([HsExp] -> HsExp) -> [HsExp] -> HsExp
forall a b. (a -> b) -> a -> b
$ do
        (FilePath
fieldName, FilePath
qualifiedFieldName) <- [FilePath] -> [FilePath] -> [(FilePath, FilePath)]
forall a b. [a] -> [b] -> [(a, b)]
zip [FilePath]
fieldNames [FilePath]
qualifiedFieldNames
        HsExp -> [HsExp]
forall (m :: * -> *) a. Monad m => a -> m a
return ([HsExp] -> HsExp
HsTuple [ FilePath -> HsExp
str_  FilePath
fieldName, FilePath -> HsExp
uvar_ FilePath
qualifiedFieldName ])

  let _schemaPropertiesExpression :: HsExp
_schemaPropertiesExpression =
        HsExp -> HsExp -> HsExp
HsApp (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"insOrdFromList")) HsExp
properties

      -- { _schemaParamSchema = ...
      -- , _schemaProperties  = ...
      -- , ...
      -- }
  let schemaUpdates :: [HsFieldUpdate]
schemaUpdates = [HsFieldUpdate]
normalUpdates [HsFieldUpdate] -> [HsFieldUpdate] -> [HsFieldUpdate]
forall a. [a] -> [a] -> [a]
++ [HsFieldUpdate]
extraUpdates
        where
          normalUpdates :: [HsFieldUpdate]
normalUpdates =
            [ HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate HsQName
_schemaParamSchema HsExp
_schemaParamSchemaExpression
            , HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate HsQName
_schemaProperties  HsExp
_schemaPropertiesExpression
            ]

          extraUpdates :: [HsFieldUpdate]
extraUpdates =
            case Maybe [HsName]
maybeConstructors of
                Just [HsName]
_ ->
                  [ HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate HsQName
_schemaMinProperties HsExp
justOne
                  , HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate HsQName
_schemaMaxProperties HsExp
justOne
                  ]
                Maybe [HsName]
Nothing ->
                  []

          _schemaParamSchema :: HsQName
_schemaParamSchema    = FilePath -> HsQName
jsonpbName FilePath
"_schemaParamSchema"
          _schemaProperties :: HsQName
_schemaProperties     = FilePath -> HsQName
jsonpbName FilePath
"_schemaProperties"
          _schemaMinProperties :: HsQName
_schemaMinProperties  = FilePath -> HsQName
jsonpbName FilePath
"_schemaMinProperties"
          _schemaMaxProperties :: HsQName
_schemaMaxProperties  = FilePath -> HsQName
jsonpbName FilePath
"_schemaMaxProperties"

          justOne :: HsExp
justOne = HsExp -> HsExp -> HsExp
HsApp HsExp
justC (HsLiteral -> HsExp
HsLit (Integer -> HsLiteral
HsInt Integer
1))

  let _namedSchemaSchemaExpression :: HsExp
_namedSchemaSchemaExpression = HsExp -> [HsFieldUpdate] -> HsExp
HsRecUpdate HsExp
memptyE [HsFieldUpdate]
schemaUpdates

      -- { _namedSchemaName   = ...
      -- , _namedSchemaSchema = ...
      -- }
  let namedSchemaUpdates :: [HsFieldUpdate]
namedSchemaUpdates =
        [ HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate HsQName
_namedSchemaName   HsExp
_namedSchemaNameExpression
        , HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate HsQName
_namedSchemaSchema HsExp
_namedSchemaSchemaExpression
        ]
        where
          _namedSchemaName :: HsQName
_namedSchemaName   = FilePath -> HsQName
jsonpbName FilePath
"_namedSchemaName"
          _namedSchemaSchema :: HsQName
_namedSchemaSchema = FilePath -> HsQName
jsonpbName FilePath
"_namedSchemaSchema"

  let namedSchema :: HsExp
namedSchema = HsQName -> [HsFieldUpdate] -> HsExp
HsRecConstr (FilePath -> HsQName
jsonpbName FilePath
"NamedSchema") [HsFieldUpdate]
namedSchemaUpdates

  let toDeclareName :: FilePath -> FilePath
toDeclareName FilePath
fieldName = FilePath
"declare_" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
fieldName

  let toArgument :: FilePath -> HsExp
toArgument FilePath
fieldName = HsExp -> HsExp -> HsExp
HsApp HsExp
asProxy HsExp
declare
        where
          declare :: HsExp
declare = FilePath -> HsExp
uvar_ (FilePath -> FilePath
toDeclareName FilePath
fieldName)

          asProxy :: HsExp
asProxy = HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"asProxy")

      -- do let declare_fieldName0 = HsJSONPB.declareSchemaRef
      --    qualifiedFieldName0 <- declare_fieldName0 Proxy.Proxy
      --    let declare_fieldName1 = HsJSONPB.declareSchemaRef
      --    qualifiedFieldName1 <- declare_fieldName1 Proxy.Proxy
      --    ...
      --    let _ = pure MessageName <*> HsJSONPB.asProxy declare_fieldName0 <*> HsJSONPB.asProxy declare_fieldName1 <*> ...
      --    return (...)
  let expressionForMessage :: HsExp
expressionForMessage =
          [HsStmt] -> HsExp
HsDo ([HsStmt]
bindingStatements [HsStmt] -> [HsStmt] -> [HsStmt]
forall a. [a] -> [a] -> [a]
++ [HsStmt]
inferenceStatement [HsStmt] -> [HsStmt] -> [HsStmt]
forall a. [a] -> [a] -> [a]
++ [ HsStmt
returnStatement ])
        where
          bindingStatements :: [HsStmt]
bindingStatements = do
            (FilePath
fieldName, FilePath
qualifiedFieldName) <- [FilePath] -> [FilePath] -> [(FilePath, FilePath)]
forall a b. [a] -> [b] -> [(a, b)]
zip [FilePath]
fieldNames [FilePath]
qualifiedFieldNames

            let declareIdentifier :: HsName
declareIdentifier = FilePath -> HsName
HsIdent (FilePath -> FilePath
toDeclareName FilePath
fieldName)

            let stmt0 :: HsStmt
stmt0 = [HsDecl] -> HsStmt
HsLetStmt [ [HsMatch] -> HsDecl
HsFunBind
                                    [ SrcLoc -> HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
HsMatch SrcLoc
defaultSrcLoc HsName
declareIdentifier []
                                               (HsExp -> HsRhs
HsUnGuardedRhs (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"declareSchemaRef"))) []
                                    ]
                                  ]

            let stmt1 :: HsStmt
stmt1 = SrcLoc -> HsPat -> HsExp -> HsStmt
HsGenerator SrcLoc
defaultSrcLoc (HsName -> HsPat
HsPVar (FilePath -> HsName
HsIdent FilePath
qualifiedFieldName))
                                      (HsExp -> HsExp -> HsExp
HsApp (HsQName -> HsExp
HsVar (HsName -> HsQName
UnQual HsName
declareIdentifier))
                                             (HsQName -> HsExp
HsCon (FilePath -> HsQName
proxyName FilePath
"Proxy")))
            [ HsStmt
stmt0, HsStmt
stmt1]


          inferenceStatement :: [HsStmt]
inferenceStatement =
              if [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
fieldNames then [] else [ [HsDecl] -> HsStmt
HsLetStmt [ HsDecl
patternBind ] ]
            where
              arguments :: [HsExp]
arguments = (FilePath -> HsExp) -> [FilePath] -> [HsExp]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> HsExp
toArgument [FilePath]
fieldNames

              patternBind :: HsDecl
patternBind = SrcLoc -> HsPat -> HsRhs -> [HsDecl] -> HsDecl
HsPatBind SrcLoc
defaultSrcLoc HsPat
HsPWildCard
                                        (HsExp -> HsRhs
HsUnGuardedRhs (HsExp -> [HsExp] -> HsExp
applicativeApply HsExp
messageConstructor [HsExp]
arguments)) []

          returnStatement :: HsStmt
returnStatement = HsExp -> HsStmt
HsQualifier (HsExp -> HsExp -> HsExp
HsApp HsExp
returnE (HsExp -> HsExp
HsParen HsExp
namedSchema))

      -- do let declare_fieldName0 = HsJSONPB.declareSchemaRef
      --    let _ = pure ConstructorName0 <*> HsJSONPB.asProxy declare_fieldName0
      --    qualifiedFieldName0 <- declare_fieldName0 Proxy.Proxy
      --    let declare_fieldName1 = HsJSONPB.declareSchemaRef
      --    let _ = pure ConstructorName1 <*> HsJSONPB.asProxy declare_fieldName1
      --    qualifiedFieldName1 <- declare_fieldName1 Proxy.Proxy
      --    ...
      --    return (...)
  let expressionForOneOf :: [HsName] -> HsExp
expressionForOneOf [HsName]
constructors =
          [HsStmt] -> HsExp
HsDo ([HsStmt]
bindingStatements [HsStmt] -> [HsStmt] -> [HsStmt]
forall a. [a] -> [a] -> [a]
++ [ HsStmt
returnStatement ])
        where
          bindingStatements :: [HsStmt]
bindingStatements = do
            (FilePath
fieldName, FilePath
qualifiedFieldName, HsName
constructor)
                <- [FilePath]
-> [FilePath] -> [HsName] -> [(FilePath, FilePath, HsName)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [FilePath]
fieldNames [FilePath]
qualifiedFieldNames [HsName]
constructors

            let declareIdentifier :: HsName
declareIdentifier = FilePath -> HsName
HsIdent (FilePath -> FilePath
toDeclareName FilePath
fieldName)

            let stmt0 :: HsStmt
stmt0 = [HsDecl] -> HsStmt
HsLetStmt [ [HsMatch] -> HsDecl
HsFunBind
                                      [ SrcLoc -> HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
HsMatch SrcLoc
defaultSrcLoc HsName
declareIdentifier []
                                                 (HsExp -> HsRhs
HsUnGuardedRhs (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"declareSchemaRef"))) []
                                      ]
                                  ]
            let stmt1 :: HsStmt
stmt1 = SrcLoc -> HsPat -> HsExp -> HsStmt
HsGenerator SrcLoc
defaultSrcLoc (HsName -> HsPat
HsPVar (FilePath -> HsName
HsIdent FilePath
qualifiedFieldName))
                                      (HsExp -> HsExp -> HsExp
HsApp (HsQName -> HsExp
HsVar (HsName -> HsQName
UnQual HsName
declareIdentifier))
                                             (HsQName -> HsExp
HsCon (FilePath -> HsQName
proxyName FilePath
"Proxy")))
            let inferenceStatement :: [HsStmt]
inferenceStatement =
                    if [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
fieldNames then [] else [ [HsDecl] -> HsStmt
HsLetStmt [ HsDecl
patternBind ] ]
                  where
                    arguments :: [HsExp]
arguments = [ FilePath -> HsExp
toArgument FilePath
fieldName ]

                    patternBind :: HsDecl
patternBind = SrcLoc -> HsPat -> HsRhs -> [HsDecl] -> HsDecl
HsPatBind SrcLoc
defaultSrcLoc HsPat
HsPWildCard
                                              (HsExp -> HsRhs
HsUnGuardedRhs (HsExp -> [HsExp] -> HsExp
applicativeApply (HsQName -> HsExp
HsCon (HsName -> HsQName
UnQual HsName
constructor)) [HsExp]
arguments)) []

            [HsStmt
stmt0, HsStmt
stmt1] [HsStmt] -> [HsStmt] -> [HsStmt]
forall a. [a] -> [a] -> [a]
++ [HsStmt]
inferenceStatement


          returnStatement :: HsStmt
returnStatement = HsExp -> HsStmt
HsQualifier (HsExp -> HsExp -> HsExp
HsApp HsExp
returnE (HsExp -> HsExp
HsParen HsExp
namedSchema))

  let instanceDeclaration :: HsDecl
instanceDeclaration =
          HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ HsQName
className [ HsType
classArgument ] [ HsDecl
classDeclaration ]
        where
          className :: HsQName
className = FilePath -> HsQName
jsonpbName FilePath
"ToSchema"

          classArgument :: HsType
classArgument = HsQName -> HsType
HsTyCon (HsName -> HsQName
UnQual (FilePath -> HsName
HsIdent FilePath
messageName))

          classDeclaration :: HsDecl
classDeclaration = [HsMatch] -> HsDecl
HsFunBind [ HsMatch
match ]
            where
              match :: HsMatch
match = HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ HsName
matchName [ HsPat
HsPWildCard ] HsRhs
rightHandSide []
                where
                  expression :: HsExp
expression = case Maybe [HsName]
maybeConstructors of
                      Maybe [HsName]
Nothing           -> HsExp
expressionForMessage
                      Just [HsName]
constructors -> [HsName] -> HsExp
expressionForOneOf [HsName]
constructors

                  rightHandSide :: HsRhs
rightHandSide = HsExp -> HsRhs
HsUnGuardedRhs HsExp
expression

                  matchName :: HsName
matchName = FilePath -> HsName
HsIdent FilePath
"declareNamedSchema"

  HsDecl -> m HsDecl
forall (m :: * -> *) a. Monad m => a -> m a
return HsDecl
instanceDeclaration


-- ** Generate types and instances for .proto enums

dotProtoEnumD
    :: MonadError CompileError m
    => DotProtoIdentifier
    -> DotProtoIdentifier
    -> [DotProtoEnumPart]
    -> m [HsDecl]
dotProtoEnumD :: DotProtoIdentifier
-> DotProtoIdentifier -> [DotProtoEnumPart] -> m [HsDecl]
dotProtoEnumD DotProtoIdentifier
parentIdent DotProtoIdentifier
enumIdent [DotProtoEnumPart]
enumParts = do
  FilePath
enumName <- DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> DotProtoIdentifier -> m FilePath
qualifiedMessageName DotProtoIdentifier
parentIdent DotProtoIdentifier
enumIdent

  let enumeratorDecls :: [(DotProtoEnumValue, DotProtoIdentifier)]
enumeratorDecls =
        [ (DotProtoEnumValue
i, DotProtoIdentifier
conIdent) | DotProtoEnumField DotProtoIdentifier
conIdent DotProtoEnumValue
i [DotProtoOption]
_options <- [DotProtoEnumPart]
enumParts ]

  case [(DotProtoEnumValue, DotProtoIdentifier)]
enumeratorDecls of
    [] -> CompileError -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (CompileError -> m ()) -> CompileError -> m ()
forall a b. (a -> b) -> a -> b
$ FilePath -> CompileError
EmptyEnumeration FilePath
enumName
    (DotProtoEnumValue
i, DotProtoIdentifier
conIdent) : [(DotProtoEnumValue, DotProtoIdentifier)]
_
      | DotProtoEnumValue
i DotProtoEnumValue -> DotProtoEnumValue -> Bool
forall a. Eq a => a -> a -> Bool
== DotProtoEnumValue
0 -> () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
      | Bool
otherwise -> CompileError -> m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (CompileError -> m ()) -> CompileError -> m ()
forall a b. (a -> b) -> a -> b
$ FilePath -> DotProtoIdentifier -> DotProtoEnumValue -> CompileError
NonzeroFirstEnumeration FilePath
enumName DotProtoIdentifier
conIdent DotProtoEnumValue
i

  [(DotProtoEnumValue, FilePath)]
enumCons <- ((DotProtoEnumValue, FilePath)
 -> (DotProtoEnumValue, FilePath) -> Ordering)
-> [(DotProtoEnumValue, FilePath)]
-> [(DotProtoEnumValue, FilePath)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (((DotProtoEnumValue, FilePath) -> DotProtoEnumValue)
-> (DotProtoEnumValue, FilePath)
-> (DotProtoEnumValue, FilePath)
-> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (DotProtoEnumValue, FilePath) -> DotProtoEnumValue
forall a b. (a, b) -> a
fst) ([(DotProtoEnumValue, FilePath)]
 -> [(DotProtoEnumValue, FilePath)])
-> m [(DotProtoEnumValue, FilePath)]
-> m [(DotProtoEnumValue, FilePath)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((DotProtoEnumValue, DotProtoIdentifier)
 -> m (DotProtoEnumValue, FilePath))
-> [(DotProtoEnumValue, DotProtoIdentifier)]
-> m [(DotProtoEnumValue, FilePath)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((DotProtoIdentifier -> m FilePath)
-> (DotProtoEnumValue, DotProtoIdentifier)
-> m (DotProtoEnumValue, FilePath)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((FilePath -> FilePath) -> m FilePath -> m FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath -> FilePath -> FilePath
prefixedEnumFieldName FilePath
enumName) (m FilePath -> m FilePath)
-> (DotProtoIdentifier -> m FilePath)
-> DotProtoIdentifier
-> m FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> m FilePath
dpIdentUnqualName)) [(DotProtoEnumValue, DotProtoIdentifier)]
enumeratorDecls

  let enumConNames :: [FilePath]
enumConNames = ((DotProtoEnumValue, FilePath) -> FilePath)
-> [(DotProtoEnumValue, FilePath)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (DotProtoEnumValue, FilePath) -> FilePath
forall a b. (a, b) -> b
snd [(DotProtoEnumValue, FilePath)]
enumCons

      minBoundD :: [HsMatch]
minBoundD =
          [ HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"minBound")
                   []
                   (HsExp -> HsRhs
HsUnGuardedRhs (FilePath -> HsExp
uvar_ ([FilePath] -> FilePath
forall a. [a] -> a
head [FilePath]
enumConNames)))
                   []
          ]

      maxBoundD :: [HsMatch]
maxBoundD =
          [ HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"maxBound")
                   []
                   (HsExp -> HsRhs
HsUnGuardedRhs (FilePath -> HsExp
uvar_ ([FilePath] -> FilePath
forall a. [a] -> a
last [FilePath]
enumConNames)))
                   []
          ]

      compareD :: [HsMatch]
compareD =
          [ HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"compare")
                   [ FilePath -> HsPat
patVar FilePath
"x", FilePath -> HsPat
patVar FilePath
"y" ]
                   (HsExp -> HsRhs
HsUnGuardedRhs
                       (HsExp -> HsExp -> HsExp
HsApp
                           (HsExp -> HsExp -> HsExp
HsApp
                               (HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"compare"))
                               (HsExp -> HsExp
HsParen
                                   (HsExp -> HsExp -> HsExp
HsApp (HsQName -> HsExp
HsVar(FilePath -> HsQName
protobufName FilePath
"fromProtoEnum"))
                                          (FilePath -> HsExp
uvar_ FilePath
"x")
                                   )
                               )
                           )
                           (HsExp -> HsExp
HsParen
                               (HsExp -> HsExp -> HsExp
HsApp (HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"fromProtoEnum"))
                                      (FilePath -> HsExp
uvar_ FilePath
"y")
                               )
                           )
                       )
                   )
                   []
          ]

      fromProtoEnumD :: [HsMatch]
fromProtoEnumD =
          [ HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"fromProtoEnum") [ HsQName -> [HsPat] -> HsPat
HsPApp (FilePath -> HsQName
unqual_ FilePath
conName) [] ]
                   (HsExp -> HsRhs
HsUnGuardedRhs (DotProtoEnumValue -> HsExp
forall a. Integral a => a -> HsExp
intE DotProtoEnumValue
conIdx))
                   []
          | (DotProtoEnumValue
conIdx, FilePath
conName) <- [(DotProtoEnumValue, FilePath)]
enumCons
          ]

      toProtoEnumMayD :: [HsMatch]
toProtoEnumMayD =
          [ HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"toProtoEnumMay")
                   [ DotProtoEnumValue -> HsPat
forall a. Integral a => a -> HsPat
intP DotProtoEnumValue
conIdx ]
                   (HsExp -> HsRhs
HsUnGuardedRhs (HsExp -> HsExp -> HsExp
HsApp HsExp
justC (FilePath -> HsExp
uvar_ FilePath
conName)))
                   []
          | (DotProtoEnumValue
conIdx, FilePath
conName) <- [(DotProtoEnumValue, FilePath)]
enumCons ] [HsMatch] -> [HsMatch] -> [HsMatch]
forall a. [a] -> [a] -> [a]
++
          [ HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"toProtoEnumMay")
                   [ HsPat
HsPWildCard ]
                   (HsExp -> HsRhs
HsUnGuardedRhs HsExp
nothingC)
                   []
          ]

      parseJSONPBDecls :: [HsMatch]
      parseJSONPBDecls :: [HsMatch]
parseJSONPBDecls = (FilePath -> [HsMatch] -> [HsMatch])
-> [HsMatch] -> [FilePath] -> [HsMatch]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((:) (HsMatch -> [HsMatch] -> [HsMatch])
-> (FilePath -> HsMatch) -> FilePath -> [HsMatch] -> [HsMatch]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsMatch
matchConName) [HsMatch
mismatch] [FilePath]
enumConNames
        where
          matchConName :: FilePath -> HsMatch
matchConName FilePath
conName = HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"parseJSONPB") [FilePath -> HsPat
pat FilePath
conName]
                                        (HsExp -> HsRhs
HsUnGuardedRhs
                                           (HsExp -> HsExp -> HsExp
HsApp HsExp
pureE (FilePath -> HsExp
uvar_ FilePath
conName)))
                                        []

          pat :: FilePath -> HsPat
pat FilePath
nm = HsQName -> [HsPat] -> HsPat
HsPApp (FilePath -> HsQName
jsonpbName FilePath
"String") [ HsLiteral -> HsPat
HsPLit (FilePath -> HsLiteral
HsString (FilePath -> FilePath
tryStripEnumName FilePath
nm)) ]

          tryStripEnumName :: FilePath -> FilePath
tryStripEnumName = FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> Maybe FilePath -> FilePath)
-> (FilePath -> Maybe FilePath) -> FilePath -> FilePath
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FilePath -> FilePath -> Maybe FilePath
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix FilePath
enumName

          mismatch :: HsMatch
mismatch = HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"parseJSONPB") [FilePath -> HsPat
patVar FilePath
"v"]
                            (HsExp -> HsRhs
HsUnGuardedRhs
                                  (HsExp -> [HsExp] -> HsExp
apply (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"typeMismatch"))
                                    [ FilePath -> HsExp
str_ FilePath
enumName, FilePath -> HsExp
uvar_ FilePath
"v" ]))
                            []


      toJSONPBDecl :: HsMatch
toJSONPBDecl =
        HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"toJSONPB") [ FilePath -> HsPat
patVar FilePath
"x", HsPat
HsPWildCard ]
          (HsExp -> HsRhs
HsUnGuardedRhs
             (HsExp -> HsExp -> HsExp
HsApp (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"enumFieldString"))
                    (FilePath -> HsExp
uvar_ FilePath
"x")))
          []

      toEncodingPBDecl :: HsMatch
toEncodingPBDecl =
        HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
"toEncodingPB") [ FilePath -> HsPat
patVar FilePath
"x", HsPat
HsPWildCard ]
          (HsExp -> HsRhs
HsUnGuardedRhs
             (HsExp -> HsExp -> HsExp
HsApp (HsQName -> HsExp
HsVar (FilePath -> HsQName
jsonpbName FilePath
"enumFieldEncoding"))
                    (FilePath -> HsExp
uvar_ FilePath
"x")))
          []

  [HsDecl] -> m [HsDecl]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [ FilePath -> [HsConDecl] -> [HsQName] -> HsDecl
dataDecl_ FilePath
enumName
                   [ HsName -> [HsBangType] -> HsConDecl
conDecl_ (FilePath -> HsName
HsIdent FilePath
con) [] | FilePath
con <- [FilePath]
enumConNames ]
                   [HsQName]
defaultEnumDeriving
       , FilePath -> HsDecl
namedInstD FilePath
enumName
       , FilePath -> HsDecl
hasDefaultInstD FilePath
enumName
       , HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
haskellName FilePath
"Bounded") [ FilePath -> HsType
type_ FilePath
enumName ]
                   [ [HsMatch] -> HsDecl
HsFunBind [HsMatch]
minBoundD
                   , [HsMatch] -> HsDecl
HsFunBind [HsMatch]
maxBoundD
                   ]
       , HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
haskellName FilePath
"Ord") [ FilePath -> HsType
type_ FilePath
enumName ]
                   [ [HsMatch] -> HsDecl
HsFunBind [HsMatch]
compareD ]
       , HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
protobufName FilePath
"ProtoEnum") [ FilePath -> HsType
type_ FilePath
enumName ]
                   [ [HsMatch] -> HsDecl
HsFunBind [HsMatch]
toProtoEnumMayD
                   , [HsMatch] -> HsDecl
HsFunBind [HsMatch]
fromProtoEnumD
                   ]
       , HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
jsonpbName FilePath
"ToJSONPB") [ FilePath -> HsType
type_ FilePath
enumName ]
                   [ [HsMatch] -> HsDecl
HsFunBind [HsMatch
toJSONPBDecl]
                   , [HsMatch] -> HsDecl
HsFunBind [HsMatch
toEncodingPBDecl]
                   ]
       , HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
jsonpbName FilePath
"FromJSONPB") [ FilePath -> HsType
type_ FilePath
enumName ]
                   [ [HsMatch] -> HsDecl
HsFunBind [HsMatch]
parseJSONPBDecls ]
       -- Generate Aeson instances in terms of JSONPB instances
       , FilePath -> HsDecl
toJSONInstDecl FilePath
enumName
       , FilePath -> HsDecl
fromJSONInstDecl FilePath
enumName

#ifdef DHALL
       -- Generate Dhall instances
       , dhallInterpretInstDecl enumName
       , dhallInjectInstDecl enumName
#endif

       -- And the Finite instance, used to infer a Swagger ToSchema instance
       -- for this enumerated type.
       , HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ (FilePath -> HsQName
protobufName FilePath
"Finite") [ FilePath -> HsType
type_ FilePath
enumName ] []
       ]

-- ** Generate code for dot proto services

dotProtoServiceD
    :: MonadError CompileError m
    => DotProtoIdentifier
    -> TypeContext
    -> DotProtoIdentifier
    -> [DotProtoServicePart]
    -> m [HsDecl]
dotProtoServiceD :: DotProtoIdentifier
-> TypeContext
-> DotProtoIdentifier
-> [DotProtoServicePart]
-> m [HsDecl]
dotProtoServiceD DotProtoIdentifier
pkgIdent TypeContext
ctxt DotProtoIdentifier
serviceIdent [DotProtoServicePart]
service = do
     FilePath
serviceName <- FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> m FilePath
typeLikeName (FilePath -> m FilePath) -> m FilePath -> m FilePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> m FilePath
dpIdentUnqualName DotProtoIdentifier
serviceIdent
     FilePath
packageName <- DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> m FilePath
dpIdentQualName DotProtoIdentifier
pkgIdent

     let endpointPrefix :: FilePath
endpointPrefix = FilePath
"/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
packageName FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
serviceName FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"/"

     let serviceFieldD :: DotProtoServicePart
-> m [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
serviceFieldD (DotProtoServiceRPCMethod RPCMethod{[DotProtoOption]
Streaming
DotProtoIdentifier
rpcMethodOptions :: RPCMethod -> [DotProtoOption]
rpcMethodResponseStreaming :: RPCMethod -> Streaming
rpcMethodResponseType :: RPCMethod -> DotProtoIdentifier
rpcMethodRequestStreaming :: RPCMethod -> Streaming
rpcMethodRequestType :: RPCMethod -> DotProtoIdentifier
rpcMethodName :: RPCMethod -> DotProtoIdentifier
rpcMethodOptions :: [DotProtoOption]
rpcMethodResponseStreaming :: Streaming
rpcMethodResponseType :: DotProtoIdentifier
rpcMethodRequestStreaming :: Streaming
rpcMethodRequestType :: DotProtoIdentifier
rpcMethodName :: DotProtoIdentifier
..}) = do
           FilePath
fullName <- FilePath -> FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> FilePath -> m FilePath
prefixedMethodName FilePath
serviceName (FilePath -> m FilePath) -> m FilePath -> m FilePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DotProtoIdentifier -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoIdentifier -> m FilePath
dpIdentUnqualName DotProtoIdentifier
rpcMethodName

           FilePath
methodName <- case DotProtoIdentifier
rpcMethodName of
                           Single FilePath
nm -> FilePath -> m FilePath
forall (f :: * -> *) a. Applicative f => a -> f a
pure FilePath
nm
                           DotProtoIdentifier
_ -> DotProtoIdentifier -> m FilePath
forall (m :: * -> *) a.
MonadError CompileError m =>
DotProtoIdentifier -> m a
invalidMethodNameError DotProtoIdentifier
rpcMethodName

           HsType
requestTy  <- TypeContext -> DotProtoPrimType -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoPrimType -> m HsType
dpptToHsType TypeContext
ctxt (DotProtoIdentifier -> DotProtoPrimType
Named DotProtoIdentifier
rpcMethodRequestType)

           HsType
responseTy <- TypeContext -> DotProtoPrimType -> m HsType
forall (m :: * -> *).
MonadError CompileError m =>
TypeContext -> DotProtoPrimType -> m HsType
dpptToHsType TypeContext
ctxt (DotProtoIdentifier -> DotProtoPrimType
Named DotProtoIdentifier
rpcMethodResponseType)

           let streamingType :: HsType
streamingType =
                 case (Streaming
rpcMethodRequestStreaming, Streaming
rpcMethodResponseStreaming) of
                   (Streaming
Streaming, Streaming
Streaming)       -> HsType
biDiStreamingC
                   (Streaming
Streaming, Streaming
NonStreaming)    -> HsType
clientStreamingC
                   (Streaming
NonStreaming, Streaming
Streaming)    -> HsType
serverStreamingC
                   (Streaming
NonStreaming, Streaming
NonStreaming) -> HsType
normalC

           [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
-> m [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [ ( FilePath
endpointPrefix FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
methodName
                  , FilePath
fullName, Streaming
rpcMethodRequestStreaming, Streaming
rpcMethodResponseStreaming
                  , HsType -> HsBangType
HsUnBangedTy (HsType -> HsBangType) -> HsType -> HsBangType
forall a b. (a -> b) -> a -> b
$
                    HsType -> HsType -> HsType
HsTyFun (HsType -> [HsType] -> HsType
tyApp (HsName -> HsType
HsTyVar (FilePath -> HsName
HsIdent FilePath
"request"))
                                   [HsType
streamingType, HsType
requestTy, HsType
responseTy])
                            (HsType -> [HsType] -> HsType
tyApp HsType
ioT
                                   [HsType -> [HsType] -> HsType
tyApp (HsName -> HsType
HsTyVar (FilePath -> HsName
HsIdent FilePath
"response"))
                                          [HsType
streamingType, HsType
responseTy]
                                   ]
                            )
                  )
                ]

         serviceFieldD DotProtoServicePart
_ = [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
-> m [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []

     [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
fieldsD <- (DotProtoServicePart
 -> m [(FilePath, FilePath, Streaming, Streaming, HsBangType)])
-> [DotProtoServicePart]
-> m [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m, Monoid b, Semigroup b) =>
(a -> m b) -> t a -> m b
foldMapM DotProtoServicePart
-> m [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
forall (m :: * -> *).
MonadError CompileError m =>
DotProtoServicePart
-> m [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
serviceFieldD [DotProtoServicePart]
service

     FilePath
serverFuncName <- FilePath -> FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> FilePath -> m FilePath
prefixedFieldName FilePath
serviceName FilePath
"server"
     FilePath
clientFuncName <- FilePath -> FilePath -> m FilePath
forall (m :: * -> *).
MonadError CompileError m =>
FilePath -> FilePath -> m FilePath
prefixedFieldName FilePath
serviceName FilePath
"client"

     let conDecl :: HsConDecl
conDecl = HsName -> [([HsName], HsBangType)] -> HsConDecl
recDecl_ (FilePath -> HsName
HsIdent FilePath
serviceName)
                            [ ([FilePath -> HsName
HsIdent FilePath
hsName], HsBangType
ty) | (FilePath
_, FilePath
hsName, Streaming
_, Streaming
_, HsBangType
ty) <- [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
fieldsD ]

     let serverT :: HsType
serverT = HsType -> [HsType] -> HsType
tyApp (HsQName -> HsType
HsTyCon (FilePath -> HsQName
unqual_ FilePath
serviceName))
                         [ HsType
serverRequestT, HsType
serverResponseT ]

     let serviceServerTypeD :: HsDecl
serviceServerTypeD =
            SrcLoc -> [HsName] -> HsQualType -> HsDecl
HsTypeSig SrcLoc
defaultSrcLoc [ FilePath -> HsName
HsIdent FilePath
serverFuncName ]
                        (HsContext -> HsType -> HsQualType
HsQualType [] (HsType -> HsType -> HsType
HsTyFun HsType
serverT (HsType -> HsType -> HsType
HsTyFun HsType
serviceOptionsC HsType
ioActionT)))

     let serviceServerD :: HsDecl
serviceServerD = [HsMatch] -> HsDecl
HsFunBind [HsMatch
serverFuncD]
           where
             serverFuncD :: HsMatch
serverFuncD =
               HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
serverFuncName)
                      [ HsQName -> [HsPatField] -> HsPat
HsPRec (FilePath -> HsQName
unqual_ FilePath
serviceName)
                               [ HsQName -> HsPat -> HsPatField
HsPFieldPat (FilePath -> HsQName
unqual_ FilePath
methodName) (HsName -> HsPat
HsPVar (FilePath -> HsName
HsIdent FilePath
methodName))
                               | (FilePath
_, FilePath
methodName, Streaming
_, Streaming
_, HsBangType
_) <- [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
fieldsD
                               ]
                      , HsQName -> [HsPat] -> HsPat
HsPApp (FilePath -> HsQName
unqual_ FilePath
"ServiceOptions")
                               [ FilePath -> HsPat
patVar FilePath
"serverHost"
                               , FilePath -> HsPat
patVar FilePath
"serverPort"
                               , FilePath -> HsPat
patVar FilePath
"useCompression"
                               , FilePath -> HsPat
patVar FilePath
"userAgentPrefix"
                               , FilePath -> HsPat
patVar FilePath
"userAgentSuffix"
                               , FilePath -> HsPat
patVar FilePath
"initialMetadata"
                               , FilePath -> HsPat
patVar FilePath
"sslConfig"
                               , FilePath -> HsPat
patVar FilePath
"logger"
                               , FilePath -> HsPat
patVar FilePath
"serverMaxReceiveMessageLength"
                               , FilePath -> HsPat
patVar FilePath
"serverMaxMetadataSize"
                               ]
                      ]
                      (HsExp -> HsRhs
HsUnGuardedRhs (HsExp -> [HsExp] -> HsExp
apply HsExp
serverLoopE [ HsExp
serverOptsE ]))
                      []

             handlerE :: HsExp -> HsExp -> FilePath -> FilePath -> HsExp
handlerE HsExp
handlerC HsExp
adapterE FilePath
methodName FilePath
hsName =
                 HsExp -> [HsExp] -> HsExp
apply HsExp
handlerC [ HsExp -> [HsExp] -> HsExp
apply HsExp
methodNameC [ FilePath -> HsExp
str_ FilePath
methodName ]
                                , HsExp -> [HsExp] -> HsExp
apply HsExp
adapterE [ FilePath -> HsExp
uvar_ FilePath
hsName ]
                                ]

             update :: FilePath -> FilePath -> HsFieldUpdate
update FilePath
u FilePath
v = HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate (FilePath -> HsQName
unqual_ FilePath
u) (FilePath -> HsExp
uvar_ FilePath
v)

             serverOptsE :: HsExp
serverOptsE = HsExp -> [HsFieldUpdate] -> HsExp
HsRecUpdate HsExp
defaultOptionsE
                 [ HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate (FilePath -> HsQName
grpcName FilePath
"optNormalHandlers") (HsExp -> HsFieldUpdate) -> HsExp -> HsFieldUpdate
forall a b. (a -> b) -> a -> b
$
                       [HsExp] -> HsExp
HsList [ HsExp -> HsExp -> FilePath -> FilePath -> HsExp
handlerE HsExp
unaryHandlerC HsExp
convertServerHandlerE FilePath
endpointName FilePath
hsName
                              | (FilePath
endpointName, FilePath
hsName, Streaming
NonStreaming, Streaming
NonStreaming, HsBangType
_) <- [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
fieldsD
                              ]

                 , HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate (FilePath -> HsQName
grpcName FilePath
"optClientStreamHandlers") (HsExp -> HsFieldUpdate) -> HsExp -> HsFieldUpdate
forall a b. (a -> b) -> a -> b
$
                       [HsExp] -> HsExp
HsList [ HsExp -> HsExp -> FilePath -> FilePath -> HsExp
handlerE HsExp
clientStreamHandlerC HsExp
convertServerReaderHandlerE FilePath
endpointName FilePath
hsName
                              | (FilePath
endpointName, FilePath
hsName, Streaming
Streaming, Streaming
NonStreaming, HsBangType
_) <- [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
fieldsD
                              ]


                 , HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate (FilePath -> HsQName
grpcName FilePath
"optServerStreamHandlers") (HsExp -> HsFieldUpdate) -> HsExp -> HsFieldUpdate
forall a b. (a -> b) -> a -> b
$
                       [HsExp] -> HsExp
HsList [ HsExp -> HsExp -> FilePath -> FilePath -> HsExp
handlerE HsExp
serverStreamHandlerC HsExp
convertServerWriterHandlerE FilePath
endpointName FilePath
hsName
                              | (FilePath
endpointName, FilePath
hsName, Streaming
NonStreaming, Streaming
Streaming, HsBangType
_) <- [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
fieldsD
                              ]


                 , HsQName -> HsExp -> HsFieldUpdate
HsFieldUpdate (FilePath -> HsQName
grpcName FilePath
"optBiDiStreamHandlers") (HsExp -> HsFieldUpdate) -> HsExp -> HsFieldUpdate
forall a b. (a -> b) -> a -> b
$
                       [HsExp] -> HsExp
HsList [ HsExp -> HsExp -> FilePath -> FilePath -> HsExp
handlerE HsExp
biDiStreamHandlerC HsExp
convertServerRWHandlerE FilePath
endpointName FilePath
hsName
                              | (FilePath
endpointName, FilePath
hsName, Streaming
Streaming, Streaming
Streaming, HsBangType
_) <- [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
fieldsD
                              ]

                 , FilePath -> FilePath -> HsFieldUpdate
update FilePath
"optServerHost" FilePath
"serverHost"
                 , FilePath -> FilePath -> HsFieldUpdate
update FilePath
"optServerPort" FilePath
"serverPort"
                 , FilePath -> FilePath -> HsFieldUpdate
update FilePath
"optUseCompression" FilePath
"useCompression"
                 , FilePath -> FilePath -> HsFieldUpdate
update FilePath
"optUserAgentPrefix" FilePath
"userAgentPrefix"
                 , FilePath -> FilePath -> HsFieldUpdate
update FilePath
"optUserAgentSuffix" FilePath
"userAgentSuffix"
                 , FilePath -> FilePath -> HsFieldUpdate
update FilePath
"optInitialMetadata" FilePath
"initialMetadata"
                 , FilePath -> FilePath -> HsFieldUpdate
update FilePath
"optSSLConfig" FilePath
"sslConfig"
                 , FilePath -> FilePath -> HsFieldUpdate
update FilePath
"optLogger" FilePath
"logger"
                 , FilePath -> FilePath -> HsFieldUpdate
update FilePath
"optMaxReceiveMessageLength" FilePath
"serverMaxReceiveMessageLength"
                 , FilePath -> FilePath -> HsFieldUpdate
update FilePath
"optMaxMetadataSize" FilePath
"serverMaxMetadataSize"
                 ]

     let clientT :: HsType
clientT = HsType -> [HsType] -> HsType
tyApp (HsQName -> HsType
HsTyCon (FilePath -> HsQName
unqual_ FilePath
serviceName)) [ HsType
clientRequestT, HsType
clientResultT ]

     let serviceClientTypeD :: HsDecl
serviceClientTypeD =
             SrcLoc -> [HsName] -> HsQualType -> HsDecl
HsTypeSig SrcLoc
defaultSrcLoc [ FilePath -> HsName
HsIdent FilePath
clientFuncName ]
                       (HsContext -> HsType -> HsQualType
HsQualType [] (HsType -> HsType -> HsType
HsTyFun HsType
grpcClientT (HsType -> HsType -> HsType
HsTyApp HsType
ioT HsType
clientT)))

     let serviceClientD :: HsDecl
serviceClientD = [HsMatch] -> HsDecl
HsFunBind [ HsMatch
clientFuncD ]
            where
              clientFuncD :: HsMatch
clientFuncD = HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ (FilePath -> HsName
HsIdent FilePath
clientFuncName)
                                   [ HsName -> HsPat
HsPVar (FilePath -> HsName
HsIdent FilePath
"client") ]
                                   ( HsExp -> HsRhs
HsUnGuardedRhs HsExp
clientRecE ) []

              clientRecE :: HsExp
clientRecE = (HsExp -> HsExp -> HsExp) -> HsExp -> [HsExp] -> HsExp
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\HsExp
f -> HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp HsExp
f HsQOp
apOp)
                                 (HsExp -> [HsExp] -> HsExp
apply HsExp
pureE [ FilePath -> HsExp
uvar_ FilePath
serviceName ])
                                 [ HsExp -> HsExp
HsParen (HsExp -> HsExp) -> HsExp -> HsExp
forall a b. (a -> b) -> a -> b
$ HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp HsExp
clientRequestE' HsQOp
apOp (FilePath -> HsExp
registerClientMethodE FilePath
endpointName)
                                 | (FilePath
endpointName, FilePath
_, Streaming
_, Streaming
_, HsBangType
_) <- [(FilePath, FilePath, Streaming, Streaming, HsBangType)]
fieldsD
                                 ]

              clientRequestE' :: HsExp
clientRequestE' = HsExp -> [HsExp] -> HsExp
apply HsExp
pureE [ HsExp -> [HsExp] -> HsExp
apply HsExp
clientRequestE [ FilePath -> HsExp
uvar_ FilePath
"client" ] ]

              registerClientMethodE :: FilePath -> HsExp
registerClientMethodE FilePath
endpoint =
                HsExp -> [HsExp] -> HsExp
apply HsExp
clientRegisterMethodE [ FilePath -> HsExp
uvar_ FilePath
"client"
                                            , HsExp -> [HsExp] -> HsExp
apply HsExp
methodNameC [ FilePath -> HsExp
str_ FilePath
endpoint ]
                                            ]

     [HsDecl] -> m [HsDecl]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [ SrcLoc
-> HsContext
-> HsName
-> [HsName]
-> [HsConDecl]
-> [HsQName]
-> HsDecl
HsDataDecl SrcLoc
defaultSrcLoc  [] (FilePath -> HsName
HsIdent FilePath
serviceName)
                [ FilePath -> HsName
HsIdent FilePath
"request", FilePath -> HsName
HsIdent FilePath
"response" ]
                [ HsConDecl
conDecl ] [HsQName]
defaultServiceDeriving

          , HsDecl
serviceServerTypeD
          , HsDecl
serviceServerD

          , HsDecl
serviceClientTypeD
          , HsDecl
serviceClientD
          ]

--------------------------------------------------------------------------------

--
-- * Common Haskell expressions, constructors, and operators
--

dotProtoFieldC, primC, repeatedC, nestedRepeatedC, namedC, mapC,
  fieldNumberC, singleC, dotsC, pathC, nestedC, anonymousC, dotProtoOptionC,
  identifierC, stringLitC, intLitC, floatLitC, boolLitC, trueC, falseC,
  unaryHandlerC, clientStreamHandlerC, serverStreamHandlerC, biDiStreamHandlerC,
  methodNameC, nothingC, justC, forceEmitC, mconcatE, encodeMessageFieldE,
  fromStringE, decodeMessageFieldE, pureE, returnE, memptyE, msumE, atE, oneofE,
  fmapE, defaultOptionsE, serverLoopE, convertServerHandlerE,
  convertServerReaderHandlerE, convertServerWriterHandlerE,
  convertServerRWHandlerE, clientRegisterMethodE, clientRequestE :: HsExp

dotProtoFieldC :: HsExp
dotProtoFieldC       = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"DotProtoField")
primC :: HsExp
primC                = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"Prim")
repeatedC :: HsExp
repeatedC            = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"Repeated")
nestedRepeatedC :: HsExp
nestedRepeatedC      = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"NestedRepeated")
namedC :: HsExp
namedC               = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"Named")
mapC :: HsExp
mapC                 = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"Map")
fieldNumberC :: HsExp
fieldNumberC         = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"FieldNumber")
singleC :: HsExp
singleC              = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"Single")
pathC :: HsExp
pathC                = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"Path")
dotsC :: HsExp
dotsC                = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"Dots")
nestedC :: HsExp
nestedC              = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"Nested")
anonymousC :: HsExp
anonymousC           = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"Anonymous")
dotProtoOptionC :: HsExp
dotProtoOptionC      = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"DotProtoOption")
identifierC :: HsExp
identifierC          = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"Identifier")
stringLitC :: HsExp
stringLitC           = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"StringLit")
intLitC :: HsExp
intLitC              = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"IntLit")
floatLitC :: HsExp
floatLitC            = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"FloatLit")
boolLitC :: HsExp
boolLitC             = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"BoolLit")
forceEmitC :: HsExp
forceEmitC           = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"ForceEmit")
encodeMessageFieldE :: HsExp
encodeMessageFieldE  = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"encodeMessageField")
decodeMessageFieldE :: HsExp
decodeMessageFieldE  = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"decodeMessageField")
atE :: HsExp
atE                  = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"at")
oneofE :: HsExp
oneofE               = HsQName -> HsExp
HsVar (FilePath -> HsQName
protobufName FilePath
"oneof")

trueC :: HsExp
trueC                       = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"True")
falseC :: HsExp
falseC                      = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"False")
nothingC :: HsExp
nothingC                    = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"Nothing")
justC :: HsExp
justC                       = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"Just")
mconcatE :: HsExp
mconcatE                    = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"mconcat")
fromStringE :: HsExp
fromStringE                 = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"fromString")
pureE :: HsExp
pureE                       = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"pure")
returnE :: HsExp
returnE                     = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"return")
memptyE :: HsExp
memptyE                     = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"mempty")
msumE :: HsExp
msumE                       = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"msum")
fmapE :: HsExp
fmapE                       = HsQName -> HsExp
HsVar (FilePath -> HsQName
haskellName FilePath
"fmap")

unaryHandlerC :: HsExp
unaryHandlerC               = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"UnaryHandler")
clientStreamHandlerC :: HsExp
clientStreamHandlerC        = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"ClientStreamHandler")
serverStreamHandlerC :: HsExp
serverStreamHandlerC        = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"ServerStreamHandler")
biDiStreamHandlerC :: HsExp
biDiStreamHandlerC          = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"BiDiStreamHandler")
methodNameC :: HsExp
methodNameC                 = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"MethodName")
defaultOptionsE :: HsExp
defaultOptionsE             = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"defaultOptions")
serverLoopE :: HsExp
serverLoopE                 = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"serverLoop")
convertServerHandlerE :: HsExp
convertServerHandlerE       = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"convertGeneratedServerHandler")
convertServerReaderHandlerE :: HsExp
convertServerReaderHandlerE = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"convertGeneratedServerReaderHandler")
convertServerWriterHandlerE :: HsExp
convertServerWriterHandlerE = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"convertGeneratedServerWriterHandler")
convertServerRWHandlerE :: HsExp
convertServerRWHandlerE     = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"convertGeneratedServerRWHandler")
clientRegisterMethodE :: HsExp
clientRegisterMethodE       = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"clientRegisterMethod")
clientRequestE :: HsExp
clientRequestE              = HsQName -> HsExp
HsVar (FilePath -> HsQName
grpcName FilePath
"clientRequest")

biDiStreamingC, serverStreamingC, clientStreamingC, normalC, serviceOptionsC,
  ioActionT, serverRequestT, serverResponseT, clientRequestT, clientResultT,
  ioT, grpcClientT :: HsType
biDiStreamingC :: HsType
biDiStreamingC   = HsQName -> HsType
HsTyCon (Module -> HsName -> HsQName
Qual (FilePath -> Module
Module FilePath
"'HsGRPC") (FilePath -> HsName
HsIdent FilePath
"BiDiStreaming"))
serverStreamingC :: HsType
serverStreamingC = HsQName -> HsType
HsTyCon (Module -> HsName -> HsQName
Qual (FilePath -> Module
Module FilePath
"'HsGRPC") (FilePath -> HsName
HsIdent FilePath
"ServerStreaming"))
clientStreamingC :: HsType
clientStreamingC = HsQName -> HsType
HsTyCon (Module -> HsName -> HsQName
Qual (FilePath -> Module
Module FilePath
"'HsGRPC") (FilePath -> HsName
HsIdent FilePath
"ClientStreaming"))
normalC :: HsType
normalC          = HsQName -> HsType
HsTyCon (Module -> HsName -> HsQName
Qual (FilePath -> Module
Module FilePath
"'HsGRPC") (FilePath -> HsName
HsIdent FilePath
"Normal"))
serviceOptionsC :: HsType
serviceOptionsC  = HsQName -> HsType
HsTyCon (Module -> HsName -> HsQName
Qual (FilePath -> Module
Module FilePath
"HsGRPC") (FilePath -> HsName
HsIdent FilePath
"ServiceOptions"))
serverRequestT :: HsType
serverRequestT   = HsQName -> HsType
HsTyCon (FilePath -> HsQName
grpcName FilePath
"ServerRequest")
serverResponseT :: HsType
serverResponseT  = HsQName -> HsType
HsTyCon (FilePath -> HsQName
grpcName FilePath
"ServerResponse")
clientRequestT :: HsType
clientRequestT   = HsQName -> HsType
HsTyCon (FilePath -> HsQName
grpcName FilePath
"ClientRequest")
clientResultT :: HsType
clientResultT    = HsQName -> HsType
HsTyCon (FilePath -> HsQName
grpcName FilePath
"ClientResult")
grpcClientT :: HsType
grpcClientT      = HsQName -> HsType
HsTyCon (FilePath -> HsQName
grpcName FilePath
"Client")
ioActionT :: HsType
ioActionT        = HsType -> [HsType] -> HsType
tyApp HsType
ioT [ [HsType] -> HsType
HsTyTuple [] ]
ioT :: HsType
ioT              = HsQName -> HsType
HsTyCon (FilePath -> HsQName
haskellName FilePath
"IO")

apOp :: HsQOp
apOp :: HsQOp
apOp  = HsQName -> HsQOp
HsQVarOp (HsName -> HsQName
UnQual (FilePath -> HsName
HsSymbol FilePath
"<*>"))

fmapOp :: HsQOp
fmapOp :: HsQOp
fmapOp  = HsQName -> HsQOp
HsQVarOp (HsName -> HsQName
UnQual (FilePath -> HsName
HsSymbol FilePath
"<$>"))

composeOp :: HsQOp
composeOp :: HsQOp
composeOp = HsQName -> HsQOp
HsQVarOp (Module -> HsName -> HsQName
Qual Module
haskellNS (FilePath -> HsName
HsSymbol FilePath
"."))

bindOp :: HsQOp
bindOp :: HsQOp
bindOp = HsQName -> HsQOp
HsQVarOp (Module -> HsName -> HsQName
Qual Module
haskellNS (FilePath -> HsName
HsSymbol FilePath
">>="))

altOp :: HsQOp
altOp :: HsQOp
altOp = HsQName -> HsQOp
HsQVarOp (HsName -> HsQName
UnQual (FilePath -> HsName
HsSymbol FilePath
"<|>"))

toJSONPBOp :: HsQOp
toJSONPBOp :: HsQOp
toJSONPBOp = HsQName -> HsQOp
HsQVarOp (HsName -> HsQName
UnQual (FilePath -> HsName
HsSymbol FilePath
".="))

parseJSONPBOp :: HsQOp
parseJSONPBOp :: HsQOp
parseJSONPBOp = HsQName -> HsQOp
HsQVarOp (HsName -> HsQName
UnQual (FilePath -> HsName
HsSymbol FilePath
".:"))

neConsOp :: HsQOp
neConsOp :: HsQOp
neConsOp = HsQName -> HsQOp
HsQVarOp (Module -> HsName -> HsQName
Qual Module
haskellNS (FilePath -> HsName
HsSymbol FilePath
":|"))

intE :: Integral a => a -> HsExp
intE :: a -> HsExp
intE a
x = (if a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 then HsExp -> HsExp
HsParen else HsExp -> HsExp
forall a. a -> a
id) (HsExp -> HsExp) -> (a -> HsExp) -> a -> HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsLiteral -> HsExp
HsLit (HsLiteral -> HsExp) -> (a -> HsLiteral) -> a -> HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> HsLiteral
HsInt (Integer -> HsLiteral) -> (a -> Integer) -> a -> HsLiteral
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> HsExp) -> a -> HsExp
forall a b. (a -> b) -> a -> b
$ a
x

intP :: Integral a => a -> HsPat
intP :: a -> HsPat
intP a
x = (if a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 then HsPat -> HsPat
HsPParen else HsPat -> HsPat
forall a. a -> a
id) (HsPat -> HsPat) -> (a -> HsPat) -> a -> HsPat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsLiteral -> HsPat
HsPLit (HsLiteral -> HsPat) -> (a -> HsLiteral) -> a -> HsPat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> HsLiteral
HsInt (Integer -> HsLiteral) -> (a -> Integer) -> a -> HsLiteral
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> HsPat) -> a -> HsPat
forall a b. (a -> b) -> a -> b
$ a
x

-- ** Expressions for protobuf-wire types

forceEmitE :: HsExp -> HsExp
forceEmitE :: HsExp -> HsExp
forceEmitE = HsExp -> HsExp
HsParen (HsExp -> HsExp) -> (HsExp -> HsExp) -> HsExp -> HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsExp -> HsExp -> HsExp
HsApp HsExp
forceEmitC

fieldNumberE :: FieldNumber -> HsExp
fieldNumberE :: FieldNumber -> HsExp
fieldNumberE = HsExp -> HsExp
HsParen (HsExp -> HsExp) -> (FieldNumber -> HsExp) -> FieldNumber -> HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsExp -> HsExp -> HsExp
HsApp HsExp
fieldNumberC (HsExp -> HsExp) -> (FieldNumber -> HsExp) -> FieldNumber -> HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> HsExp
forall a. Integral a => a -> HsExp
intE (Word64 -> HsExp)
-> (FieldNumber -> Word64) -> FieldNumber -> HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldNumber -> Word64
getFieldNumber

dpIdentE :: DotProtoIdentifier -> HsExp
dpIdentE :: DotProtoIdentifier -> HsExp
dpIdentE (Single FilePath
n)       = HsExp -> [HsExp] -> HsExp
apply HsExp
singleC [ FilePath -> HsExp
str_ FilePath
n ]
dpIdentE (Dots (Path (FilePath
n NE.:| [FilePath]
ns)))
  = HsExp -> [HsExp] -> HsExp
apply HsExp
dotsC [ HsExp -> [HsExp] -> HsExp
apply HsExp
pathC [ HsExp -> HsExp
HsParen (HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp (FilePath -> HsExp
str_ FilePath
n) HsQOp
neConsOp ([HsExp] -> HsExp
HsList ((FilePath -> HsExp) -> [FilePath] -> [HsExp]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> HsExp
str_ [FilePath]
ns))) ] ]
dpIdentE (Qualified DotProtoIdentifier
a DotProtoIdentifier
b)  = HsExp -> [HsExp] -> HsExp
apply HsExp
nestedC [ DotProtoIdentifier -> HsExp
dpIdentE DotProtoIdentifier
a, DotProtoIdentifier -> HsExp
dpIdentE DotProtoIdentifier
b ]
dpIdentE DotProtoIdentifier
Anonymous        = HsExp
anonymousC

dpValueE :: DotProtoValue -> HsExp
dpValueE :: DotProtoValue -> HsExp
dpValueE (Identifier DotProtoIdentifier
nm) = HsExp -> [HsExp] -> HsExp
apply HsExp
identifierC [ DotProtoIdentifier -> HsExp
dpIdentE DotProtoIdentifier
nm ]
dpValueE (StringLit FilePath
s)   = HsExp -> [HsExp] -> HsExp
apply HsExp
stringLitC  [ FilePath -> HsExp
str_ FilePath
s ]
dpValueE (IntLit Int
i)      = HsExp -> [HsExp] -> HsExp
apply HsExp
intLitC     [ HsLiteral -> HsExp
HsLit (Integer -> HsLiteral
HsInt (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i)) ]
dpValueE (FloatLit Double
f)    = HsExp -> [HsExp] -> HsExp
apply HsExp
floatLitC   [ HsLiteral -> HsExp
HsLit (Rational -> HsLiteral
HsFrac (Double -> Rational
forall a. Real a => a -> Rational
toRational Double
f)) ]
dpValueE (BoolLit Bool
True)  = HsExp -> [HsExp] -> HsExp
apply HsExp
boolLitC    [ HsExp
trueC ]
dpValueE (BoolLit Bool
False) = HsExp -> [HsExp] -> HsExp
apply HsExp
boolLitC    [ HsExp
falseC ]

optionE :: DotProtoOption -> HsExp
optionE :: DotProtoOption -> HsExp
optionE (DotProtoOption DotProtoIdentifier
name DotProtoValue
value) =
  HsExp -> [HsExp] -> HsExp
apply HsExp
dotProtoOptionC [ DotProtoIdentifier -> HsExp
dpIdentE DotProtoIdentifier
name, DotProtoValue -> HsExp
dpValueE DotProtoValue
value ]

-- | Translate a dot proto type to its Haskell AST type
dpTypeE :: DotProtoType -> HsExp
dpTypeE :: DotProtoType -> HsExp
dpTypeE (Prim DotProtoPrimType
p)           = HsExp -> [HsExp] -> HsExp
apply HsExp
primC           [ DotProtoPrimType -> HsExp
dpPrimTypeE DotProtoPrimType
p ]
dpTypeE (Repeated DotProtoPrimType
p)       = HsExp -> [HsExp] -> HsExp
apply HsExp
repeatedC       [ DotProtoPrimType -> HsExp
dpPrimTypeE DotProtoPrimType
p ]
dpTypeE (NestedRepeated DotProtoPrimType
p) = HsExp -> [HsExp] -> HsExp
apply HsExp
nestedRepeatedC [ DotProtoPrimType -> HsExp
dpPrimTypeE DotProtoPrimType
p ]
dpTypeE (Map DotProtoPrimType
k DotProtoPrimType
v)          = HsExp -> [HsExp] -> HsExp
apply HsExp
mapC            [ DotProtoPrimType -> HsExp
dpPrimTypeE DotProtoPrimType
k, DotProtoPrimType -> HsExp
dpPrimTypeE DotProtoPrimType
v]


-- | Translate a dot proto primitive type to a Haskell AST primitive type.
dpPrimTypeE :: DotProtoPrimType -> HsExp
dpPrimTypeE :: DotProtoPrimType -> HsExp
dpPrimTypeE DotProtoPrimType
ty =
    let wrap :: FilePath -> HsExp
wrap = HsQName -> HsExp
HsVar (HsQName -> HsExp) -> (FilePath -> HsQName) -> FilePath -> HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsQName
protobufName in
    case DotProtoPrimType
ty of
        Named DotProtoIdentifier
n  -> HsExp -> [HsExp] -> HsExp
apply HsExp
namedC [ DotProtoIdentifier -> HsExp
dpIdentE DotProtoIdentifier
n ]
        DotProtoPrimType
Int32    -> FilePath -> HsExp
wrap FilePath
"Int32"
        DotProtoPrimType
Int64    -> FilePath -> HsExp
wrap FilePath
"Int64"
        DotProtoPrimType
SInt32   -> FilePath -> HsExp
wrap FilePath
"SInt32"
        DotProtoPrimType
SInt64   -> FilePath -> HsExp
wrap FilePath
"SInt64"
        DotProtoPrimType
UInt32   -> FilePath -> HsExp
wrap FilePath
"UInt32"
        DotProtoPrimType
UInt64   -> FilePath -> HsExp
wrap FilePath
"UInt64"
        DotProtoPrimType
Fixed32  -> FilePath -> HsExp
wrap FilePath
"Fixed32"
        DotProtoPrimType
Fixed64  -> FilePath -> HsExp
wrap FilePath
"Fixed64"
        DotProtoPrimType
SFixed32 -> FilePath -> HsExp
wrap FilePath
"SFixed32"
        DotProtoPrimType
SFixed64 -> FilePath -> HsExp
wrap FilePath
"SFixed64"
        DotProtoPrimType
String   -> FilePath -> HsExp
wrap FilePath
"String"
        DotProtoPrimType
Bytes    -> FilePath -> HsExp
wrap FilePath
"Bytes"
        DotProtoPrimType
Bool     -> FilePath -> HsExp
wrap FilePath
"Bool"
        DotProtoPrimType
Float    -> FilePath -> HsExp
wrap FilePath
"Float"
        DotProtoPrimType
Double   -> FilePath -> HsExp
wrap FilePath
"Double"

defaultImports :: Bool -> [HsImportDecl]
defaultImports :: Bool -> [HsImportDecl]
defaultImports Bool
usesGrpc =
    [ Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Prelude")               (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Proto3.Suite.Class")    (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
protobufNS (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
#ifdef DHALL
    , importDecl_ (m "Proto3.Suite.DhallPB")  & qualified (m hsDhallPB) & everything
#endif
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Proto3.Suite.DotProto") (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
protobufNS (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Proto3.Suite.JSONPB")   (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
jsonpbNS   (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Proto3.Suite.JSONPB")   (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec]) -> HsImportDecl
forall a. (Bool -> Maybe Module -> a) -> a
unqualified          (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& [HsImportSpec]
-> (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a.
[HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
selecting  [FilePath -> HsImportSpec
sFilePath
".=", FilePath -> HsImportSpec
sFilePath
".:"]
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Proto3.Suite.Types")    (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
protobufNS (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Proto3.Wire")           (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
protobufNS (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Control.Applicative")   (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Control.Applicative")   (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec]) -> HsImportDecl
forall a. (Bool -> Maybe Module -> a) -> a
unqualified          (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& [HsImportSpec]
-> (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a.
[HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
selecting  [FilePath -> HsImportSpec
sFilePath
"<*>", FilePath -> HsImportSpec
sFilePath
"<|>", FilePath -> HsImportSpec
sFilePath
"<$>"]
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Control.DeepSeq")       (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Control.Monad")         (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Data.ByteString")       (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Data.Coerce")           (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Data.Int")              (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& [HsImportSpec]
-> (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a.
[HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
selecting  [FilePath -> HsImportSpec
iFilePath
"Int16", FilePath -> HsImportSpec
iFilePath
"Int32", FilePath -> HsImportSpec
iFilePath
"Int64"]
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Data.List.NonEmpty")    (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& [HsImportSpec]
-> (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a.
[HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
selecting  [HsName -> HsImportSpec
HsIThingAll (FilePath -> HsName
HsIdent FilePath
"NonEmpty")]
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Data.Map")              (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& [HsImportSpec]
-> (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a.
[HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
selecting  [FilePath -> HsImportSpec
iFilePath
"Map", FilePath -> HsImportSpec
iFilePath
"mapKeysMonotonic"]
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Data.Proxy")            (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
proxyNS    (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Data.String")           (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& [HsImportSpec]
-> (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a.
[HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
selecting  [FilePath -> HsImportSpec
iFilePath
"fromString"]
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Data.Text.Lazy")        (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& [HsImportSpec]
-> (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a.
[HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
selecting  [FilePath -> HsImportSpec
iFilePath
"Text"]
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Data.Vector")           (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& [HsImportSpec]
-> (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a.
[HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
selecting  [FilePath -> HsImportSpec
iFilePath
"Vector"]
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Data.Word")             (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& [HsImportSpec]
-> (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a.
[HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
selecting  [FilePath -> HsImportSpec
iFilePath
"Word16", FilePath -> HsImportSpec
iFilePath
"Word32", FilePath -> HsImportSpec
iFilePath
"Word64"]
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"GHC.Enum")              (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"GHC.Generics")          (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Unsafe.Coerce")         (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
haskellNS  (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    ]
    [HsImportDecl] -> [HsImportDecl] -> [HsImportDecl]
forall a. Semigroup a => a -> a -> a
<>
    (if Bool -> Bool
not Bool
usesGrpc then [] else
    [ Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Network.GRPC.HighLevel.Generated")           (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
alias Module
grpcNS (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Network.GRPC.HighLevel.Client")              (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
alias Module
grpcNS (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a. (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Network.GRPC.HighLevel.Server")              (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
alias Module
grpcNS (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& [HsImportSpec]
-> (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a.
[HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
hiding    [FilePath -> HsImportSpec
iFilePath
"serverLoop"]
    , Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ (FilePath -> Module
m FilePath
"Network.GRPC.HighLevel.Server.Unregistered") (Bool
 -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Bool
     -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
    -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& Module
-> (Bool
    -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
forall a. Module -> (Bool -> Maybe Module -> a) -> a
alias Module
grpcNS (Maybe (Bool, [HsImportSpec]) -> HsImportDecl)
-> ((Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl)
-> HsImportDecl
forall a b. a -> (a -> b) -> b
& [HsImportSpec]
-> (Maybe (Bool, [HsImportSpec]) -> HsImportDecl) -> HsImportDecl
forall a.
[HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
selecting [FilePath -> HsImportSpec
iFilePath
"serverLoop"]
    ])
  where
    m :: FilePath -> Module
m = FilePath -> Module
Module
    i :: FilePath -> HsImportSpec
i = HsName -> HsImportSpec
HsIVar (HsName -> HsImportSpec)
-> (FilePath -> HsName) -> FilePath -> HsImportSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsName
HsIdent
    s :: FilePath -> HsImportSpec
s = HsName -> HsImportSpec
HsIVar (HsName -> HsImportSpec)
-> (FilePath -> HsName) -> FilePath -> HsImportSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsName
HsSymbol

    grpcNS :: Module
grpcNS                    = FilePath -> Module
m FilePath
"HsGRPC"
    jsonpbNS :: Module
jsonpbNS                  = FilePath -> Module
m FilePath
"HsJSONPB"
    protobufNS :: Module
protobufNS                = FilePath -> Module
m FilePath
"HsProtobuf"
    proxyNS :: Module
proxyNS                   = FilePath -> Module
m FilePath
"Proxy"

    -- staged constructors for importDecl
    qualified :: Module -> (Bool -> Maybe Module -> a)  -> a
    qualified :: Module -> (Bool -> Maybe Module -> a) -> a
qualified Module
m' Bool -> Maybe Module -> a
f = Bool -> Maybe Module -> a
f Bool
True (Module -> Maybe Module
forall a. a -> Maybe a
Just Module
m')

    unqualified :: (Bool -> Maybe Module -> a) -> a
    unqualified :: (Bool -> Maybe Module -> a) -> a
unqualified Bool -> Maybe Module -> a
f = Bool -> Maybe Module -> a
f Bool
False Maybe Module
forall a. Maybe a
Nothing

    -- import unqualified AND also under a namespace
    alias :: Module -> (Bool -> Maybe Module -> a) -> a
    alias :: Module -> (Bool -> Maybe Module -> a) -> a
alias Module
m' Bool -> Maybe Module -> a
f = Bool -> Maybe Module -> a
f Bool
False (Module -> Maybe Module
forall a. a -> Maybe a
Just Module
m')

    selecting :: [HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
    selecting :: [HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
selecting [HsImportSpec]
is Maybe (Bool, [HsImportSpec]) -> a
f = Maybe (Bool, [HsImportSpec]) -> a
f ((Bool, [HsImportSpec]) -> Maybe (Bool, [HsImportSpec])
forall a. a -> Maybe a
Just (Bool
False, [HsImportSpec]
is))

    hiding :: [HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
    hiding :: [HsImportSpec] -> (Maybe (Bool, [HsImportSpec]) -> a) -> a
hiding [HsImportSpec]
is Maybe (Bool, [HsImportSpec]) -> a
f =  Maybe (Bool, [HsImportSpec]) -> a
f ((Bool, [HsImportSpec]) -> Maybe (Bool, [HsImportSpec])
forall a. a -> Maybe a
Just (Bool
True, [HsImportSpec]
is))

    everything :: (Maybe (Bool, [HsImportSpec]) -> a) -> a
    everything :: (Maybe (Bool, [HsImportSpec]) -> a) -> a
everything Maybe (Bool, [HsImportSpec]) -> a
f = Maybe (Bool, [HsImportSpec]) -> a
f Maybe (Bool, [HsImportSpec])
forall a. Maybe a
Nothing

haskellNS :: Module
haskellNS :: Module
haskellNS = FilePath -> Module
Module FilePath
"Hs"

defaultMessageDeriving :: [HsQName]
defaultMessageDeriving :: [HsQName]
defaultMessageDeriving = (FilePath -> HsQName) -> [FilePath] -> [HsQName]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> HsQName
haskellName [ FilePath
"Show", FilePath
"Eq", FilePath
"Ord", FilePath
"Generic", FilePath
"NFData" ]

defaultEnumDeriving :: [HsQName]
defaultEnumDeriving :: [HsQName]
defaultEnumDeriving = (FilePath -> HsQName) -> [FilePath] -> [HsQName]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> HsQName
haskellName [ FilePath
"Show", FilePath
"Eq", FilePath
"Generic", FilePath
"NFData" ]

defaultServiceDeriving :: [HsQName]
defaultServiceDeriving :: [HsQName]
defaultServiceDeriving = (FilePath -> HsQName) -> [FilePath] -> [HsQName]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> HsQName
haskellName [ FilePath
"Generic" ]

--------------------------------------------------------------------------------
--
-- * Wrappers around haskell-src-exts constructors
--

apply :: HsExp -> [HsExp] -> HsExp
apply :: HsExp -> [HsExp] -> HsExp
apply HsExp
f = HsExp -> HsExp
HsParen (HsExp -> HsExp) -> ([HsExp] -> HsExp) -> [HsExp] -> HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HsExp -> HsExp -> HsExp) -> HsExp -> [HsExp] -> HsExp
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl HsExp -> HsExp -> HsExp
HsApp HsExp
f

applicativeApply :: HsExp -> [HsExp] -> HsExp
applicativeApply :: HsExp -> [HsExp] -> HsExp
applicativeApply HsExp
f = (HsExp -> HsExp -> HsExp) -> HsExp -> [HsExp] -> HsExp
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl HsExp -> HsExp -> HsExp
snoc HsExp
nil
  where
    nil :: HsExp
nil = HsExp -> HsExp -> HsExp
HsApp HsExp
pureE HsExp
f

    snoc :: HsExp -> HsExp -> HsExp
snoc HsExp
g HsExp
x = HsExp -> HsQOp -> HsExp -> HsExp
HsInfixApp HsExp
g HsQOp
apOp HsExp
x

tyApp :: HsType -> [HsType] -> HsType
tyApp :: HsType -> [HsType] -> HsType
tyApp = (HsType -> HsType -> HsType) -> HsType -> [HsType] -> HsType
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl HsType -> HsType -> HsType
HsTyApp

module_ :: Module -> Maybe [HsExportSpec] -> [HsImportDecl] -> [HsDecl] -> HsModule
module_ :: Module
-> Maybe [HsExportSpec] -> [HsImportDecl] -> [HsDecl] -> HsModule
module_ = SrcLoc
-> Module
-> Maybe [HsExportSpec]
-> [HsImportDecl]
-> [HsDecl]
-> HsModule
HsModule SrcLoc
defaultSrcLoc

importDecl_ :: Module -> Bool -> Maybe Module -> Maybe (Bool, [HsImportSpec]) -> HsImportDecl
importDecl_ :: Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
importDecl_ = SrcLoc
-> Module
-> Bool
-> Maybe Module
-> Maybe (Bool, [HsImportSpec])
-> HsImportDecl
HsImportDecl SrcLoc
defaultSrcLoc

dataDecl_ :: String -> [HsConDecl] -> [HsQName] -> HsDecl
dataDecl_ :: FilePath -> [HsConDecl] -> [HsQName] -> HsDecl
dataDecl_ FilePath
messageName [constructor :: HsConDecl
constructor@(HsRecDecl SrcLoc
_ HsName
_ [([HsName], HsBangType)
_])] =
  SrcLoc
-> HsContext
-> HsName
-> [HsName]
-> HsConDecl
-> [HsQName]
-> HsDecl
HsNewTypeDecl SrcLoc
defaultSrcLoc [] (FilePath -> HsName
HsIdent FilePath
messageName) [] HsConDecl
constructor
dataDecl_ FilePath
messageName [HsConDecl]
constructors =
  SrcLoc
-> HsContext
-> HsName
-> [HsName]
-> [HsConDecl]
-> [HsQName]
-> HsDecl
HsDataDecl SrcLoc
defaultSrcLoc [] (FilePath -> HsName
HsIdent FilePath
messageName) [] [HsConDecl]
constructors

recDecl_ :: HsName -> [([HsName], HsBangType)] -> HsConDecl
recDecl_ :: HsName -> [([HsName], HsBangType)] -> HsConDecl
recDecl_ = SrcLoc -> HsName -> [([HsName], HsBangType)] -> HsConDecl
HsRecDecl SrcLoc
defaultSrcLoc

conDecl_ :: HsName -> [HsBangType] -> HsConDecl
conDecl_ :: HsName -> [HsBangType] -> HsConDecl
conDecl_ = SrcLoc -> HsName -> [HsBangType] -> HsConDecl
HsConDecl SrcLoc
defaultSrcLoc

instDecl_ :: HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ :: HsQName -> [HsType] -> [HsDecl] -> HsDecl
instDecl_ = SrcLoc -> HsContext -> HsQName -> [HsType] -> [HsDecl] -> HsDecl
HsInstDecl SrcLoc
defaultSrcLoc []

match_ :: HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ :: HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
match_ = SrcLoc -> HsName -> [HsPat] -> HsRhs -> [HsDecl] -> HsMatch
HsMatch SrcLoc
defaultSrcLoc

unqual_ :: String -> HsQName
unqual_ :: FilePath -> HsQName
unqual_ = HsName -> HsQName
UnQual (HsName -> HsQName) -> (FilePath -> HsName) -> FilePath -> HsQName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsName
HsIdent

uvar_ :: String -> HsExp
uvar_ :: FilePath -> HsExp
uvar_ = HsQName -> HsExp
HsVar (HsQName -> HsExp) -> (FilePath -> HsQName) -> FilePath -> HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsQName
unqual_

protobufType_, primType_, protobufWrapperType_ :: String -> HsType
protobufType_ :: FilePath -> HsType
protobufType_ = HsQName -> HsType
HsTyCon (HsQName -> HsType) -> (FilePath -> HsQName) -> FilePath -> HsType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsQName
protobufName
primType_ :: FilePath -> HsType
primType_ = HsQName -> HsType
HsTyCon (HsQName -> HsType) -> (FilePath -> HsQName) -> FilePath -> HsType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsQName
haskellName
protobufWrapperType_ :: FilePath -> HsType
protobufWrapperType_ = HsQName -> HsType
HsTyCon (HsQName -> HsType) -> (FilePath -> HsQName) -> FilePath -> HsType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsQName
protobufWrapperName

type_ :: String -> HsType
type_ :: FilePath -> HsType
type_ = HsQName -> HsType
HsTyCon (HsQName -> HsType) -> (FilePath -> HsQName) -> FilePath -> HsType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsQName
unqual_

patVar :: String -> HsPat
patVar :: FilePath -> HsPat
patVar =  HsName -> HsPat
HsPVar (HsName -> HsPat) -> (FilePath -> HsName) -> FilePath -> HsPat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsName
HsIdent

alt_ :: HsPat -> HsGuardedAlts -> [HsDecl] -> HsAlt
alt_ :: HsPat -> HsGuardedAlts -> [HsDecl] -> HsAlt
alt_ = SrcLoc -> HsPat -> HsGuardedAlts -> [HsDecl] -> HsAlt
HsAlt SrcLoc
defaultSrcLoc

str_ :: String -> HsExp
str_ :: FilePath -> HsExp
str_ = HsLiteral -> HsExp
HsLit (HsLiteral -> HsExp)
-> (FilePath -> HsLiteral) -> FilePath -> HsExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> HsLiteral
HsString

-- | For some reason, haskell-src-exts needs this 'SrcLoc' parameter
--   for some data constructors. Its value does not affect
--   pretty-printed output
defaultSrcLoc :: SrcLoc
defaultSrcLoc :: SrcLoc
defaultSrcLoc = FilePath -> Int -> Int -> SrcLoc
SrcLoc FilePath
"<generated>" Int
0 Int
0

__nowarn_unused :: a
__nowarn_unused :: a
__nowarn_unused = OneofSubfield -> DotProtoType
subfieldType (OneofSubfield -> DotProtoType)
-> (OneofSubfield -> [DotProtoOption]) -> Any
forall a. HasCallStack => a
`undefined` OneofSubfield -> [DotProtoOption]
subfieldOptions Any -> (OneofField -> FilePath) -> a
forall a. HasCallStack => a
`undefined` OneofField -> FilePath
oneofType