-- This file is part of Hoppy.
--
-- Copyright 2015-2021 Bryan Gardiner <bog@khumba.net>
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU Affero General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU Affero General Public License for more details.
--
-- You should have received a copy of the GNU Affero General Public License
-- along with this program.  If not, see <http://www.gnu.org/licenses/>.

{-# LANGUAGE CPP #-}

-- | Conversions for C++ classes.
--
-- TODO Refactor this, 'cause the TManual conversion stuff is in Base.  (Not a
-- high priority, this /is/ a private module.)
--
-- 'Show' instances in this module produce strings of the form @\"\<TypeOfObject
-- nameOfObject otherInfo...\>\"@.  They can be used in error messages without
-- specifying a noun separately, i.e. write @show cls@ instead of @\"the class
-- \" ++ show cls@.
module Foreign.Hoppy.Generator.Spec.Conversion (
  -- * Advanced class conversions
  classSetConversionToHeap,
  classSetConversionToGc,
  ) where

#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (mconcat)
#endif
import Foreign.Hoppy.Generator.Language.Haskell
import Foreign.Hoppy.Generator.Spec.Base
import Foreign.Hoppy.Generator.Spec.Class
import Foreign.Hoppy.Generator.Types

-- | Modifies a class's 'ClassConversion' structure by setting all languages
-- to copy objects to the heap when being passed out of C++.  Lifetimes of the
-- resulting objects must be managed by code in the foreign language.
--
-- Calling this on a class makes 'objT' behave like 'objToHeapT' for values
-- being passed out of C++.
classSetConversionToHeap :: Class -> Class
classSetConversionToHeap :: Class -> Class
classSetConversionToHeap Class
cls = case Class -> Maybe Ctor
classFindCopyCtor Class
cls of
  Just Ctor
_ ->
    ((ClassConversion -> ClassConversion) -> Class -> Class)
-> Class -> (ClassConversion -> ClassConversion) -> Class
forall a b c. (a -> b -> c) -> b -> a -> c
flip HasCallStack =>
(ClassConversion -> ClassConversion) -> Class -> Class
(ClassConversion -> ClassConversion) -> Class -> Class
classModifyConversion Class
cls ((ClassConversion -> ClassConversion) -> Class)
-> (ClassConversion -> ClassConversion) -> Class
forall a b. (a -> b) -> a -> b
$ \ClassConversion
c ->
    ClassConversion
c { classHaskellConversion :: ClassHaskellConversion
classHaskellConversion = Class -> ClassHaskellConversion
classHaskellConversionToHeap Class
cls
      }
  Maybe Ctor
