-- Copyright (c) Microsoft. All rights reserved. -- Licensed under the MIT license. See LICENSE file in the project root for full license information. {-# LANGUAGE QuasiQuotes, OverloadedStrings, RecordWildCards #-} module Language.Bond.Codegen.Cpp.Comm_h (comm_h) where import System.FilePath import Data.Monoid import Prelude import qualified Data.Text.Lazy as L import Data.Text.Lazy.Builder import Text.Shakespeare.Text import Language.Bond.Util import Language.Bond.Syntax.Types import Language.Bond.Syntax.Util import Language.Bond.Codegen.Util import Language.Bond.Codegen.TypeMapping import qualified Language.Bond.Codegen.Cpp.Util as CPP -- | Codegen template for generating /base_name/_comm.h containing declarations of -- of service interface and proxy. comm_h :: Maybe String -> MappingContext -> String -> [Import] -> [Declaration] -> (String, L.Text) comm_h export_attribute cpp file imports declarations = ("_comm.h", [lt| #pragma once #include #include "#{file}_types.h" #{newlineSep 0 includeImport imports} #{CPP.openNamespace cpp} #{doubleLineSep 1 comm declarations} #{CPP.closeNamespace cpp} |]) where includeImport (Import path) = [lt|#include "#{dropExtension path}_comm.h"|] cppType = getTypeName cpp request mt = request' (payload mt) where payload = maybe "void" cppType request' params = [lt|::bond::comm::payload<#{padLeft}#{params}>|] where paramsText = toLazyText params padLeft = if L.head paramsText == ':' then [lt| |] else mempty response mt = response' (payload mt) where payload = maybe "void" cppType response' params = [lt|::bond::comm::message<#{padLeft}#{params}>|] where paramsText = toLazyText params padLeft = if L.head paramsText == ':' then [lt| |] else mempty callback m = [lt|const std::function& callback|] comm s@Service {..} = [lt|#{template}class #{declName} { public: virtual ~#{declName}() = default; #{doubleLineSep 2 virtualMethod serviceMethods} struct Schema; class Proxy; template