From 3a636804fa549e3d8b557d5c623d32d697bb7abc Mon Sep 17 00:00:00 2001 From: Gary Burgess Date: Mon, 24 Apr 2017 20:48:22 +0100 Subject: [PATCH 1/4] Update to and for PureScript 0.11 --- bower.json | 4 +- package.json | 23 +-- src/GulpPurescript/ChildProcess.purs | 4 +- src/GulpPurescript/Glob.purs | 4 +- src/GulpPurescript/Logalot.purs | 4 +- src/GulpPurescript/OS.purs | 35 +++-- src/GulpPurescript/Options.purs | 224 +++++++++++++-------------- src/GulpPurescript/Plugin.purs | 53 ++++--- src/GulpPurescript/ResolveBin.purs | 4 +- src/GulpPurescript/Stream.purs | 8 +- src/GulpPurescript/Which.purs | 4 +- test/test.js | 4 +- 12 files changed, 184 insertions(+), 187 deletions(-) diff --git a/bower.json b/bower.json index 95baee1..4f93e5e 100644 --- a/bower.json +++ b/bower.json @@ -2,7 +2,7 @@ "name": "gulp-purescript", "private": true, "dependencies": { - "purescript-aff": "~0.17.0", - "purescript-foreign": "~1.0.0" + "purescript-aff": "~3.0.0", + "purescript-foreign": "~4.0.0" } } diff --git a/package.json b/package.json index d930dd7..bd9f4fd 100644 --- a/package.json +++ b/package.json @@ -17,29 +17,30 @@ "output" ], "scripts": { - "psc": "psc 'src/**/*.purs' 'bower_components/purescript-*/src/**/*.purs'", + "psc": "purs compile 'src/**/*.purs' 'bower_components/purescript-*/src/**/*.purs'", "test": "npm run psc && (node test/test.js | tap-spec)", - "prepublish": "rm -r output && npm run psc" + "prepublish": "rimraf output && npm run psc" }, "keywords": [ "gulpplugin", "purescript" ], "dependencies": { - "async": "^2.0.0-rc.5", - "camelcase": "^3.0.0", - "cross-spawn": "^4.0.0", - "glob": "^7.0.3", - "gulp-util": "^3.0.7", + "async": "^2.3.0", + "camelcase": "^4.1.0", + "cross-spawn": "^5.1.0", + "glob": "^7.1.1", + "gulp-util": "^3.0.8", "logalot": "^2.1.0", "resolve-bin": "^0.4.0", - "which": "^1.2.9" + "which": "^1.2.14" }, "devDependencies": { "gulp": "^3.9.1", - "purescript": "^0.9.1-rc.1", + "purescript": "^0.11.4", + "rimraf": "^2.6.1", "tap-spec": "^4.1.1", - "tape": "^4.5.1", - "through2": "^2.0.1" + "tape": "^4.6.3", + "through2": "^2.0.3" } } diff --git a/src/GulpPurescript/ChildProcess.purs b/src/GulpPurescript/ChildProcess.purs index df85a79..3838fb2 100644 --- a/src/GulpPurescript/ChildProcess.purs +++ b/src/GulpPurescript/ChildProcess.purs @@ -6,12 +6,12 @@ module GulpPurescript.ChildProcess import Prelude import Control.Monad.Aff (Aff, makeAff) -import Control.Monad.Eff (Eff) +import Control.Monad.Eff (Eff, kind Effect) import Control.Monad.Eff.Exception (Error) import Data.Function.Uncurried (Fn4, runFn4) -foreign import data ChildProcess :: ! +foreign import data ChildProcess :: Effect spawn :: forall eff. String -> Array String -> Aff (cp :: ChildProcess | eff) String spawn command args = makeAff $ runFn4 spawnFn command args diff --git a/src/GulpPurescript/Glob.purs b/src/GulpPurescript/Glob.purs index 06be943..6de7694 100644 --- a/src/GulpPurescript/Glob.purs +++ b/src/GulpPurescript/Glob.purs @@ -7,12 +7,12 @@ module GulpPurescript.Glob import Prelude (Unit, ($)) import Control.Monad.Aff (Aff, makeAff) -import Control.Monad.Eff (Eff) +import Control.Monad.Eff (Eff, kind Effect) import Control.Monad.Eff.Exception (Error) import Data.Function.Uncurried (Fn3, runFn3) -foreign import data Glob :: ! +foreign import data Glob :: Effect glob :: forall eff. String -> Aff (glob :: Glob | eff) (Array String) glob pattern = makeAff $ runFn3 globFn pattern diff --git a/src/GulpPurescript/Logalot.purs b/src/GulpPurescript/Logalot.purs index c2144bc..585e081 100644 --- a/src/GulpPurescript/Logalot.purs +++ b/src/GulpPurescript/Logalot.purs @@ -5,8 +5,8 @@ module GulpPurescript.Logalot import Prelude (Unit) -import Control.Monad.Eff (Eff) +import Control.Monad.Eff (Eff, kind Effect) -foreign import data Logalot :: ! +foreign import data Logalot :: Effect foreign import info :: forall eff. String -> Eff (logalot :: Logalot | eff) Unit diff --git a/src/GulpPurescript/OS.purs b/src/GulpPurescript/OS.purs index c7e6deb..b4064ae 100644 --- a/src/GulpPurescript/OS.purs +++ b/src/GulpPurescript/OS.purs @@ -4,34 +4,35 @@ module GulpPurescript.OS , platform ) where -import Prelude (class Show, (<$>), (<>), const) +import Prelude -import Control.Monad.Eff (Eff) +import Control.Monad.Eff (Eff, kind Effect) import Control.Monad.Eff.Exception.Unsafe (unsafeThrow) +import Control.Monad.Except (runExcept) import Data.Either (either) -import Data.Foreign (Foreign) -import Data.Foreign.Class (class IsForeign, read) +import Data.Foreign (F, Foreign, readString) import Data.Maybe (Maybe(..)) -foreign import data OS :: ! +foreign import data OS :: Effect data Platform = Darwin | Linux | Win32 instance showPlatform :: Show Platform where - show a = case a of - Darwin -> "darwin" - Linux -> "linux" - Win32 -> "win32" - -instance isForeignPlatform :: IsForeign Platform where - read a = (\a -> case a of - "darwin" -> Darwin - "linux" -> Linux - "win32" -> Win32 - _ -> unsafeThrow ("Unhandled platform: " <> a)) <$> read a + show = case _ of + Darwin -> "darwin" + Linux -> "linux" + Win32 -> "win32" + +readPlatform :: Foreign -> F Platform +readPlatform = + readString >=> case _ of + "darwin" -> pure Darwin + "linux" -> pure Linux + "win32" -> pure Win32 + a -> unsafeThrow ("Unhandled platform: " <> a) platform :: forall eff. Eff (os :: OS | eff) (Maybe Platform) -platform = either (const Nothing) Just <$> read <$> platformFn +platform = either (const Nothing) Just <$> runExcept <$> readPlatform <$> platformFn foreign import platformFn :: forall eff. Eff (os :: OS | eff) Foreign diff --git a/src/GulpPurescript/Options.purs b/src/GulpPurescript/Options.purs index 8cb4123..6677d2e 100644 --- a/src/GulpPurescript/Options.purs +++ b/src/GulpPurescript/Options.purs @@ -3,20 +3,21 @@ module GulpPurescript.Options , pscOptions , pscBundleOptions , pscDocsOptions + , readPsci ) where -import Prelude ((<>), (<$>), (<*>), (<<<), ($), (>>=), bind, const, id, pure) +import Prelude import Control.Alt ((<|>)) +import Control.Monad.Except (runExcept) import Data.Array (concat, singleton) import Data.Either (Either(..), either) -import Data.Foreign (Foreign, ForeignError(TypeMismatch), F) -import Data.Foreign.Class (class IsForeign, read, readProp) +import Data.Foreign (F, Foreign, ForeignError(..), fail, readArray, readBoolean, readNullOrUndefined, readString) +import Data.Foreign.Index (readProp) import Data.Foreign.Keys (keys) -import Data.Foreign.NullOrUndefined (NullOrUndefined(..), unNullOrUndefined) import Data.Maybe (Maybe(..), fromMaybe, maybe) -import Data.Traversable (for) +import Data.Traversable (for, traverse) srcKey :: String srcKey = "src" @@ -107,29 +108,29 @@ docgenKey = docgenOpt newtype Psc = Psc { src :: Either String (Array String) - , output :: NullOrUndefined String - , noTco :: NullOrUndefined Boolean - , noMagicDo :: NullOrUndefined Boolean - , noOpts :: NullOrUndefined Boolean - , verboseErrors :: NullOrUndefined Boolean - , comments :: NullOrUndefined Boolean - , noPrefix :: NullOrUndefined Boolean - , sourceMaps :: NullOrUndefined Boolean - , jsonErrors :: NullOrUndefined Boolean + , output :: Maybe String + , noTco :: Maybe Boolean + , noMagicDo :: Maybe Boolean + , noOpts :: Maybe Boolean + , verboseErrors :: Maybe Boolean + , comments :: Maybe Boolean + , noPrefix :: Maybe Boolean + , sourceMaps :: Maybe Boolean + , jsonErrors :: Maybe Boolean } newtype PscBundle = PscBundle { src :: Either String (Array String) - , output :: NullOrUndefined String - , "module" :: NullOrUndefined (Either String (Array String)) - , main :: NullOrUndefined (Either Boolean String) - , namespace :: NullOrUndefined String + , output :: Maybe String + , "module" :: Maybe (Either String (Array String)) + , main :: Maybe (Either Boolean String) + , namespace :: Maybe String } newtype PscDocs = PscDocs { src :: Either String (Array String) - , format :: NullOrUndefined Format - , docgen :: NullOrUndefined Docgen + , format :: Maybe Format + , docgen :: Maybe Docgen } newtype Psci @@ -141,121 +142,103 @@ newtype PathArray = PathArray (Array String) data Format = Markdown | ETags | CTags -instance isForeignPsc :: IsForeign Psc where - read obj = - Psc <$> ({ src: _ - , output: _ - , noTco: _ - , noMagicDo: _ - , noOpts: _ - , verboseErrors: _ - , comments: _ - , noPrefix: _ - , sourceMaps: _ - , jsonErrors: _ - } <$> (readProp srcKey obj >>= readEither) - <*> readProp outputKey obj - <*> readProp noTcoKey obj - <*> readProp noMagicDoKey obj - <*> readProp noOptsKey obj - <*> readProp verboseErrorsKey obj - <*> readProp commentsKey obj - <*> readProp noPrefixKey obj - <*> readProp sourceMapsKey obj - <*> readProp jsonErrorsKey obj) - -instance isForeignPscBundle :: IsForeign PscBundle where - read obj = - PscBundle <$> ({ src: _ - , output: _ - , "module": _ - , main: _ - , namespace: _ - } <$> (readProp srcKey obj >>= readEither) - <*> readProp outputKey obj - <*> (readProp moduleKey obj >>= readEitherNU) - <*> (readProp mainKey obj >>= readEitherNU) - <*> readProp namespaceKey obj) - -instance isForeignPscDocs :: IsForeign PscDocs where - read obj = - PscDocs <$> ({ src: _ - , format: _ - , docgen: _ - } <$> (readProp srcKey obj >>= readEither) - <*> readProp formatKey obj - <*> readProp docgenOpt obj) - -instance isForeignPsci :: IsForeign Psci where - read obj = Psci <$> ({ src: _ } <$> (readProp srcKey obj >>= readEither)) - -instance isForeignPathArray :: IsForeign PathArray where - read val = PathArray <$> read val - -instance isForeignDocgen :: IsForeign Docgen where - read val = Docgen <$> read val - -instance isForeignFormat :: IsForeign Format where - read val = read val >>= (\a -> case a of - "markdown" -> Right Markdown - "etags" -> Right ETags - "ctags" -> Right CTags - b -> Left $ TypeMismatch "Format" b) +readPsc :: Foreign -> F Psc +readPsc obj = do + src <- readSources =<< readProp srcKey obj + output <- readPropNU readString outputKey obj + noTco <- readPropNU readBoolean noTcoKey obj + noMagicDo <- readPropNU readBoolean noMagicDoKey obj + noOpts <- readPropNU readBoolean noOptsKey obj + verboseErrors <- readPropNU readBoolean verboseErrorsKey obj + comments <- readPropNU readBoolean commentsKey obj + noPrefix <- readPropNU readBoolean noPrefixKey obj + sourceMaps <- readPropNU readBoolean sourceMapsKey obj + jsonErrors <- readPropNU readBoolean jsonErrorsKey obj + pure $ Psc { src, output, noTco, noMagicDo, noOpts, verboseErrors, comments, noPrefix, sourceMaps, jsonErrors } + +readPscBundle :: Foreign -> F PscBundle +readPscBundle obj = do + src <- readSources =<< readProp srcKey obj + output <- readPropNU readString outputKey obj + mod <- readPropNU readSources moduleKey obj + main <- readPropNU (readEither readBoolean readString) mainKey obj + namespace <- readPropNU readString namespaceKey obj + pure $ PscBundle { src, output, "module": mod, main, namespace } + +readPscDocs :: Foreign -> F PscDocs +readPscDocs obj = do + src <- readSources =<< readProp srcKey obj + format <- readPropNU readFormat formatKey obj + docgen <- readPropNU readDocgen docgenOpt obj + pure $ PscDocs { src, format, docgen } + +readPsci :: Foreign -> F Psci +readPsci obj = Psci <$> { src: _ } <$> (readSources =<< readProp srcKey obj) + +readPathArray :: Foreign -> F PathArray +readPathArray = map PathArray <<< traverse readString <=< readArray + +readDocgen :: Foreign -> F Docgen +readDocgen = pure <<< Docgen + +readFormat :: Foreign -> F Format +readFormat = readString >=> case _ of + "markdown" -> pure Markdown + "etags" -> pure ETags + "ctags" -> pure CTags + b -> fail $ TypeMismatch "Format" b class CommandLineOption a where - opt :: String -> NullOrUndefined a -> Array String + opt :: String -> Maybe a -> Array String instance commandLineOptionBoolean :: CommandLineOption Boolean where - opt key val = maybe [] (\a -> if a then ["--" <> key] else []) (unNullOrUndefined val) + opt key = maybe [] (\a -> if a then ["--" <> key] else []) instance commandLineOptionString :: CommandLineOption String where - opt key val = maybe [] (\a -> ["--" <> key <> "=" <> a]) (unNullOrUndefined val) + opt key = maybe [] (\a -> ["--" <> key <> "=" <> a]) instance commandLineOptionEither :: (CommandLineOption a, CommandLineOption b) => CommandLineOption (Either a b) where - opt key val = maybe [] (either (\a -> opt key (NullOrUndefined $ Just a)) - (\a -> opt key (NullOrUndefined $ Just a))) - (unNullOrUndefined val) + opt key = maybe [] (either (opt key <<< Just) (opt key <<< Just)) instance commandLineOptionArray :: (CommandLineOption a) => CommandLineOption (Array a) where - opt key val = concat $ opt key <$> (NullOrUndefined <<< Just) - <$> (fromMaybe [] $ unNullOrUndefined val) + opt key val = concat $ opt key <$> Just <$> (fromMaybe [] val) instance commandLineOptionPathArray :: CommandLineOption PathArray where - opt key val = opt key (NullOrUndefined ((\(PathArray a) -> a >>= expandGlob) <$> (unNullOrUndefined val))) + opt key = opt key <<< map \(PathArray a) -> a >>= expandGlob instance commandLineOptionDocgen :: CommandLineOption Docgen where - opt key val = opt key (NullOrUndefined (parseDocgen <$> (unNullOrUndefined val))) + opt key = opt key <<< map parseDocgen + +instance commandLineOptionFormat :: CommandLineOption Format where + opt key = opt key <<< map case _ of + Markdown -> "markdown" + ETags -> "etags" + CTags -> "ctags" parseDocgen :: Docgen -> Array String -parseDocgen (Docgen obj) = either (const []) id $ parseName obj - <|> parseList obj - <|> parseObj obj - <|> pure [] +parseDocgen (Docgen obj) = + either (const []) id $ runExcept + $ parseName obj + <|> parseList obj + <|> parseObj obj + <|> pure [] where parseName :: Foreign -> F (Array String) - parseName obj = singleton <$> read obj + parseName = map singleton <<< readString parseList :: Foreign -> F (Array String) - parseList obj = read obj + parseList = traverse readString <=< readArray parseObj :: Foreign -> F (Array String) - parseObj obj = do - modules <- keys obj - for modules \m -> (\f -> m <> ":" <> f) <$> readProp m obj + parseObj obj' = do + modules <- keys obj' + for modules \m -> (\f -> m <> ":" <> f) <$> (readString =<< readProp m obj') -instance commandLineOptionFormat :: CommandLineOption Format where - opt key val = opt key (maybe (NullOrUndefined Nothing) - (\a -> case a of - Markdown -> NullOrUndefined (Just "markdown") - ETags -> NullOrUndefined (Just "etags") - CTags -> NullOrUndefined (Just "ctags")) - (unNullOrUndefined val)) - -pscOptions :: Foreign -> Either ForeignError (Array String) +pscOptions :: Foreign -> F (Array String) pscOptions opts = fold <$> parsed where parsed :: F Psc - parsed = read opts + parsed = readPsc opts fold :: Psc -> Array String fold (Psc a) = either pure id a.src <> @@ -269,11 +252,11 @@ pscOptions opts = fold <$> parsed opt sourceMapsOpt a.sourceMaps <> opt jsonErrorsOpt a.jsonErrors -pscBundleOptions :: Foreign -> Either ForeignError (Array String) +pscBundleOptions :: Foreign -> F (Array String) pscBundleOptions opts = fold <$> parsed where parsed :: F PscBundle - parsed = read opts + parsed = readPscBundle opts fold :: PscBundle -> Array String fold (PscBundle a) = either pure id a.src <> @@ -282,23 +265,28 @@ pscBundleOptions opts = fold <$> parsed opt mainOpt a.main <> opt namespaceOpt a.namespace -pscDocsOptions :: Foreign -> Either ForeignError (Array String) +pscDocsOptions :: Foreign -> F (Array String) pscDocsOptions opts = fold <$> parsed where parsed :: F PscDocs - parsed = read opts + parsed = readPscDocs opts fold :: PscDocs -> Array String fold (PscDocs a) = either pure id a.src <> opt formatOpt a.format <> opt docgenOpt a.docgen -readEither :: forall left right. (IsForeign left, IsForeign right) => Foreign -> F (Either left right) -readEither a = (Left <$> read a) <|> (Right <$> read a) +readEither :: forall left right. (Foreign -> F left) -> (Foreign -> F right) -> Foreign -> F (Either left right) +readEither readL readR a = (Left <$> readL a) <|> (Right <$> readR a) + +readEitherNU :: forall left right. (Foreign -> F left) -> (Foreign -> F right) -> Foreign -> F (Maybe (Either left right)) +readEitherNU readL readR = traverse (readEither readL readR) <=< readNullOrUndefined + +readPropNU :: forall a. (Foreign -> F a) -> String -> Foreign -> F (Maybe a) +readPropNU f k = traverse f <=< readNullOrUndefined <=< readProp k -readEitherNU :: forall left right. (IsForeign left, IsForeign right) => NullOrUndefined Foreign -> F (NullOrUndefined (Either left right)) -readEitherNU a @ (NullOrUndefined Nothing) = pure (NullOrUndefined Nothing) -readEitherNU (NullOrUndefined (Just a)) = (NullOrUndefined <<< Just) <$> readEither a +readSources :: Foreign -> F (Either String (Array String)) +readSources = readEither readString (traverse readString <=< readArray) foreign import expandGlob :: String -> (Array String) diff --git a/src/GulpPurescript/Plugin.purs b/src/GulpPurescript/Plugin.purs index 7cb9516..96d5d80 100644 --- a/src/GulpPurescript/Plugin.purs +++ b/src/GulpPurescript/Plugin.purs @@ -8,30 +8,31 @@ module GulpPurescript.Plugin , psci ) where -import Prelude (Unit, ($), (<>), (<$>), (<*>), (<<<), (>>=), (+), bind, const, id, pure, show, unit) +import Prelude import Control.Monad.Aff (Aff) import Control.Monad.Eff (Eff) import Control.Monad.Eff.Class (liftEff) import Control.Monad.Eff.Exception (Error) import Control.Monad.Error.Class (catchError, throwError) +import Control.Monad.Except (runExcept) import Data.Array as Array +import Data.Bifunctor (lmap) import Data.Either (either) -import Data.Foreign (Foreign) -import Data.Foreign.Class (read) +import Data.Foreign (F, Foreign, renderForeignError) +import Data.List.NonEmpty as NEL import Data.Maybe (Maybe(Just)) import Data.String (joinWith, null) import Data.Tuple (Tuple(..)) -import Data.Tuple.Nested (tuple2) import GulpPurescript.Buffer (mkBufferFromString) import GulpPurescript.ChildProcess (ChildProcess, spawn) import GulpPurescript.Glob (Glob, globAll) import GulpPurescript.GulpUtil (File, mkFile, mkPluginError) import GulpPurescript.Logalot (Logalot, info) +import GulpPurescript.Options (Psci(..), pscOptions, pscBundleOptions, pscDocsOptions, readPsci) import GulpPurescript.OS (OS, Platform(Win32), platform) -import GulpPurescript.Options (Psci(..), pscOptions, pscBundleOptions, pscDocsOptions) import GulpPurescript.Path (relative) import GulpPurescript.ResolveBin (ResolveBin, resolveBin) import GulpPurescript.Stream (Stream, ReadableStream, mkReadableStreamFromAff) @@ -76,14 +77,17 @@ psciLoadModuleCommand = ":m" psciLoadForeignCommand :: String psciLoadForeignCommand = ":f" -pscCommand :: String -pscCommand = "psc" +pursCommand :: String +pursCommand = "purs" -pscBundleCommand :: String -pscBundleCommand = "psc-bundle" +compileCommand :: String +compileCommand = "compile" -pscDocsCommand :: String -pscDocsCommand = "psc-docs" +bundleCommand :: String +bundleCommand = "bundle" + +docsCommand :: String +docsCommand = "docs" foreign import cwd :: String @@ -98,46 +102,46 @@ resolve cmd args = catchError primary fallback bin <- resolveBin pursPackage { executable: cmd } os <- liftEff platform pure $ case os of - Just Win32 -> tuple2 nodeCommand ([bin] <> args) - _ -> tuple2 bin args + Just Win32 -> Tuple nodeCommand ([bin] <> args) + _ -> Tuple bin args fallback :: Error -> Aff (Effects eff) (Tuple String (Array String)) - fallback _ = (const $ tuple2 cmd args) <$> catchError (which cmd) mapError + fallback _ = (const $ Tuple cmd args) <$> catchError (which cmd) mapError mapError :: Error -> Aff (Effects eff) String mapError _ = throwPluginError ("Failed to find " <> cmd <> ". " <> "Please ensure it is available on your system.") execute :: forall eff. String -> Array String -> Aff (Effects eff) String execute cmd args = do - Tuple cmd' args' <- resolve cmd args + Tuple cmd' args' <- resolve pursCommand ([cmd] <> args) result <- spawn cmd' args' pure result psc :: forall eff. Foreign -> Eff (Effects eff) (ReadableStream Unit) psc opts = mkReadableStreamFromAff $ do - output <- either (throwPluginError <<< show) - (execute pscCommand <<< (_ <> rtsOpts)) + output <- handleRead + (execute compileCommand <<< (_ <> rtsOpts)) (pscOptions opts) if null output then pure unit - else liftEff $ info $ pscCommand <> "\n" <> output + else liftEff $ info $ compileCommand <> "\n" <> output pscBundle :: forall eff. Foreign -> Eff (Effects eff) (ReadableStream File) -pscBundle opts = mkReadableStreamFromAff (either (throwPluginError <<< show) run (pscBundleOptions opts)) +pscBundle opts = mkReadableStreamFromAff (handleRead run (pscBundleOptions opts)) where run :: Array String -> Aff (Effects eff) File run args = mkFile "." <$> mkBufferFromString - <$> execute pscBundleCommand args + <$> execute bundleCommand args pscDocs :: forall eff. Foreign -> Eff (Effects eff) (ReadableStream File) -pscDocs opts = mkReadableStreamFromAff (either (throwPluginError <<< show) run (pscDocsOptions opts)) +pscDocs opts = mkReadableStreamFromAff (handleRead run (pscDocsOptions opts)) where run :: Array String -> Aff (Effects eff) File run args = mkFile "." <$> mkBufferFromString - <$> execute pscDocsCommand args + <$> execute docsCommand args psci :: forall eff. Foreign -> Eff (Effects eff) (ReadableStream File) -psci opts = mkReadableStreamFromAff (either (throwPluginError <<< show) run (read opts)) +psci opts = mkReadableStreamFromAff (handleRead run (readPsci opts)) where run :: Psci -> Aff (Effects eff) File run (Psci a) = do @@ -153,3 +157,6 @@ psci opts = mkReadableStreamFromAff (either (throwPluginError <<< show) run (rea loadForeign :: String -> String loadForeign a = psciLoadForeignCommand <> " " <> relative cwd a + +handleRead :: forall a b eff. (a -> Aff (Effects eff) b) -> F a -> Aff (Effects eff) b +handleRead r = either (throwPluginError <<< renderForeignError) r <<< lmap NEL.head <<< runExcept diff --git a/src/GulpPurescript/ResolveBin.purs b/src/GulpPurescript/ResolveBin.purs index 9e43d29..ffe9091 100644 --- a/src/GulpPurescript/ResolveBin.purs +++ b/src/GulpPurescript/ResolveBin.purs @@ -7,12 +7,12 @@ module GulpPurescript.ResolveBin import Prelude (Unit, ($)) import Control.Monad.Aff (Aff, makeAff) -import Control.Monad.Eff (Eff) +import Control.Monad.Eff (Eff, kind Effect) import Control.Monad.Eff.Exception (Error) import Data.Function.Uncurried (Fn4, runFn4) -foreign import data ResolveBin :: ! +foreign import data ResolveBin :: Effect type Options = { executable :: String } diff --git a/src/GulpPurescript/Stream.purs b/src/GulpPurescript/Stream.purs index ba8997a..2aa23ea 100644 --- a/src/GulpPurescript/Stream.purs +++ b/src/GulpPurescript/Stream.purs @@ -4,22 +4,22 @@ module GulpPurescript.Stream , mkReadableStreamFromAff ) where -import Prelude (Unit) +import Prelude import Control.Monad.Aff (Aff, runAff) -import Control.Monad.Eff (Eff) +import Control.Monad.Eff (Eff, kind Effect) import Control.Monad.Eff.Exception (Error) import Data.Function.Uncurried (Fn2, runFn2) -foreign import data Stream :: ! +foreign import data Stream :: Effect data ReadableStream out type RunAff eff a = (Error -> Eff eff Unit) -> (a -> Eff eff Unit) -> Aff eff a -> Eff eff Unit mkReadableStreamFromAff :: forall eff1 eff2 out. Aff eff1 out -> Eff (stream :: Stream | eff2) (ReadableStream out) -mkReadableStreamFromAff = runFn2 mkReadableStreamFromAffFn runAff +mkReadableStreamFromAff = runFn2 mkReadableStreamFromAffFn \x y z -> void (runAff x y z) foreign import mkReadableStreamFromAffFn :: forall eff1 eff2 out. Fn2 (RunAff eff1 out) (Aff eff1 out) diff --git a/src/GulpPurescript/Which.purs b/src/GulpPurescript/Which.purs index b2ce1e1..0298946 100644 --- a/src/GulpPurescript/Which.purs +++ b/src/GulpPurescript/Which.purs @@ -6,12 +6,12 @@ module GulpPurescript.Which import Prelude (Unit, ($)) import Control.Monad.Aff (Aff, makeAff) -import Control.Monad.Eff (Eff) +import Control.Monad.Eff (Eff, kind Effect) import Control.Monad.Eff.Exception (Error) import Data.Function.Uncurried (Fn3, runFn3) -foreign import data Which :: ! +foreign import data Which :: Effect which :: forall eff. String -> Aff (which :: Which | eff) String which cmd = makeAff $ runFn3 whichFn cmd diff --git a/test/test.js b/test/test.js index 2c9cb15..09377eb 100644 --- a/test/test.js +++ b/test/test.js @@ -45,8 +45,8 @@ test('psc - invalid option type', function(t){ var stream = purescript.psc({src: 10}); stream.on('error', function(e){ - t.ok(/type mismatch/i.test(error.message), 'should have a failure message'); - t.equal(error.name, 'Error'); + t.ok(/type mismatch/i.test(e.message), 'should have a failure message'); + t.equal(e.name, 'Error'); }); } catch (error) { From a3ff9049a41a1137c74f7eedafdbe6315e3714eb Mon Sep 17 00:00:00 2001 From: Gary Burgess Date: Tue, 25 Apr 2017 00:56:22 +0100 Subject: [PATCH 2/4] Update compiler options --- README.md | 34 +++++++++++++--------------- src/GulpPurescript/Options.purs | 39 +++++++++++++++------------------ src/GulpPurescript/Plugin.purs | 2 +- 3 files changed, 34 insertions(+), 41 deletions(-) diff --git a/README.md b/README.md index 4db7b6b..79ed491 100644 --- a/README.md +++ b/README.md @@ -34,7 +34,7 @@ There is also [a more complete example](#full-example) that makes use of all the Refer to the PureScript [compiler usage](https://github.com/purescript/purescript/wiki/Language-Guide:-Getting-Started#compiler-usage) section of the Github wiki for additional details on the behaviour of each option below. -Options can be passed to the Haskell runtime system for `psc` by passing a `--psc-rts-flags` argument to `gulp`. Any values that follow this flag will be passed through to the runtime. There is no need to include `+RTS`/`-RTS` options as these are inserted automatically. See [the GHC documentation](https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/runtime-control.html#rts-opts-cmdline) for information on the available RTS options. +Options can be passed to the Haskell runtime system for `purs` by passing a `--purs-rts-flags` argument to `gulp`. Any values that follow this flag will be passed through to the runtime. There is no need to include `+RTS`/`-RTS` options as these are inserted automatically. See [the GHC documentation](https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/runtime-control.html#rts-opts-cmdline) for information on the available RTS options. ### `purescript.psc(options)` @@ -44,17 +44,9 @@ Invokes the `psc` command. The following options are supported. Files to compile. Glob syntax is supported. -###### `noTco` (Boolean) - -Toggles `--no-tco` that disables tail-call optimizations. - -###### `noMagicDo` (Boolean) - -Toggles `--no-magic-do` that disables optimizations overloading the do keyword generating efficient code for the `Eff` monad. - -###### `noOpts` (Boolean) +###### `output` (String) -Toggles `--no-opts` that skips the optimization phase. +Sets `--output=` the specifies the output directory, `output` by default. ###### `verboseErrors` (Boolean) @@ -64,17 +56,17 @@ Toggles `--verbose-errors` that displays verbose error messages. Toggles `--comments` that includes comments in generated code. -###### `output` (String) +###### `sourceMaps` (Boolean) -Sets `--output=` the specifies the output directory, `output` by default. +Toggles `--source-maps` that generates source maps. -###### `noPrefix` (Boolean) +###### `dumpCoreFn` (Boolean) -Toggles `--no-prefix` that does not include the comment header. +Toggles `--dump-corefn` that generates dumps the (functional) core representation of the compiled code at `output/*/corefn.json`. -###### `sourceMaps` (Boolean) +###### `noPrefix` (Boolean) -Toggles `--source-maps` that generates source maps. +Toggles `--no-prefix` that does not include the comment header. ###### `jsonErrors` (Boolean) @@ -82,7 +74,7 @@ Toggles `--json-errors` that prints errors to stderr as JSON. ### `purescript.pscBundle(options)` -Invokes the `psc-bundle` command. The following options are supported. +Invokes the `purs compile` command. The following options are supported. ###### `src` (String or String Array) @@ -104,9 +96,13 @@ Toggles `--main` or sets `--main=` that generates code to run the `main` Sets `--namespace=` that specifies the namespace that PureScript modules will be exported to when running in the browser. +###### `sourceMaps` (Boolean) + +Toggles `--source-maps` that generates source maps. + ### `purescript.pscDocs(options)` -Invokes the `psc-docs` command. The following options are supported. +Invokes the `purs docs` command. The following options are supported. ###### `src` (String or String Array) diff --git a/src/GulpPurescript/Options.purs b/src/GulpPurescript/Options.purs index 6677d2e..7d985bb 100644 --- a/src/GulpPurescript/Options.purs +++ b/src/GulpPurescript/Options.purs @@ -34,12 +34,6 @@ noMagicDoOpt = "no-magic-do" noMagicDoKey :: String noMagicDoKey = camelcaseFn noMagicDoOpt -noTcoOpt :: String -noTcoOpt = "no-tco" - -noTcoKey :: String -noTcoKey = camelcaseFn noTcoOpt - verboseErrorsOpt :: String verboseErrorsOpt = "verbose-errors" @@ -76,6 +70,12 @@ sourceMapsOpt = "source-maps" sourceMapsKey :: String sourceMapsKey = camelcaseFn sourceMapsOpt +dumpCoreFnOpt :: String +dumpCoreFnOpt = "dump-corefn" + +dumpCoreFnKey :: String +dumpCoreFnKey = "dumpCoreFn" + jsonErrorsOpt :: String jsonErrorsOpt = "json-errors" @@ -109,13 +109,11 @@ docgenKey = docgenOpt newtype Psc = Psc { src :: Either String (Array String) , output :: Maybe String - , noTco :: Maybe Boolean - , noMagicDo :: Maybe Boolean - , noOpts :: Maybe Boolean , verboseErrors :: Maybe Boolean , comments :: Maybe Boolean - , noPrefix :: Maybe Boolean , sourceMaps :: Maybe Boolean + , dumpCoreFn :: Maybe Boolean + , noPrefix :: Maybe Boolean , jsonErrors :: Maybe Boolean } @@ -125,6 +123,7 @@ newtype PscBundle , "module" :: Maybe (Either String (Array String)) , main :: Maybe (Either Boolean String) , namespace :: Maybe String + , sourceMaps :: Maybe Boolean } newtype PscDocs @@ -146,15 +145,13 @@ readPsc :: Foreign -> F Psc readPsc obj = do src <- readSources =<< readProp srcKey obj output <- readPropNU readString outputKey obj - noTco <- readPropNU readBoolean noTcoKey obj - noMagicDo <- readPropNU readBoolean noMagicDoKey obj - noOpts <- readPropNU readBoolean noOptsKey obj verboseErrors <- readPropNU readBoolean verboseErrorsKey obj comments <- readPropNU readBoolean commentsKey obj - noPrefix <- readPropNU readBoolean noPrefixKey obj sourceMaps <- readPropNU readBoolean sourceMapsKey obj + dumpCoreFn <- readPropNU readBoolean dumpCoreFnKey obj + noPrefix <- readPropNU readBoolean noPrefixKey obj jsonErrors <- readPropNU readBoolean jsonErrorsKey obj - pure $ Psc { src, output, noTco, noMagicDo, noOpts, verboseErrors, comments, noPrefix, sourceMaps, jsonErrors } + pure $ Psc { src, output, verboseErrors, comments, sourceMaps, dumpCoreFn, noPrefix, jsonErrors } readPscBundle :: Foreign -> F PscBundle readPscBundle obj = do @@ -163,7 +160,8 @@ readPscBundle obj = do mod <- readPropNU readSources moduleKey obj main <- readPropNU (readEither readBoolean readString) mainKey obj namespace <- readPropNU readString namespaceKey obj - pure $ PscBundle { src, output, "module": mod, main, namespace } + sourceMaps <- readPropNU readBoolean sourceMapsKey obj + pure $ PscBundle { src, output, "module": mod, main, namespace, sourceMaps } readPscDocs :: Foreign -> F PscDocs readPscDocs obj = do @@ -243,13 +241,11 @@ pscOptions opts = fold <$> parsed fold :: Psc -> Array String fold (Psc a) = either pure id a.src <> opt outputOpt a.output <> - opt noTcoOpt a.noTco <> - opt noMagicDoOpt a.noMagicDo <> - opt noOptsOpt a.noOpts <> opt verboseErrorsOpt a.verboseErrors <> opt commentsOpt a.comments <> - opt noPrefixOpt a.noPrefix <> opt sourceMapsOpt a.sourceMaps <> + opt dumpCoreFnOpt a.dumpCoreFn <> + opt noPrefixOpt a.noPrefix <> opt jsonErrorsOpt a.jsonErrors pscBundleOptions :: Foreign -> F (Array String) @@ -263,7 +259,8 @@ pscBundleOptions opts = fold <$> parsed opt outputOpt a.output <> opt moduleOpt a."module" <> opt mainOpt a.main <> - opt namespaceOpt a.namespace + opt namespaceOpt a.namespace <> + opt sourceMapsOpt a.sourceMaps pscDocsOptions :: Foreign -> F (Array String) pscDocsOptions opts = fold <$> parsed diff --git a/src/GulpPurescript/Plugin.purs b/src/GulpPurescript/Plugin.purs index 96d5d80..6f75bcc 100644 --- a/src/GulpPurescript/Plugin.purs +++ b/src/GulpPurescript/Plugin.purs @@ -42,7 +42,7 @@ foreign import argv :: Array String rtsOpts :: Array String rtsOpts = - let startIndex = Array.elemIndex "--psc-rts-flags" argv + let startIndex = Array.elemIndex "--purs-rts-flags" argv in case startIndex of Just i -> ["+RTS"] <> Array.drop (i + 1) argv <> ["-RTS"] _ -> [] From d461594620c9a7b8c9808b115a3c01a3f794d4ff Mon Sep 17 00:00:00 2001 From: Gary Burgess Date: Tue, 25 Apr 2017 00:57:55 +0100 Subject: [PATCH 3/4] Add travis build --- .travis.yml | 10 ++++++++++ 1 file changed, 10 insertions(+) create mode 100644 .travis.yml diff --git a/.travis.yml b/.travis.yml new file mode 100644 index 0000000..3290d8a --- /dev/null +++ b/.travis.yml @@ -0,0 +1,10 @@ +language: node_js +dist: trusty +sudo: required +node_js: stable +install: + - npm install -g bower + - bower install + - npm install +script: + - npm run -s test From dbb8ce770c36ab52509c990c1987242bf179999b Mon Sep 17 00:00:00 2001 From: Gary Burgess Date: Tue, 25 Apr 2017 01:11:58 +0100 Subject: [PATCH 4/4] Update task names to reflect purs commands --- README.md | 24 +++++------ index.js | 18 ++++---- package.json | 6 +-- src/GulpPurescript/Options.purs | 75 ++++++++++++++++----------------- src/GulpPurescript/Plugin.purs | 22 +++++----- test/test.js | 18 ++++---- 6 files changed, 80 insertions(+), 83 deletions(-) diff --git a/README.md b/README.md index 79ed491..33e6f22 100644 --- a/README.md +++ b/README.md @@ -21,8 +21,8 @@ var gulp = require('gulp'); var purescript = require('gulp-purescript'); -gulp.task('psc', function(){ - return purescript.psc({ +gulp.task('make', function(){ + return purescript.compile({ src: 'src/*.purs' }); }); @@ -36,9 +36,9 @@ Refer to the PureScript [compiler usage](https://github.com/purescript/purescrip Options can be passed to the Haskell runtime system for `purs` by passing a `--purs-rts-flags` argument to `gulp`. Any values that follow this flag will be passed through to the runtime. There is no need to include `+RTS`/`-RTS` options as these are inserted automatically. See [the GHC documentation](https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/runtime-control.html#rts-opts-cmdline) for information on the available RTS options. -### `purescript.psc(options)` +### `purescript.compile(options)` -Invokes the `psc` command. The following options are supported. +Invokes the `purs compile` command. The following options are supported. ###### `src` (String or String Array) @@ -72,13 +72,13 @@ Toggles `--no-prefix` that does not include the comment header. Toggles `--json-errors` that prints errors to stderr as JSON. -### `purescript.pscBundle(options)` +### `purescript.bundle(options)` -Invokes the `purs compile` command. The following options are supported. +Invokes the `purs bundle` command. The following options are supported. ###### `src` (String or String Array) -The `psc`-produced JavaScript source files to bundle. Glob syntax is supported. +The `purs compile`-produced JavaScript source files to bundle. Glob syntax is supported. ###### `output` (String) @@ -100,7 +100,7 @@ Sets `--namespace=` that specifies the namespace that PureScript modules Toggles `--source-maps` that generates source maps. -### `purescript.pscDocs(options)` +### `purescript.docs(options)` Invokes the `purs docs` command. The following options are supported. @@ -143,15 +143,15 @@ var sources = [ ]; gulp.task("make", function () { - return purescript.psc({ src: sources }); + return purescript.compile({ src: sources }); }); gulp.task("bundle", ["make"], function () { - return purescript.pscBundle({ src: "output/**/*.js", output: "dist/bundle.js" }); + return purescript.bundle({ src: "output/**/*.js", output: "dist/bundle.js" }); }); gulp.task("docs", function () { - return purescript.pscDocs({ + return purescript.docs({ src: sources, docgen: { "Name.Of.Module1": "docs/Name/Of/Module1.md", @@ -166,7 +166,7 @@ gulp.task("dotpsci", function () { }); gulp.task("test", ["make"], function() { - return purescript.pscBundle({ src: "output/**/*.js", main: "Test.Main" }) + return purescript.bundle({ src: "output/**/*.js", main: "Test.Main" }) .pipe(run("node")); }); diff --git a/index.js b/index.js index e64d945..a07f981 100644 --- a/index.js +++ b/index.js @@ -2,26 +2,26 @@ var gulpPurescript = require('./output/GulpPurescript.Plugin'); -function psc(options) { - return gulpPurescript.psc(options)(); +function compile(options) { + return gulpPurescript.compile(options)(); } -function pscBundle(options) { - return gulpPurescript.pscBundle(options)(); +function bundle(options) { + return gulpPurescript.bundle(options)(); } -function pscDocs(options) { - return gulpPurescript.pscDocs(options)(); +function docs(options) { + return gulpPurescript.docs(options)(); } function psci(options) { return gulpPurescript.psci(options)(); } -module.exports.psc = psc; +module.exports.compile = compile; -module.exports.pscBundle = pscBundle; +module.exports.bundle = bundle; -module.exports.pscDocs = pscDocs; +module.exports.docs = docs; module.exports.psci = psci; diff --git a/package.json b/package.json index bd9f4fd..03a499d 100644 --- a/package.json +++ b/package.json @@ -17,9 +17,9 @@ "output" ], "scripts": { - "psc": "purs compile 'src/**/*.purs' 'bower_components/purescript-*/src/**/*.purs'", - "test": "npm run psc && (node test/test.js | tap-spec)", - "prepublish": "rimraf output && npm run psc" + "build": "purs compile 'src/**/*.purs' 'bower_components/purescript-*/src/**/*.purs'", + "test": "npm run build && (node test/test.js | tap-spec)", + "prepublish": "rimraf output && npm run build" }, "keywords": [ "gulpplugin", diff --git a/src/GulpPurescript/Options.purs b/src/GulpPurescript/Options.purs index 7d985bb..e180b63 100644 --- a/src/GulpPurescript/Options.purs +++ b/src/GulpPurescript/Options.purs @@ -1,8 +1,8 @@ module GulpPurescript.Options ( Psci(..) - , pscOptions - , pscBundleOptions - , pscDocsOptions + , compileOptions + , bundleOptions + , docsOptions , readPsci ) where @@ -106,8 +106,8 @@ docgenOpt = "docgen" docgenKey :: String docgenKey = docgenOpt -newtype Psc - = Psc { src :: Either String (Array String) +newtype Compile + = Compile { src :: Either String (Array String) , output :: Maybe String , verboseErrors :: Maybe Boolean , comments :: Maybe Boolean @@ -117,8 +117,8 @@ newtype Psc , jsonErrors :: Maybe Boolean } -newtype PscBundle - = PscBundle { src :: Either String (Array String) +newtype Bundle + = Bundle { src :: Either String (Array String) , output :: Maybe String , "module" :: Maybe (Either String (Array String)) , main :: Maybe (Either Boolean String) @@ -126,8 +126,8 @@ newtype PscBundle , sourceMaps :: Maybe Boolean } -newtype PscDocs - = PscDocs { src :: Either String (Array String) +newtype Docs + = Docs { src :: Either String (Array String) , format :: Maybe Format , docgen :: Maybe Docgen } @@ -141,8 +141,8 @@ newtype PathArray = PathArray (Array String) data Format = Markdown | ETags | CTags -readPsc :: Foreign -> F Psc -readPsc obj = do +readCompile :: Foreign -> F Compile +readCompile obj = do src <- readSources =<< readProp srcKey obj output <- readPropNU readString outputKey obj verboseErrors <- readPropNU readBoolean verboseErrorsKey obj @@ -151,24 +151,24 @@ readPsc obj = do dumpCoreFn <- readPropNU readBoolean dumpCoreFnKey obj noPrefix <- readPropNU readBoolean noPrefixKey obj jsonErrors <- readPropNU readBoolean jsonErrorsKey obj - pure $ Psc { src, output, verboseErrors, comments, sourceMaps, dumpCoreFn, noPrefix, jsonErrors } + pure $ Compile { src, output, verboseErrors, comments, sourceMaps, dumpCoreFn, noPrefix, jsonErrors } -readPscBundle :: Foreign -> F PscBundle -readPscBundle obj = do +readBundle :: Foreign -> F Bundle +readBundle obj = do src <- readSources =<< readProp srcKey obj output <- readPropNU readString outputKey obj mod <- readPropNU readSources moduleKey obj main <- readPropNU (readEither readBoolean readString) mainKey obj namespace <- readPropNU readString namespaceKey obj sourceMaps <- readPropNU readBoolean sourceMapsKey obj - pure $ PscBundle { src, output, "module": mod, main, namespace, sourceMaps } + pure $ Bundle { src, output, "module": mod, main, namespace, sourceMaps } -readPscDocs :: Foreign -> F PscDocs -readPscDocs obj = do +readDocs :: Foreign -> F Docs +readDocs obj = do src <- readSources =<< readProp srcKey obj format <- readPropNU readFormat formatKey obj docgen <- readPropNU readDocgen docgenOpt obj - pure $ PscDocs { src, format, docgen } + pure $ Docs { src, format, docgen } readPsci :: Foreign -> F Psci readPsci obj = Psci <$> { src: _ } <$> (readSources =<< readProp srcKey obj) @@ -232,14 +232,14 @@ parseDocgen (Docgen obj) = modules <- keys obj' for modules \m -> (\f -> m <> ":" <> f) <$> (readString =<< readProp m obj') -pscOptions :: Foreign -> F (Array String) -pscOptions opts = fold <$> parsed +compileOptions :: Foreign -> F (Array String) +compileOptions opts = fold <$> parsed where - parsed :: F Psc - parsed = readPsc opts + parsed :: F Compile + parsed = readCompile opts - fold :: Psc -> Array String - fold (Psc a) = either pure id a.src <> + fold :: Compile -> Array String + fold (Compile a) = either pure id a.src <> opt outputOpt a.output <> opt verboseErrorsOpt a.verboseErrors <> opt commentsOpt a.comments <> @@ -248,37 +248,34 @@ pscOptions opts = fold <$> parsed opt noPrefixOpt a.noPrefix <> opt jsonErrorsOpt a.jsonErrors -pscBundleOptions :: Foreign -> F (Array String) -pscBundleOptions opts = fold <$> parsed +bundleOptions :: Foreign -> F (Array String) +bundleOptions opts = fold <$> parsed where - parsed :: F PscBundle - parsed = readPscBundle opts + parsed :: F Bundle + parsed = readBundle opts - fold :: PscBundle -> Array String - fold (PscBundle a) = either pure id a.src <> + fold :: Bundle -> Array String + fold (Bundle a) = either pure id a.src <> opt outputOpt a.output <> opt moduleOpt a."module" <> opt mainOpt a.main <> opt namespaceOpt a.namespace <> opt sourceMapsOpt a.sourceMaps -pscDocsOptions :: Foreign -> F (Array String) -pscDocsOptions opts = fold <$> parsed +docsOptions :: Foreign -> F (Array String) +docsOptions opts = fold <$> parsed where - parsed :: F PscDocs - parsed = readPscDocs opts + parsed :: F Docs + parsed = readDocs opts - fold :: PscDocs -> Array String - fold (PscDocs a) = either pure id a.src <> + fold :: Docs -> Array String + fold (Docs a) = either pure id a.src <> opt formatOpt a.format <> opt docgenOpt a.docgen readEither :: forall left right. (Foreign -> F left) -> (Foreign -> F right) -> Foreign -> F (Either left right) readEither readL readR a = (Left <$> readL a) <|> (Right <$> readR a) -readEitherNU :: forall left right. (Foreign -> F left) -> (Foreign -> F right) -> Foreign -> F (Maybe (Either left right)) -readEitherNU readL readR = traverse (readEither readL readR) <=< readNullOrUndefined - readPropNU :: forall a. (Foreign -> F a) -> String -> Foreign -> F (Maybe a) readPropNU f k = traverse f <=< readNullOrUndefined <=< readProp k diff --git a/src/GulpPurescript/Plugin.purs b/src/GulpPurescript/Plugin.purs index 6f75bcc..8c4a80e 100644 --- a/src/GulpPurescript/Plugin.purs +++ b/src/GulpPurescript/Plugin.purs @@ -2,9 +2,9 @@ module GulpPurescript.Plugin ( Effects , Errorback , Callback - , psc - , pscBundle - , pscDocs + , compile + , bundle + , docs , psci ) where @@ -31,7 +31,7 @@ import GulpPurescript.ChildProcess (ChildProcess, spawn) import GulpPurescript.Glob (Glob, globAll) import GulpPurescript.GulpUtil (File, mkFile, mkPluginError) import GulpPurescript.Logalot (Logalot, info) -import GulpPurescript.Options (Psci(..), pscOptions, pscBundleOptions, pscDocsOptions, readPsci) +import GulpPurescript.Options (Psci(..), compileOptions, bundleOptions, docsOptions, readPsci) import GulpPurescript.OS (OS, Platform(Win32), platform) import GulpPurescript.Path (relative) import GulpPurescript.ResolveBin (ResolveBin, resolveBin) @@ -117,24 +117,24 @@ execute cmd args = do result <- spawn cmd' args' pure result -psc :: forall eff. Foreign -> Eff (Effects eff) (ReadableStream Unit) -psc opts = mkReadableStreamFromAff $ do +compile :: forall eff. Foreign -> Eff (Effects eff) (ReadableStream Unit) +compile opts = mkReadableStreamFromAff $ do output <- handleRead (execute compileCommand <<< (_ <> rtsOpts)) - (pscOptions opts) + (compileOptions opts) if null output then pure unit else liftEff $ info $ compileCommand <> "\n" <> output -pscBundle :: forall eff. Foreign -> Eff (Effects eff) (ReadableStream File) -pscBundle opts = mkReadableStreamFromAff (handleRead run (pscBundleOptions opts)) +bundle :: forall eff. Foreign -> Eff (Effects eff) (ReadableStream File) +bundle opts = mkReadableStreamFromAff (handleRead run (bundleOptions opts)) where run :: Array String -> Aff (Effects eff) File run args = mkFile "." <$> mkBufferFromString <$> execute bundleCommand args -pscDocs :: forall eff. Foreign -> Eff (Effects eff) (ReadableStream File) -pscDocs opts = mkReadableStreamFromAff (handleRead run (pscDocsOptions opts)) +docs :: forall eff. Foreign -> Eff (Effects eff) (ReadableStream File) +docs opts = mkReadableStreamFromAff (handleRead run (docsOptions opts)) where run :: Array String -> Aff (Effects eff) File run args = mkFile "." <$> mkBufferFromString diff --git a/test/test.js b/test/test.js index 09377eb..3567809 100644 --- a/test/test.js +++ b/test/test.js @@ -12,12 +12,12 @@ var through2 = require('through2'); var purescript = require('../'); -test('psc - basic', function(t){ +test('compile - basic', function(t){ t.plan(1); var fixture = './test/Fixture1.purs'; - var stream = purescript.psc({src: fixture}); + var stream = purescript.compile({src: fixture}); stream.pipe(through2.obj(function(chunk, encoding, callback){ t.pass('should output a compiled result'); @@ -25,12 +25,12 @@ test('psc - basic', function(t){ })); }); -test('psc - error', function(t){ +test('compile - error', function(t){ t.plan(2); var fixture = './test/Fixture2.purs'; - var stream = purescript.psc({src: fixture}); + var stream = purescript.compile({src: fixture}); stream.on('error', function(e){ t.ok(/"where"/.test(e.message), 'should have a failure message'); @@ -38,11 +38,11 @@ test('psc - error', function(t){ }); }); -test('psc - invalid option type', function(t){ +test('compile - invalid option type', function(t){ t.plan(2); try { - var stream = purescript.psc({src: 10}); + var stream = purescript.compile({src: 10}); stream.on('error', function(e){ t.ok(/type mismatch/i.test(e.message), 'should have a failure message'); @@ -55,15 +55,15 @@ test('psc - invalid option type', function(t){ } }); -test('psc-bundle - basic', function(t){ +test('bundle - basic', function(t){ t.plan(1); var fixture = './test/foreign.js'; - var stream = purescript.pscBundle({src: fixture}); + var stream = purescript.bundle({src: fixture}); stream.pipe(through2.obj(function(chunk, encoding, callback){ - t.ok(/psc-bundle/.test(chunk.contents.toString()), 'should have a compiled result'); + t.ok(/bundle/.test(chunk.contents.toString()), 'should have a compiled result'); callback(); })); });