-- 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.Enum_h (enum_h) where



import Data.Monoid

import Prelude

import Data.Text.Lazy (Text)

import Text.Shakespeare.Text

import Language.Bond.Syntax.Types

import Language.Bond.Codegen.TypeMapping

import Language.Bond.Codegen.Util

import qualified Language.Bond.Codegen.Cpp.Util as CPP



-- | Codegen template for generating /base_name/_enum.h containing definitions

-- of enums. Generated by <https://microsoft.github.io/bond/manual/compiler.html gbc> with @--enum-header@ flag.

enum_h :: MappingContext -> String -> [Import] -> [Declaration] -> (String, Text)

enum_h cpp _file _imports declarations = ("_enum.h", [lt|

#pragma once



#include <stdint.h>



#{CPP.openNamespace cpp}

namespace _bond_enumerators

{

    #{newlineSep 1 typeDeclaration declarations}

} // namespace _bond_enumerators



#{newlineSep 0 usingDeclaration declarations}

#{CPP.closeNamespace cpp}

|])

  where

    -- enum definition

    typeDeclaration e@Enum {..} = [lt|

    namespace #{declName}

    {

        #{CPP.enumDefinition e}

    } // namespace #{declName}

|]

    typeDeclaration _ = mempty



    usingDeclaration Enum {..} = [lt|using namespace _bond_enumerators::#{declName};|]

    usingDeclaration _ = mempty