{-# LANGUAGE CPP #-}
{-
Copyright (C) 2009 John MacFarlane <jgm@berkeley.edu>

This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation; either version 2 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 General Public License for more details.

You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
-}

{- Functions for loading plugins.
-}

module Network.Gitit.Plugins ( loadPlugin, loadPlugins )
where
import Network.Gitit.Types
import System.FilePath (takeBaseName)
import Control.Monad (unless)
import System.Log.Logger (logM, Priority(..))
#ifdef _PLUGINS
import Data.List (isInfixOf, isPrefixOf)
import GHC
import GHC.Paths
import Unsafe.Coerce

loadPlugin :: FilePath -> IO Plugin
loadPlugin :: FilePath -> IO Plugin
loadPlugin FilePath
pluginName = do
  FilePath -> Priority -> FilePath -> IO ()
logM FilePath
"gitit" Priority
WARNING (FilePath
"Loading plugin '" forall a. [a] -> [a] -> [a]
++ FilePath
pluginName forall a. [a] -> [a] -> [a]
++ FilePath
"'...")
  forall a. Maybe FilePath -> Ghc a -> IO a
runGhc (forall a. a -> Maybe a
Just FilePath
libdir) forall a b. (a -> b) -> a -> b
$ do
    DynFlags
dflags <- forall (m :: * -> *). GhcMonad m => m DynFlags
getSessionDynFlags
    forall (m :: * -> *). GhcMonad m => DynFlags -> m ()
setSessionDynFlags DynFlags
dflags
    -- initDynFlags
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FilePath
"Network.Gitit.Plugin." forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
pluginName)
      forall a b. (a -> b) -> a -> b
$ do
#if __GLASGOW_HASKELL__ >= 904
          addTarget =<< guessTarget pluginName Nothing Nothing
#else
          forall (m :: * -> *). GhcMonad m => Target -> m ()
addTarget forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: * -> *).
GhcMonad m =>
FilePath -> Maybe Phase -> m Target
guessTarget FilePath
pluginName forall a. Maybe a
Nothing
#endif
          SuccessFlag
r <- forall (m :: * -> *). GhcMonad m => LoadHowMuch -> m SuccessFlag
load LoadHowMuch
LoadAllTargets
          case SuccessFlag
r of
            SuccessFlag
Failed -> forall a. HasCallStack => FilePath -> a
error forall a b. (a -> b) -> a -> b
$ FilePath
"Error loading plugin: " forall a. [a] -> [a] -> [a]
++ FilePath
pluginName
            SuccessFlag
Succeeded -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
    let modName :: FilePath
modName =
          if FilePath
"Network.Gitit.Plugin" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
pluginName
             then FilePath
pluginName
             else if FilePath
"Network/Gitit/Plugin/" forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` FilePath
pluginName
                     then FilePath
"Network.Gitit.Plugin." forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
takeBaseName FilePath
pluginName
                     else FilePath -> FilePath
takeBaseName FilePath
pluginName
    ImportDecl GhcPs
pr <- forall (m :: * -> *).
GhcMonad m =>
FilePath -> m (ImportDecl GhcPs)
parseImportDecl FilePath
"import Prelude"
    ImportDecl GhcPs
i <- forall (m :: * -> *).
GhcMonad m =>
FilePath -> m (ImportDecl GhcPs)
parseImportDecl FilePath
"import Network.Gitit.Interface"
    ImportDecl GhcPs
m <- forall (m :: * -> *).
GhcMonad m =>
FilePath -> m (ImportDecl GhcPs)
parseImportDecl (FilePath
"import " forall a. [a] -> [a] -> [a]
++ FilePath
modName)
    forall (m :: * -> *). GhcMonad m => [InteractiveImport] -> m ()
setContext [ImportDecl GhcPs -> InteractiveImport
IIDecl ImportDecl GhcPs
m, ImportDecl GhcPs -> InteractiveImport
IIDecl  ImportDecl GhcPs
i, ImportDecl GhcPs -> InteractiveImport
IIDecl ImportDecl GhcPs
pr]
    HValue
value <- forall (m :: * -> *). GhcMonad m => FilePath -> m HValue
compileExpr (FilePath
modName forall a. [a] -> [a] -> [a]
++ FilePath
".plugin :: Plugin")
    let value' :: Plugin
value' = (forall a b. a -> b
unsafeCoerce HValue
value) :: Plugin
    forall (m :: * -> *) a. Monad m => a -> m a
return Plugin
value'

#else

loadPlugin :: FilePath -> IO Plugin
loadPlugin pluginName = do
  error $ "Cannot load plugin '" ++ pluginName ++
          "'. gitit was not compiled with plugin support."
  return undefined

#endif

loadPlugins :: [FilePath] -> IO [Plugin]
loadPlugins :: [FilePath] -> IO [Plugin]
loadPlugins [FilePath]
pluginNames = do
  [Plugin]
plugins' <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FilePath -> IO Plugin
loadPlugin [FilePath]
pluginNames
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
pluginNames) forall a b. (a -> b) -> a -> b
$ FilePath -> Priority -> FilePath -> IO ()
logM FilePath
"gitit" Priority
WARNING FilePath
"Finished loading plugins."
  forall (m :: * -> *) a. Monad m => a -> m a
return [Plugin]
plugins'