{- -----------------------------------------------------------------------------
Copyright 2019-2021 Kevin P. Barry

Licensed under the Apache License, Version 2.0 (the "License");
you may not use this file except in compliance with the License.
You may obtain a copy of the License at

    http://www.apache.org/licenses/LICENSE-2.0

Unless required by applicable law or agreed to in writing, software
distributed under the License is distributed on an "AS IS" BASIS,
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
See the License for the specific language governing permissions and
limitations under the License.
----------------------------------------------------------------------------- -}

-- Author: Kevin P. Barry [ta0kira@gmail.com]

{-# LANGUAGE Safe #-}

module CompilerCxx.Naming (
  allGetter,
  anyGetter,
  baseHeaderIncludes,
  baseSourceIncludes,
  callName,
  categoryCreator,
  categoryCustom,
  categoryGetter,
  categoryName,
  collectionName,
  functionDebugName,
  functionName,
  headerFilename,
  headerStreamlined,
  hiddenVariableName,
  initializerName,
  intersectGetter,
  mainFilename,
  mainSourceIncludes,
  paramName,
  privateNamespace,
  privateNamespaceMacro,
  publicNamespace,
  publicNamespaceMacro,
  qualifiedTypeGetter,
  sourceFilename,
  sourceStreamlined,
  tableName,
  templateIncludes,
  templateStreamlined,
  testFilename,
  testFunctionName,
  testTimeoutMacro,
  typeCreator,
  typeCustom,
  typeGetter,
  typeName,
  unionGetter,
  valueCreator,
  valueCustom,
  valueName,
  variableName,
) where

import Data.Hashable (Hashable,hash)
import Numeric (showHex)

import Types.Procedure
import Types.TypeCategory
import Types.TypeInstance


headerFilename :: CategoryName -> String
headerFilename :: CategoryName -> String
headerFilename CategoryName
n = String
"Category_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".hpp"

sourceFilename :: CategoryName -> String
sourceFilename :: CategoryName -> String
sourceFilename CategoryName
n = String
"Category_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".cpp"

headerStreamlined :: CategoryName -> String
headerStreamlined :: CategoryName -> String
headerStreamlined CategoryName
n = String
"Streamlined_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".hpp"

sourceStreamlined :: CategoryName -> String
sourceStreamlined :: CategoryName -> String
sourceStreamlined CategoryName
n = String
"Streamlined_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".cpp"

templateStreamlined :: CategoryName -> String
templateStreamlined :: CategoryName -> String
templateStreamlined CategoryName
n = String
"Extension_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".cpp"

mainFilename :: String
mainFilename :: String
mainFilename = String
"main.cpp"

testFilename :: String
testFilename :: String
testFilename = String
"test.cpp"

baseHeaderIncludes :: [String]
baseHeaderIncludes :: [String]
baseHeaderIncludes = [String
"#include \"category-header.hpp\""]

baseSourceIncludes :: [String]
baseSourceIncludes :: [String]
baseSourceIncludes = [String
"#include \"category-source.hpp\"",String
"#include \"internal.hpp\""]

templateIncludes :: [String]
templateIncludes :: [String]
templateIncludes = [String
"#include \"category-source.hpp\""]

mainSourceIncludes :: [String]
mainSourceIncludes :: [String]
mainSourceIncludes = [String
"#include \"logging.hpp\""]

paramName :: ParamName -> String
paramName :: ParamName -> String
paramName ParamName
p = String
"Param_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. [a] -> [a]
tail (ParamName -> String
forall a. Show a => a -> String
show ParamName
p) -- Remove leading '#'.

variableName :: VariableName -> String
variableName :: VariableName -> String
variableName VariableName
VariableSelf = String
"VAR_SELF"
variableName VariableName
v            = String
"Var_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ VariableName -> String
forall a. Show a => a -> String
show VariableName
v

hiddenVariableName :: VariableName -> String
hiddenVariableName :: VariableName -> String
hiddenVariableName VariableName
v = String
"Internal_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ VariableName -> String
forall a. Show a => a -> String
show VariableName
v

initializerName :: VariableName -> String
initializerName :: VariableName -> String
initializerName VariableName
v = String
"Init_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ VariableName -> String
forall a. Show a => a -> String
show VariableName
v

categoryName :: CategoryName -> String
categoryName :: CategoryName -> String
categoryName CategoryName
n = String
"Category_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

categoryGetter :: CategoryName -> String
categoryGetter :: CategoryName -> String
categoryGetter CategoryName
n = String
"GetCategory_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

typeName :: CategoryName -> String
typeName :: CategoryName -> String
typeName CategoryName
n = String
"Type_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

typeGetter :: CategoryName -> String
typeGetter :: CategoryName -> String
typeGetter CategoryName
n = String
"GetType_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

intersectGetter :: String
intersectGetter :: String
intersectGetter = String
"Merge_Intersect"

unionGetter:: String
unionGetter :: String
unionGetter = String
"Merge_Union"

allGetter :: String
allGetter :: String
allGetter = String
"GetMerged_All"

anyGetter :: String
anyGetter :: String
anyGetter = String
"GetMerged_Any"

valueName :: CategoryName -> String
valueName :: CategoryName -> String
valueName CategoryName
n = String
"Value_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

categoryCustom :: CategoryName -> String
categoryCustom :: CategoryName -> String
categoryCustom CategoryName
n = String
"ExtCategory_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

typeCustom :: CategoryName -> String
typeCustom :: CategoryName -> String
typeCustom CategoryName
n = String
"ExtType_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

valueCustom :: CategoryName -> String
valueCustom :: CategoryName -> String
valueCustom CategoryName
n = String
"ExtValue_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

callName :: FunctionName -> String
callName :: FunctionName -> String
callName FunctionName
f = String
"Call_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ FunctionName -> String
forall a. Show a => a -> String
show FunctionName
f

functionDebugName :: CategoryName -> ScopedFunction c -> String
functionDebugName :: CategoryName -> ScopedFunction c -> String
functionDebugName CategoryName
t ScopedFunction c
f
  | ScopedFunction c -> SymbolScope
forall c. ScopedFunction c -> SymbolScope
sfScope ScopedFunction c
f SymbolScope -> SymbolScope -> Bool
forall a. Eq a => a -> a -> Bool
== SymbolScope
CategoryScope = CategoryName -> String
forall a. Show a => a -> String
show CategoryName
t String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ FunctionName -> String
forall a. Show a => a -> String
show (ScopedFunction c -> FunctionName
forall c. ScopedFunction c -> FunctionName
sfName ScopedFunction c
f)
  | Bool
otherwise                  = CategoryName -> String
forall a. Show a => a -> String
show CategoryName
t String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ FunctionName -> String
forall a. Show a => a -> String
show (ScopedFunction c -> FunctionName
forall c. ScopedFunction c -> FunctionName
sfName ScopedFunction c
f)

functionName :: ScopedFunction c -> String
functionName :: ScopedFunction c -> String
functionName ScopedFunction c
f = String
"Function_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show (ScopedFunction c -> CategoryName
forall c. ScopedFunction c -> CategoryName
sfType ScopedFunction c
f) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ FunctionName -> String
forall a. Show a => a -> String
show (ScopedFunction c -> FunctionName
forall c. ScopedFunction c -> FunctionName
sfName ScopedFunction c
f)