Nothing -> [Char] -> Class
forall a. HasCallStack => [Char] -> a
error ([Char] -> Class) -> [Char] -> Class
forall a b. (a -> b) -> a -> b
$ [Char]
"classSetConversionToHeap: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Class -> [Char]
forall a. Show a => a -> [Char]
show Class
cls [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" must be copyable."

-- | Modifies a class's 'ClassConversion' structure by setting all languages
-- that support garbage collection to copy objects to the heap when being passed
-- out of C++, and put those objects under the care of the foreign language's
-- garbage collector.
--
-- Calling this on a class makes 'objT' behave like 'toGcT' for values being
-- passed out of C++.
classSetConversionToGc :: Class -> Class
classSetConversionToGc :: Class -> Class
classSetConversionToGc Class
cls = case Class -> Maybe Ctor
classFindCopyCtor Class
cls of
  Just Ctor
_ ->
    ((ClassConversion -> ClassConversion) -> Class -> Class)
-> Class -> (ClassConversion -> ClassConversion) -> Class
forall a b c. (a -> b -> c) -> b -> a -> c
flip HasCallStack =>
(ClassConversion -> ClassConversion) -> Class -> Class
(ClassConversion -> ClassConversion) -> Class -> Class
classModifyConversion Class
cls ((ClassConversion -> ClassConversion) -> Class)
-> (ClassConversion -> ClassConversion) -> Class
forall a b. (a -> b) -> a -> b
$ \ClassConversion
c ->
    ClassConversion
c { classHaskellConversion :: ClassHaskellConversion
classHaskellConversion = Class -> ClassHaskellConversion
classHaskellConversionToGc Class
cls
      }
  Maybe Ctor
Nothing -> [Char] -> Class
forall a. HasCallStack => [Char] -> a
error ([Char] -> Class) -> [Char] -> Class
forall a b. (a -> b) -> a -> b
$ [Char]
"classSetConversionToGc: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Class -> [Char]
forall a. Show a => a -> [Char]
show Class
cls [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" must be copyable."

classHaskellConversionToHeap :: Class -> ClassHaskellConversion
classHaskellConversionToHeap :: Class -> ClassHaskellConversion
classHaskellConversionToHeap Class
cls =
  ClassHaskellConversion :: Maybe (Generator HsType)
-> Maybe (Generator ())
-> Maybe (Generator ())
-> ClassHaskellConversion
ClassHaskellConversion
  { classHaskellConversionType :: Maybe (Generator HsType)
classHaskellConversionType = Generator HsType -> Maybe (Generator HsType)
forall a. a -> Maybe a
Just (Generator HsType -> Maybe (Generator HsType))
-> Generator HsType -> Maybe (Generator HsType)
forall a b. (a -> b) -> a -> b
$ HsTypeSide -> Type -> Generator HsType
cppTypeToHsTypeAndUse HsTypeSide
HsHsSide (Type -> Generator HsType) -> Type -> Generator HsType
forall a b. (a -> b) -> a -> b
$ Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
cls
  , classHaskellConversionToCppFn :: Maybe (Generator ())
classHaskellConversionToCppFn = Maybe (Generator ())
forall a. Maybe a
Nothing
  , classHaskellConversionFromCppFn :: Maybe (Generator ())
classHaskellConversionFromCppFn = Generator () -> Maybe (Generator ())
forall a. a -> Maybe a
Just (Generator () -> Maybe (Generator ()))
-> Generator () -> Maybe (Generator ())
forall a b. (a -> b) -> a -> b
$ do
      HsImportSet -> Generator ()
addImports HsImportSet
hsImportForRuntime
      [Char] -> Generator ()
sayLn [Char]
"HoppyFHR.copy"
  }

classHaskellConversionToGc :: Class -> ClassHaskellConversion
classHaskellConversionToGc :: Class -> ClassHaskellConversion
classHaskellConversionToGc Class
cls =
  ClassHaskellConversion :: Maybe (Generator HsType)
-> Maybe (Generator ())
-> Maybe (Generator ())
-> ClassHaskellConversion
ClassHaskellConversion
  { classHaskellConversionType :: Maybe (Generator HsType)
classHaskellConversionType = Generator HsType -> Maybe (Generator HsType)
forall a. a -> Maybe a
Just (Generator HsType -> Maybe (Generator HsType))
-> Generator HsType -> Maybe (Generator HsType)
forall a b. (a -> b) -> a -> b
$ HsTypeSide -> Type -> Generator HsType
cppTypeToHsTypeAndUse HsTypeSide
HsHsSide (Type -> Generator HsType) -> Type -> Generator HsType
forall a b. (a -> b) -> a -> b
$ Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
cls
  , classHaskellConversionToCppFn :: Maybe (Generator ())
classHaskellConversionToCppFn = Maybe (Generator ())
forall a. Maybe a
Nothing
  , classHaskellConversionFromCppFn :: Maybe (Generator ())
classHaskellConversionFromCppFn = Generator () -> Maybe (Generator ())
forall a. a -> Maybe a
Just (Generator () -> Maybe (Generator ()))
-> Generator () -> Maybe (Generator ())
forall a b. (a -> b) -> a -> b
$ do
      HsImportSet -> Generator ()
addImports (HsImportSet -> Generator ()) -> HsImportSet -> Generator ()
forall a b. (a -> b) -> a -> b
$ [HsImportSet] -> HsImportSet
forall a. Monoid a => [a] -> a
mconcat [[Char] -> [Char] -> HsImportSet
hsImport1 [Char]
"Control.Monad" [Char]
"(>=>)", HsImportSet
hsImportForRuntime]
      [Char] -> Generator ()
sayLn [Char]
"HoppyFHR.copy >=> HoppyFHR.toGc"
  }