{-# LANGUAGE OverloadedStrings #-}
module Foreign.Lua.Module
  ( requirehs
  , preloadhs
  , addfield
  , addfunction
  , create
    
  , Module (..)
  , Field (..)
  , registerModule
  , preloadModule
  , pushModule
    
  , render
  )
where
import Control.Monad (unless, forM_)
import Data.Text (Text)
import Foreign.Lua.Call (HaskellFunction)
import Foreign.Lua.Core
import Foreign.Lua.Push (pushText)
import Foreign.Lua.Types (Pushable, push)
import Foreign.Lua.FunctionCalling
  ( ToHaskellFunction
  , pushHaskellFunction
  )
import qualified Data.Text as T
import qualified Foreign.Lua.Call as Call
requirehs :: String -> Lua () -> Lua ()
requirehs modname pushMod = do
  
  getfield registryindex loadedTableRegistryField
  
  getfield stackTop modname  
  alreadyLoaded <- toboolean stackTop
  unless alreadyLoaded $ do
    pop 1  
    pushMod  
    pushvalue stackTop  
    
    setfield (nthFromTop 3) modname
  remove (nthFromTop 2)  
preloadhs :: String -> Lua NumResults -> Lua ()
preloadhs name pushMod = do
  getfield registryindex preloadTableRegistryField
  pushHaskellFunction pushMod
  setfield (nthFromTop 2) name
  pop 1
addfield :: Pushable a => String -> a -> Lua ()
addfield name value = do
  push name
  push value
  rawset (nthFromTop 3)
addfunction :: ToHaskellFunction a => String -> a -> Lua ()
addfunction name fn = do
  push name
  pushHaskellFunction fn
  rawset (nthFromTop 3)
create :: Lua ()
create = newtable
data Module = Module
  { moduleName :: Text
  , moduleDescription :: Text
  , moduleFields :: [Field]
  , moduleFunctions :: [(Text, HaskellFunction)]
  }
data Field = Field
  { fieldName :: Text
  , fieldDescription :: Text
  , fieldPushValue :: Lua ()
  }
registerModule :: Module -> Lua ()
registerModule mdl =
  requirehs (T.unpack $ moduleName mdl) (pushModule mdl)
preloadModule :: Module -> Lua ()
preloadModule mdl =
  preloadhs (T.unpack $ moduleName mdl) $ do
    pushModule mdl
    return (NumResults 1)
pushModule :: Module -> Lua ()
pushModule mdl = do
  create
  forM_ (moduleFunctions mdl) $ \(name, fn) -> do
    pushText name
    Call.pushHaskellFunction fn
    rawset (nthFromTop 3)
render :: Module -> Text
render mdl =
  let fields = moduleFields mdl
  in T.unlines
     [ "# " <> moduleName mdl
     , ""
     , moduleDescription mdl
     , if null (moduleFields mdl) then "" else renderFields fields
     , "## Functions"
     , ""
     ]
     <> T.intercalate "\n"
        (map (uncurry renderFunctionDoc) (moduleFunctions mdl))
renderFunctionDoc :: Text             
                  -> HaskellFunction  
                  -> Text             
renderFunctionDoc name fn =
  case Call.functionDoc fn of
    Nothing -> ""
    Just fnDoc -> T.intercalate "\n"
      [ "### " <> name <> " (" <> renderFunctionParams fnDoc <> ")"
      , ""
      , Call.render fnDoc
      ]
renderFunctionParams :: Call.FunctionDoc -> Text
renderFunctionParams fd =
    T.intercalate ", "
  . map Call.parameterName
  $ Call.parameterDocs fd
renderFields :: [Field] -> Text
renderFields fs =
  if null fs
  then mempty
  else T.unlines $ map renderField fs
renderField :: Field -> Text
renderField f =
  "### " <> fieldName f <> "\n\n" <> fieldDescription f <> "\n"