module Data.GI.CodeGen.OverloadedMethods
( genMethodList
, genMethodInfo
, genUnsupportedMethodInfo
) where
import Control.Monad (forM, forM_, when)
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid ((<>))
#endif
import Data.Text (Text)
import qualified Data.Text as T
import Data.GI.CodeGen.API
import Data.GI.CodeGen.Conversions (ExposeClosures(..))
import Data.GI.CodeGen.Callable (callableSignature, Signature(..),
ForeignSymbol(..), fixupCallerAllocates)
import Data.GI.CodeGen.Code
import Data.GI.CodeGen.SymbolNaming (lowerName, upperName, qualifiedSymbol)
import Data.GI.CodeGen.Util (ucFirst)
methodInfoName :: Name -> Method -> CodeGen Text
methodInfoName :: Name -> Method -> CodeGen Text
methodInfoName n :: Name
n method :: Method
method =
let infoName :: Text
infoName = Name -> Text
upperName Name
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (Text -> Text
ucFirst (Text -> Text) -> (Method -> Text) -> Method -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Text
lowerName (Name -> Text) -> (Method -> Name) -> Method -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Name
methodName) Method
method
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "MethodInfo"
in Text -> Name -> CodeGen Text
qualifiedSymbol Text
infoName Name
n
genMethodResolver :: Text -> CodeGen ()
genMethodResolver :: Text -> CodeGen ()
genMethodResolver n :: Text
n = do
Text -> CodeGen ()
addLanguagePragma "TypeApplications"
BaseCodeGen e () -> BaseCodeGen e ()
forall e a. BaseCodeGen e a -> BaseCodeGen e a
group (BaseCodeGen e () -> BaseCodeGen e ())
-> BaseCodeGen e () -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ do
Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ "instance (info ~ Resolve" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "Method t " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ", "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "O.MethodInfo info " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " p) => OL.IsLabel t ("
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " -> p) where"
Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ "#if MIN_VERSION_base(4,10,0)"
BaseCodeGen e () -> BaseCodeGen e ()
forall e a. BaseCodeGen e a -> BaseCodeGen e a
indent (BaseCodeGen e () -> BaseCodeGen e ())
-> BaseCodeGen e () -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ "fromLabel = O.overloadedMethod @info"
Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ "#else"
BaseCodeGen e () -> BaseCodeGen e ()
forall e a. BaseCodeGen e a -> BaseCodeGen e a
indent (BaseCodeGen e () -> BaseCodeGen e ())
-> BaseCodeGen e () -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ "fromLabel _ = O.overloadedMethod @info"
Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ "#endif"
genMethodList :: Name -> [(Name, Method)] -> CodeGen ()
genMethodList :: Name -> [(Name, Method)] -> CodeGen ()
genMethodList n :: Name
n methods :: [(Name, Method)]
methods = do
let name :: Text
name = Name -> Text
upperName Name
n
let filteredMethods :: [(Name, Method)]
filteredMethods = ((Name, Method) -> Bool) -> [(Name, Method)] -> [(Name, Method)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Name, Method) -> Bool
isOrdinaryMethod [(Name, Method)]
methods
gets :: [(Name, Method)]
gets = ((Name, Method) -> Bool) -> [(Name, Method)] -> [(Name, Method)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Name, Method) -> Bool
isGet [(Name, Method)]
filteredMethods
sets :: [(Name, Method)]
sets = ((Name, Method) -> Bool) -> [(Name, Method)] -> [(Name, Method)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Name, Method) -> Bool
isSet [(Name, Method)]
filteredMethods
others :: [(Name, Method)]
others = ((Name, Method) -> Bool) -> [(Name, Method)] -> [(Name, Method)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\m :: (Name, Method)
m -> Bool -> Bool
not ((Name, Method) -> Bool
isSet (Name, Method)
m Bool -> Bool -> Bool
|| (Name, Method) -> Bool
isGet (Name, Method)
m)) [(Name, Method)]
filteredMethods
orderedMethods :: [(Name, Method)]
orderedMethods = [(Name, Method)]
others [(Name, Method)] -> [(Name, Method)] -> [(Name, Method)]
forall a. [a] -> [a] -> [a]
++ [(Name, Method)]
gets [(Name, Method)] -> [(Name, Method)] -> [(Name, Method)]
forall a. [a] -> [a] -> [a]
++ [(Name, Method)]
sets
[(Text, Text)]
infos <- [(Name, Method)]
-> ((Name, Method)
-> ReaderT
CodeGenConfig
(StateT (CGState, ModuleInfo) (Except e))
(Text, Text))
-> ReaderT
CodeGenConfig
(StateT (CGState, ModuleInfo) (Except e))
[(Text, Text)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [(Name, Method)]
orderedMethods (((Name, Method)
-> ReaderT
CodeGenConfig
(StateT (CGState, ModuleInfo) (Except e))
(Text, Text))
-> ReaderT
CodeGenConfig
(StateT (CGState, ModuleInfo) (Except e))
[(Text, Text)])
-> ((Name, Method)
-> ReaderT
CodeGenConfig
(StateT (CGState, ModuleInfo) (Except e))
(Text, Text))
-> ReaderT
CodeGenConfig
(StateT (CGState, ModuleInfo) (Except e))
[(Text, Text)]
forall a b. (a -> b) -> a -> b
$ \(owner :: Name
owner, method :: Method
method) ->
do Text
mi <- Name -> Method -> CodeGen Text
methodInfoName Name
owner Method
method
(Text, Text)
-> ReaderT
CodeGenConfig
(StateT (CGState, ModuleInfo) (Except e))
(Text, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Name -> Text
lowerName (Name -> Text) -> (Method -> Name) -> Method -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Name
methodName) Method
method, Text
mi)
BaseCodeGen e () -> BaseCodeGen e ()
forall e a. BaseCodeGen e a -> BaseCodeGen e a
group (BaseCodeGen e () -> BaseCodeGen e ())
-> BaseCodeGen e () -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ do
let resolver :: Text
resolver = "Resolve" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "Method"
HaddockSection -> Text -> CodeGen ()
export (NamedSection -> Text -> HaddockSection
NamedSubsection NamedSection
MethodSection "Overloaded methods") Text
resolver
Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ "type family " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
resolver Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " (t :: Symbol) (o :: *) :: * where"
BaseCodeGen e () -> BaseCodeGen e ()
forall e a. BaseCodeGen e a -> BaseCodeGen e a
indent (BaseCodeGen e () -> BaseCodeGen e ())
-> BaseCodeGen e () -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ [(Text, Text)]
-> ((Text, Text) -> BaseCodeGen e ()) -> BaseCodeGen e ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(Text, Text)]
infos (((Text, Text) -> BaseCodeGen e ()) -> BaseCodeGen e ())
-> ((Text, Text) -> BaseCodeGen e ()) -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ \(label :: Text
label, info :: Text
info) -> do
Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
resolver Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " \"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
label Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "\" o = " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
info
BaseCodeGen e () -> BaseCodeGen e ()
forall e a. BaseCodeGen e a -> BaseCodeGen e a
indent (BaseCodeGen e () -> BaseCodeGen e ())
-> BaseCodeGen e () -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
resolver Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " l o = O.MethodResolutionFailed l o"
Text -> CodeGen ()
genMethodResolver Text
name
where isOrdinaryMethod :: (Name, Method) -> Bool
isOrdinaryMethod :: (Name, Method) -> Bool
isOrdinaryMethod (_, m :: Method
m) = Method -> MethodType
methodType Method
m MethodType -> MethodType -> Bool
forall a. Eq a => a -> a -> Bool
== MethodType
OrdinaryMethod
isGet :: (Name, Method) -> Bool
isGet :: (Name, Method) -> Bool
isGet (_, m :: Method
m) = "get_" Text -> Text -> Bool
`T.isPrefixOf` (Name -> Text
name (Name -> Text) -> (Method -> Name) -> Method -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Name
methodName) Method
m
isSet :: (Name, Method) -> Bool
isSet :: (Name, Method) -> Bool
isSet (_, m :: Method
m) = "set_" Text -> Text -> Bool
`T.isPrefixOf` (Name -> Text
name (Name -> Text) -> (Method -> Name) -> Method -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Name
methodName) Method
m
genMethodInfo :: Name -> Method -> ExcCodeGen ()
genMethodInfo :: Name -> Method -> ExcCodeGen ()
genMethodInfo n :: Name
n m :: Method
m =
Bool -> ExcCodeGen () -> ExcCodeGen ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Method -> MethodType
methodType Method
m MethodType -> MethodType -> Bool
forall a. Eq a => a -> a -> Bool
== MethodType
OrdinaryMethod) (ExcCodeGen () -> ExcCodeGen ()) -> ExcCodeGen () -> ExcCodeGen ()
forall a b. (a -> b) -> a -> b
$
ExcCodeGen () -> ExcCodeGen ()
forall e a. BaseCodeGen e a -> BaseCodeGen e a
group (ExcCodeGen () -> ExcCodeGen ()) -> ExcCodeGen () -> ExcCodeGen ()
forall a b. (a -> b) -> a -> b
$ do
Text
infoName <- Name -> Method -> CodeGen Text
methodInfoName Name
n Method
m
let callable :: Callable
callable = Callable -> Callable
fixupCallerAllocates (Method -> Callable
methodCallable Method
m)
Signature
sig <- Callable -> ForeignSymbol -> ExposeClosures -> ExcCodeGen Signature
callableSignature Callable
callable (Text -> ForeignSymbol
KnownForeignSymbol Text
forall a. HasCallStack => a
undefined) ExposeClosures
WithoutClosures
Text -> ExcCodeGen ()
Text -> CodeGen ()
bline (Text -> ExcCodeGen ()) -> Text -> ExcCodeGen ()
forall a b. (a -> b) -> a -> b
$ "data " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
infoName
Bool -> ExcCodeGen () -> ExcCodeGen ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([(Maybe Arg, Text)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Signature -> [(Maybe Arg, Text)]
signatureArgTypes Signature
sig)) (ExcCodeGen () -> ExcCodeGen ()) -> ExcCodeGen () -> ExcCodeGen ()
forall a b. (a -> b) -> a -> b
$
[Char] -> ExcCodeGen ()
forall a. HasCallStack => [Char] -> a
error ([Char] -> ExcCodeGen ()) -> [Char] -> ExcCodeGen ()
forall a b. (a -> b) -> a -> b
$ "Internal error: too few parameters! " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Method -> [Char]
forall a. Show a => a -> [Char]
show Method
m
let (obj :: Text
obj:otherTypes :: [Text]
otherTypes) = ((Maybe Arg, Text) -> Text) -> [(Maybe Arg, Text)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Arg, Text) -> Text
forall a b. (a, b) -> b
snd (Signature -> [(Maybe Arg, Text)]
signatureArgTypes Signature
sig)
sigConstraint :: Text
sigConstraint = "signature ~ (" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate " -> "
([Text]
otherTypes [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Signature -> Text
signatureReturnType Signature
sig]) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ")"
Text -> ExcCodeGen ()
Text -> CodeGen ()
line (Text -> ExcCodeGen ()) -> Text -> ExcCodeGen ()
forall a b. (a -> b) -> a -> b
$ "instance (" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate ", " (Text
sigConstraint Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:
Signature -> [Text]
signatureConstraints Signature
sig)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ") => O.MethodInfo " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
infoName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
obj Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " signature where"
let mn :: Name
mn = Method -> Name
methodName Method
m
mangled :: Text
mangled = Name -> Text
lowerName (Name
mn {name :: Text
name = Name -> Text
name Name
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Name -> Text
name Name
mn})
ExcCodeGen () -> ExcCodeGen ()
forall e a. BaseCodeGen e a -> BaseCodeGen e a
indent (ExcCodeGen () -> ExcCodeGen ()) -> ExcCodeGen () -> ExcCodeGen ()
forall a b. (a -> b) -> a -> b
$ Text -> ExcCodeGen ()
Text -> CodeGen ()
line (Text -> ExcCodeGen ()) -> Text -> ExcCodeGen ()
forall a b. (a -> b) -> a -> b
$ "overloadedMethod = " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
mangled
HaddockSection -> Text -> CodeGen ()
export (NamedSection -> Text -> HaddockSection
NamedSubsection NamedSection
MethodSection (Text -> HaddockSection) -> Text -> HaddockSection
forall a b. (a -> b) -> a -> b
$ Name -> Text
lowerName Name
mn) Text
infoName
genUnsupportedMethodInfo :: Name -> Method -> CodeGen ()
genUnsupportedMethodInfo :: Name -> Method -> CodeGen ()
genUnsupportedMethodInfo n :: Name
n m :: Method
m = do
Text
infoName <- Name -> Method -> CodeGen Text
methodInfoName Name
n Method
m
Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ "-- XXX: Dummy instance, since code generation failed.\n"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "-- Please file a bug at http://github.com/haskell-gi/haskell-gi."
Text -> BaseCodeGen e ()
Text -> CodeGen ()
bline (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ "data " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
infoName
Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ "instance (p ~ (), o ~ O.UnsupportedMethodError \""
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Name -> Text
lowerName (Method -> Name
methodName Method
m) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "\" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Name -> Text
name Name
n
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ") => O.MethodInfo " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
infoName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " o p where"
BaseCodeGen e () -> BaseCodeGen e ()
forall e a. BaseCodeGen e a -> BaseCodeGen e a
indent (BaseCodeGen e () -> BaseCodeGen e ())
-> BaseCodeGen e () -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text -> BaseCodeGen e ()
Text -> CodeGen ()
line (Text -> BaseCodeGen e ()) -> Text -> BaseCodeGen e ()
forall a b. (a -> b) -> a -> b
$ "overloadedMethod = undefined"
HaddockSection -> Text -> CodeGen ()
export HaddockSection
ToplevelSection Text
infoName