{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
module Snap.Snaplet.PureScript.Internal (
CompilationMode(..)
, CompilationOutput(..)
, Verbosity(..)
, PulpPath(getPulpPath)
, PureScript(..)
, devFlagEnabled
, getCompilationFlavour
, getDestDir
, getBowerFile
, getAbsoluteOutputDir
, prependToPath
, findOrInstallPulp
, shV
, shS
) where
import Control.Exception (SomeException)
import Control.Monad.IO.Class
import Control.Monad.Reader
import Data.Configurator as Cfg
import Data.Configurator.Types
import Data.Maybe
import Data.String
import Data.String.Conv
import qualified Data.Text as T
import Shelly ( run, run_, echo, fromText, errExit, catchany_sh, verbosely, lastExitCode, Sh, setenv
, get_env_text, shelly, escaping, toTextWarn, silently
)
import qualified Shelly as Sh
import Snap
import Snap.Snaplet.PureScript.Hooks (Hooks)
import Text.Read hiding (String)
data CompilationMode = CompileOnce
| CompileAlways
| CompileNever
deriving (Show, Eq, Read)
instance Configured CompilationMode where
convert (String t) = readMaybe . T.unpack $ t
convert _ = Nothing
newtype PulpPath = PulpPath { getPulpPath :: FilePath } deriving (Show, Read)
instance Configured PulpPath where
convert (String "") = Nothing
convert (String t) = Just . PulpPath . toS $ t
convert _ = Nothing
data Verbosity = Verbose
| Quiet
deriving (Show, Read, Eq)
instance Configured Verbosity where
convert (String t) = readMaybe . T.unpack $ t
convert _ = Nothing
data CompilationOutput = CompilationFailed !T.Text
| CompilationSucceeded
deriving (Show, Ord, Eq)
data PureScript = PureScript {
pursCompilationMode :: CompilationMode
, pursVerbosity :: Verbosity
, pursBundle :: !Bool
, pursBundleName :: !T.Text
, pursBundleExe :: !T.Text
, pursBundleOpts :: ![T.Text]
, pursPulpPath :: !PulpPath
, pursPsPath :: !T.Text
, pursPsaOpts :: [T.Text]
, pursPermissiveInit :: !Bool
, pursPwdDir :: !T.Text
, pursOutputDir :: !T.Text
, pursModules :: ![T.Text]
, pursHooks :: Hooks
} deriving Show
devFlagEnabled :: Bool
devFlagEnabled =
#ifdef DEVELOPMENT
True
#else
False
#endif
shS :: MonadIO m => Sh a -> m a
shS = liftIO . shelly . silently . escaping False
shV :: MonadIO m => Sh a -> m a
shV = liftIO . shelly . verbosely . escaping False
findOrInstallPulp :: T.Text
-> Maybe PulpPath
-> (Monad (m b v), MonadIO (m b v), MonadSnaplet m)
=> m b v PulpPath
findOrInstallPulp psPath mbP = do
let p = fromMaybe (PulpPath "pulp") mbP
installed <- shS (pulpInstalled psPath p)
case installed of
True -> return p
False -> shS $ do
echo "Pulp not found, installing it locally for you..."
installPulp >> whichPulp
whichPulp :: MonadIO m => m PulpPath
whichPulp = PulpPath . toS . T.strip <$> shS (run "which" ["pulp"])
prependToPath :: Sh.FilePath -> Sh ()
prependToPath fp = do
tp <- toTextWarn fp
pe <- get_env_text "PATH"
setenv "PATH" $ tp <> T.singleton ':' <> pe
installPulp :: MonadIO m => m ()
installPulp = shS $ run_ "npm" ["install", "pulp"]
pulpInstalled :: T.Text -> PulpPath -> Sh Bool
pulpInstalled psPath (PulpPath pp) = errExit False $ verbosely $ do
check `catchany_sh` \(e :: SomeException) -> do
echo (toS . show $ e)
return False
where
check = do
prependToPath (fromText psPath)
run_ (fromString pp) ["--version"]
eC <- lastExitCode
return $ case eC of
0 -> True
1 -> True
_ -> False
getCompilationFlavour :: Initializer b v CompilationMode
getCompilationFlavour = do
cfg <- getSnapletUserConfig
cm <- liftIO (Cfg.lookup cfg "compilationMode")
case cm of
Just c -> return c
Nothing -> do
inDevelMode <- ("devel" ==) <$> getEnvironment
return $ if inDevelMode || devFlagEnabled
then CompileAlways
else CompileOnce
getDestDir :: (Monad (m b v), MonadIO (m b v), MonadSnaplet m) => m b v T.Text
getDestDir = do
fp <- getSnapletFilePath
return $ T.pack fp
getBowerFile :: (Monad (m b v), MonadIO (m b v), MonadSnaplet m) => m b v T.Text
getBowerFile = (`mappend` "/bower.json") <$> getDestDir
getAbsoluteOutputDir :: Handler b PureScript T.Text
getAbsoluteOutputDir = do
wDir <- asks pursPwdDir
oDir <- asks pursOutputDir
return $ wDir <> "/" <> oDir