collectionName :: CategoryName -> String
collectionName :: CategoryName -> String
collectionName CategoryName
n = String
"Functions_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

testFunctionName :: FunctionName -> String
testFunctionName :: FunctionName -> String
testFunctionName FunctionName
f = String
"Test_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ FunctionName -> String
forall a. Show a => a -> String
show FunctionName
f

tableName :: CategoryName -> String
tableName :: CategoryName -> String
tableName CategoryName
n = String
"Table_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

categoryCreator :: CategoryName -> String
categoryCreator :: CategoryName -> String
categoryCreator CategoryName
n = String
"CreateCategory_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

typeCreator :: CategoryName -> String
typeCreator :: CategoryName -> String
typeCreator CategoryName
n = String
"CreateType_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

valueCreator :: CategoryName -> String
valueCreator :: CategoryName -> String
valueCreator CategoryName
n = String
"CreateValue_" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n

privateNamespace :: Hashable a => a -> String
privateNamespace :: a -> String
privateNamespace = (String
"private_" String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (a -> String) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> String -> String) -> String -> Int -> String
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> String -> String
forall a. (Integral a, Show a) => a -> String -> String
showHex String
"" (Int -> String) -> (a -> Int) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a. Num a => a -> a
abs (Int -> Int) -> (a -> Int) -> a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Int
forall a. Hashable a => a -> Int
hash

publicNamespace :: Hashable a => a -> String
publicNamespace :: a -> String
publicNamespace = (String
"public_" String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (a -> String) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> String -> String) -> String -> Int -> String
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> String -> String
forall a. (Integral a, Show a) => a -> String -> String
showHex String
"" (Int -> String) -> (a -> Int) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a. Num a => a -> a
abs (Int -> Int) -> (a -> Int) -> a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Int
forall a. Hashable a => a -> Int
hash

qualifiedTypeGetter :: AnyCategory c -> String
qualifiedTypeGetter :: AnyCategory c -> String
qualifiedTypeGetter AnyCategory c
t
  | Namespace -> Bool
isStaticNamespace (Namespace -> Bool) -> Namespace -> Bool
forall a b. (a -> b) -> a -> b
$ AnyCategory c -> Namespace
forall c. AnyCategory c -> Namespace
getCategoryNamespace AnyCategory c
t =
    Namespace -> String
forall a. Show a => a -> String
show (AnyCategory c -> Namespace
forall c. AnyCategory c -> Namespace
getCategoryNamespace AnyCategory c
t) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"::" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (CategoryName -> String
typeGetter (CategoryName -> String) -> CategoryName -> String
forall a b. (a -> b) -> a -> b
$ AnyCategory c -> CategoryName
forall c. AnyCategory c -> CategoryName
getCategoryName AnyCategory c
t)
  | Bool
otherwise = CategoryName -> String
typeGetter (CategoryName -> String) -> CategoryName -> String
forall a b. (a -> b) -> a -> b
$ AnyCategory c -> CategoryName
forall c. AnyCategory c -> CategoryName
getCategoryName AnyCategory c
t

testTimeoutMacro :: String
testTimeoutMacro :: String
testTimeoutMacro = String
"ZEOLITE_TEST_TIMEOUT"

publicNamespaceMacro :: String
publicNamespaceMacro :: String
publicNamespaceMacro = String
"ZEOLITE_PUBLIC_NAMESPACE"

privateNamespaceMacro :: String
privateNamespaceMacro :: String
privateNamespaceMacro = String
"ZEOLITE_PRIVATE_NAMESPACE"