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.ModulePath (dotModulePath)
import Data.GI.CodeGen.SymbolNaming (lowerName, upperName, qualifiedSymbol,
moduleLocation, hackageModuleLink)
import Data.GI.CodeGen.Util (ucFirst)
methodInfoName :: Name -> Method -> CodeGen e Text
methodInfoName :: forall e. Name -> Method -> CodeGen e Text
methodInfoName Name
n 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
<> Text
"MethodInfo"
in Text -> Name -> CodeGen e Text
forall e. Text -> Name -> CodeGen e Text
qualifiedSymbol Text
infoName Name
n
genMethodResolver :: Text -> CodeGen e ()
genMethodResolver :: forall e. Text -> CodeGen e ()
genMethodResolver Text
n = do
Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
addLanguagePragma Text
"TypeApplications"
CodeGen e () -> CodeGen e ()
forall e a. CodeGen e a -> CodeGen e a
group (CodeGen e () -> CodeGen e ()) -> CodeGen e () -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ do
Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"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
<> Text
"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 -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"O.OverloadedMethod info " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" 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
<> Text
" -> p) where"
Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"#if MIN_VERSION_base(4,10,0)"
CodeGen e () -> CodeGen e ()
forall e a. CodeGen e a -> CodeGen e a
indent (CodeGen e () -> CodeGen e ()) -> CodeGen e () -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"fromLabel = O.overloadedMethod @info"
Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"#else"
CodeGen e () -> CodeGen e ()
forall e a. CodeGen e a -> CodeGen e a
indent (CodeGen e () -> CodeGen e ()) -> CodeGen e () -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"fromLabel _ = O.overloadedMethod @info"
Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"#endif"
CPPGuard -> CodeGen e () -> CodeGen e ()
forall e a. CPPGuard -> CodeGen e a -> CodeGen e a
cppIf (Text -> (Integer, Integer, Integer) -> CPPGuard
CPPMinVersion Text
"base" (Integer
4,Integer
13,Integer
0)) (CodeGen e () -> CodeGen e ()) -> CodeGen e () -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ CodeGen e () -> CodeGen e ()
forall e a. CodeGen e a -> CodeGen e a
group (CodeGen e () -> CodeGen e ()) -> CodeGen e () -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ do
Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"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
<> Text
"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 -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"O.OverloadedMethod info " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" p, "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"R.HasField t " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" p) => "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"R.HasField t " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" p where"
CodeGen e () -> CodeGen e ()
forall e a. CodeGen e a -> CodeGen e a
indent (CodeGen e () -> CodeGen e ()) -> CodeGen e () -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"getField = O.overloadedMethod @info"
CodeGen e () -> CodeGen e ()
forall e a. CodeGen e a -> CodeGen e a
group (CodeGen e () -> CodeGen e ()) -> CodeGen e () -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ do
Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"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
<> Text
"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 -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"O.OverloadedMethodInfo info " 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 -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"OL.IsLabel t (O.MethodProxy info "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
") where"
Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"#if MIN_VERSION_base(4,10,0)"
CodeGen e () -> CodeGen e ()
forall e a. CodeGen e a -> CodeGen e a
indent (CodeGen e () -> CodeGen e ()) -> CodeGen e () -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"fromLabel = O.MethodProxy"
Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"#else"
CodeGen e () -> CodeGen e ()
forall e a. CodeGen e a -> CodeGen e a
indent (CodeGen e () -> CodeGen e ()) -> CodeGen e () -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"fromLabel _ = O.MethodProxy"
Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
"#endif"
genMethodList :: Name -> [(Name, Method)] -> CodeGen e ()
genMethodList :: forall e. Name -> [(Name, Method)] -> CodeGen e ()
genMethodList Name
n [(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 (\(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
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
$ \(Name
owner, Method
method) ->
do mi <- Name -> Method -> CodeGen e Text
forall e. Name -> Method -> CodeGen e Text
methodInfoName Name
owner Method
method
return ((lowerName . methodName) method, mi)
group $ do
let resolver = Text
"Resolve" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"Method"
export (Section MethodSection) resolver
line $ "type family " <> resolver <> " (t :: Symbol) (o :: DK.Type) :: DK.Type where"
indent $ forM_ infos $ \(Text
label, Text
info) -> do
Text -> CodeGen e ()
forall e. Text -> CodeGen e ()
line (Text -> CodeGen e ()) -> Text -> CodeGen e ()
forall a b. (a -> b) -> a -> b
$ Text
resolver Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" \"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
label Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\" o = " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
info
indent $ line $ resolver <> " l o = O.MethodResolutionFailed l o"
genMethodResolver name
docs <- methodListDocumentation others gets sets
prependSectionFormattedDocs (Section MethodSection) docs
where isOrdinaryMethod :: (Name, Method) -> Bool
isOrdinaryMethod :: (Name, Method) -> Bool
isOrdinaryMethod (Name
_, 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 (Name
_, Method
m) = Text
"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 (Name
_, Method
m) = Text
"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
methodListDocumentation :: [(Name, Method)] -> [(Name, Method)]
-> [(Name, Method)] -> CodeGen e Text
methodListDocumentation :: forall e.
[(Name, Method)]
-> [(Name, Method)] -> [(Name, Method)] -> CodeGen e Text
methodListDocumentation [] [] [] = Text
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) Text
forall a.
a
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
methodListDocumentation [(Name, Method)]
ordinary [(Name, Method)]
getters [(Name, Method)]
setters = do
ordinaryFormatted <- [(Name, Method)]
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) Text
forall e. [(Name, Method)] -> CodeGen e Text
formatMethods [(Name, Method)]
ordinary
gettersFormatted <- formatMethods getters
settersFormatted <- formatMethods setters
return $ "\n\n === __Click to display all available methods, including inherited ones__\n"
<> "==== Methods\n" <> ordinaryFormatted
<> "\n==== Getters\n" <> gettersFormatted
<> "\n==== Setters\n" <> settersFormatted
where formatMethods :: [(Name, Method)] -> CodeGen e Text
formatMethods :: forall e. [(Name, Method)] -> CodeGen e Text
formatMethods [] = Text
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) Text
forall a.
a
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"/None/.\n"
formatMethods [(Name, Method)]
methods = do
qualifiedMethods <- [(Name, Method)]
-> ((Name, Method)
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) Text)
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [(Name, Method)]
methods (((Name, Method)
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) Text)
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) [Text])
-> ((Name, Method)
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) Text)
-> ReaderT
CodeGenConfig (StateT (CGState, ModuleInfo) (Except e)) [Text]
forall a b. (a -> b) -> a -> b
$ \(Name
owner, Method
m) -> do
api <- Name -> CodeGen e API
forall e. HasCallStack => Name -> CodeGen e API
findAPIByName Name
owner
let mn = Name -> Text
lowerName (Method -> Name
methodName Method
m)
return $ "[" <> mn <>
"](\"" <> dotModulePath (moduleLocation owner api)
<> "#g:method:" <> mn <> "\")"
return $ T.intercalate ", " qualifiedMethods <> ".\n"
nonNullableInstanceArg :: Callable -> (Callable, Bool)
nonNullableInstanceArg :: Callable -> (Callable, Bool)
nonNullableInstanceArg Callable
c = case Callable -> [Arg]
args Callable
c of
Arg
inst:[Arg]
rest -> (Callable
c {args = inst {mayBeNull = False} : rest}, Arg -> Bool
mayBeNull Arg
inst)
[] -> (Callable
c, Bool
False)
genMethodInfo :: Name -> Method -> ExcCodeGen ()
genMethodInfo :: Name -> Method -> ExcCodeGen ()
genMethodInfo Name
n 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. CodeGen e a -> CodeGen e a
group (ExcCodeGen () -> ExcCodeGen ()) -> ExcCodeGen () -> ExcCodeGen ()
forall a b. (a -> b) -> a -> b
$ do
api <- Name -> CodeGen CGError API
forall e. HasCallStack => Name -> CodeGen e API
findAPIByName Name
n
infoName <- methodInfoName n m
let (callable, nullableInstance) =
nonNullableInstanceArg . fixupCallerAllocates $ methodCallable m
sig <- callableSignature callable (KnownForeignSymbol undefined) WithoutClosures
bline $ "data " <> infoName
let (obj, otherTypes) = case map snd (signatureArgTypes sig) of
[] -> String -> (Text, [Text])
forall a. HasCallStack => String -> a
error (String -> (Text, [Text])) -> String -> (Text, [Text])
forall a b. (a -> b) -> a -> b
$ String
"Internal error: too few parameters! " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Method -> String
forall a. Show a => a -> String
show Method
m
(Text
obj':[Text]
otherTypes') -> (Text
obj', [Text]
otherTypes')
sigConstraint = Text
"signature ~ (" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
" -> "
([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
")"
hackageLink <- hackageModuleLink n
let mn = Method -> Name
methodName Method
m
mangled = Name -> Text
lowerName (Name
mn {name = name n <> "_" <> name mn})
dbgInfo = ModulePath -> Text
dotModulePath (Name -> API -> ModulePath
moduleLocation Name
n API
api) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
mangled
group $ do
line $ "instance ("
<> T.intercalate ", " (sigConstraint : signatureConstraints sig)
<> ") => O.OverloadedMethod " <> infoName <> " " <> obj
<> " signature where"
if nullableInstance
then indent $ line $ "overloadedMethod i = " <> mangled <> " (Just i)"
else indent $ line $ "overloadedMethod = " <> mangled
group $ do
line $ "instance O.OverloadedMethodInfo " <> infoName <> " " <> obj
<> " where"
indent $ do
line $ "overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {"
indent $ do
line $ "O.resolvedSymbolName = \"" <> dbgInfo <> "\","
line $ "O.resolvedSymbolURL = \"" <>
hackageLink <> "#v:" <> mangled <> "\""
line $ "})"
export (NamedSubsection MethodSection $ lowerName mn) infoName
genUnsupportedMethodInfo :: Name -> Method -> CodeGen e ()
genUnsupportedMethodInfo :: forall e. Name -> Method -> CodeGen e ()
genUnsupportedMethodInfo Name
n Method
m = do
infoName <- Name -> Method -> CodeGen e Text
forall e. Name -> Method -> CodeGen e Text
methodInfoName Name
n Method
m
line $ "-- XXX: Dummy instance, since code generation failed.\n"
<> "-- Please file a bug at http://github.com/haskell-gi/haskell-gi."
bline $ "data " <> infoName
group $ do
line $ "instance (p ~ (), o ~ O.UnsupportedMethodError \""
<> lowerName (methodName m) <> "\" " <> name n
<> ") => O.OverloadedMethod " <> infoName <> " o p where"
indent $ line $ "overloadedMethod = undefined"
group $ do
line $ "instance (o ~ O.UnsupportedMethodError \""
<> lowerName (methodName m) <> "\" " <> name n
<> ") => O.OverloadedMethodInfo " <> infoName <> " o where"
indent $ line $ "overloadedMethodInfo = undefined"
export ToplevelSection infoName