Skip to content

Commit

Permalink
Merge pull request #45 from kRITZCREEK/0.12-build
Browse files Browse the repository at this point in the history
Changes to build with 0.12 libs
  • Loading branch information
nwolverson committed Aug 12, 2018
2 parents fa949b6 + d741b78 commit b499c05
Show file tree
Hide file tree
Showing 7 changed files with 52 additions and 59 deletions.
6 changes: 3 additions & 3 deletions .travis.yml
Original file line number Diff line number Diff line change
@@ -1,13 +1,13 @@
language: node_js
dist: trusty
sudo: required
node_js: 6
node_js: 8
env:
- PATH=$HOME/purescript:$PATH
install:
- wget -O $HOME/purescript.tar.gz https://github.com/purescript/purescript/releases/download/v0.11.7/linux64.tar.gz
- wget -O $HOME/purescript.tar.gz https://github.com/purescript/purescript/releases/download/v0.12.0/linux64.tar.gz
- tar -xvf $HOME/purescript.tar.gz -C $HOME/
- chmod a+x $HOME/purescript
- npm install -g psc-package pulp
- npm install -g psc-package-bin-simple pulp
script:
- psc-package install && pulp --psc-package build
2 changes: 1 addition & 1 deletion psc-package.json
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{
"set": "psc-0.11.7",
"set": "psc-0.12.0-20180803",
"depends": [
"console",
"argonaut",
Expand Down
18 changes: 8 additions & 10 deletions src/Node/Which.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,25 +2,23 @@ module Node.Which (which, which') where

import Prelude

import Control.Monad.Aff (Aff, makeAff, nonCanceler)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Exception (Error)
import Data.Either (Either(..))
import Data.Maybe (Maybe(Nothing))
import Data.Nullable (toNullable, Nullable)
import Node.FS (FS)
import Effect (Effect)
import Effect.Aff (Aff, Error, makeAff, nonCanceler)

foreign import whichImpl :: forall eff.
foreign import whichImpl ::
{ path :: Nullable String, pathExt :: Nullable String} ->
String ->
(Error -> Eff (fs :: FS | eff) Unit) ->
((Array String) -> Eff (fs :: FS | eff) Unit) ->
Eff (fs :: FS | eff) Unit
(Error -> Effect Unit) ->
((Array String) -> Effect Unit) ->
Effect Unit

which :: forall eff. String -> Aff (fs :: FS | eff) (Array String)
which :: String -> Aff (Array String)
which s = makeAff \ cb -> nonCanceler <$
whichImpl { path: toNullable Nothing, pathExt: toNullable Nothing } s (cb <<< Left) (cb <<< Right)

which' :: forall eff. { path :: Maybe String, pathExt :: Maybe String } -> String -> Aff (fs :: FS | eff) (Array String)
which' :: { path :: Maybe String, pathExt :: Maybe String } -> String -> Aff (Array String)
which' { path, pathExt } s = makeAff \ cb -> nonCanceler <$
whichImpl { path: toNullable path, pathExt: toNullable pathExt } s (cb <<< Left) (cb <<< Right)
29 changes: 13 additions & 16 deletions src/PscIde.purs
Original file line number Diff line number Diff line change
Expand Up @@ -4,36 +4,33 @@ import PscIde.Command

import Control.Alt ((<$), (<|>))
import Control.Bind (join)
import Control.Monad.Aff (Aff, makeAff, nonCanceler)
import Control.Monad.Eff (Eff, kind Effect)
import Control.Monad.Eff.Exception (Error)
import Data.Argonaut (class DecodeJson, class EncodeJson, encodeJson)
import Data.Argonaut (class DecodeJson, class EncodeJson, encodeJson, stringify)
import Data.Either (Either(..))
import Data.Maybe (Maybe(..))
import Prelude (Unit, pure, show, (<$>), (>>>))
import Effect (Effect)
import Effect.Aff (Aff, makeAff, nonCanceler)
import Effect.Exception (Error)
import Prelude (Unit, pure, (<$>), (>>>))

foreign import data NET :: Effect

foreign import send
:: forall eff.
foreign import send ::
String -- ^ Command
-> Int -- ^ Port
-> (String -> Eff (net :: NET | eff) Unit) -- ^ Callback
-> (Error -> Eff (net :: NET | eff) Unit) -- ^ Error Callback
-> Eff (net :: NET | eff) Unit
-> (String -> Effect Unit) -- ^ Callback
-> (Error -> Effect Unit) -- ^ Error Callback
-> Effect Unit

type Cmd a = forall eff. Aff (net :: NET | eff) (Result a)
type CmdR a b = forall eff. Aff (net :: NET | eff) (Result (Either a b))
type Cmd a = Aff (Result a)
type CmdR a b = Aff (Result (Either a b))

sendCommandR :: forall i oe o. EncodeJson i => DecodeJson oe => DecodeJson o => Int -> i -> CmdR oe o
sendCommandR port command =
makeAff \cb -> nonCanceler <$
send (show (encodeJson command)) port (unwrapResponse >>> Right >>> cb) (Left >>> cb)
send (stringify (encodeJson command)) port (unwrapResponse >>> Right >>> cb) (Left >>> cb)

sendCommand :: forall i o. EncodeJson i => DecodeJson o => Int -> i -> Cmd o
sendCommand port command =
makeAff \cb -> nonCanceler <$
send (show (encodeJson command)) port (unwrapResponse >>> join >>> Right >>> cb) (Left >>> cb)
send (stringify (encodeJson command)) port (unwrapResponse >>> join >>> Right >>> cb) (Left >>> cb)

cwd :: Int -> Cmd Message
cwd port = sendCommand port Cwd
Expand Down
7 changes: 4 additions & 3 deletions src/PscIde/Command.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module PscIde.Command where
import Prelude

import Control.Alt ((<|>))
import Data.Argonaut (JObject, getField)
import Data.Argonaut (getField)
import Data.Argonaut.Core (jsonEmptyObject, jsonSingletonObject, jsonNull, fromString, Json, toString)
import Data.Argonaut.Decode (class DecodeJson, decodeJson, (.?))
import Data.Argonaut.Encode (class EncodeJson, encodeJson, (~>), (:=))
Expand All @@ -12,6 +12,7 @@ import Data.Array (singleton)
import Data.Either (Either(..), either, hush)
import Data.Maybe (Maybe(..), maybe)
import Data.String (joinWith)
import Foreign.Object (Object)

data PursuitType = Package | Ident

Expand Down Expand Up @@ -302,10 +303,10 @@ instance decodeTypeInfo :: DecodeJson TypeInfo where
expandedType <- o `getFieldMaybe` "expandedType"
documentation <- o `getFieldMaybe` "documentation"
-- TODO: Handling both missing/incorrect exportedFrom. Remove this after 0.12
exportedFrom <- Right $ either (const []) id $ getField o "exportedFrom"
exportedFrom <- Right $ either (const []) identity $ getField o "exportedFrom"
pure (TypeInfo { identifier, type', module', definedAt, expandedType, documentation, exportedFrom })
where
getFieldMaybe :: forall a. (DecodeJson a) => JObject -> String -> Either String (Maybe a)
getFieldMaybe :: forall a. (DecodeJson a) => Object Json -> String -> Either String (Maybe a)
getFieldMaybe o f = Right $ either (const Nothing) Just $ getField o f

instance decodeTypePosition :: DecodeJson TypePosition where
Expand Down
8 changes: 4 additions & 4 deletions src/PscIde/Project.purs
Original file line number Diff line number Diff line change
@@ -1,15 +1,15 @@
module PscIde.Project where

import Prelude
import Node.Path as NP
import Control.Monad.Eff (Eff)

import Data.Maybe (Maybe(..))
import Data.String (Pattern(..), contains)
import Node.FS (FS) as FS
import Effect (Effect)
import Node.FS.Sync (exists) as FS
import Node.Path as NP

-- | Get PureScript project root given a .purs file (identified by presence of bower.json)
getRoot :: forall eff'. NP.FilePath -> Eff (fs :: FS.FS | eff') (Maybe NP.FilePath)
getRoot :: NP.FilePath -> Effect (Maybe NP.FilePath)
getRoot path =
let parent = getParent path
bower = NP.concat [path, "bower.json"]
Expand Down
41 changes: 19 additions & 22 deletions src/PscIde/Server.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,29 +3,26 @@ module PscIde.Server where
import Prelude

import Control.Alt ((<|>))
import Control.Monad.Aff (Aff, attempt, delay, makeAff, nonCanceler, sequential)
import Control.Monad.Aff.AVar (AVAR)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Exception (EXCEPTION, catchException)
import Control.Monad.Eff.Random (RANDOM, randomInt)
import Control.Parallel.Class (parallel)
import Control.Parallel.Class (parallel, sequential)
import Data.Either (Either(..), either)
import Data.Int (fromNumber)
import Data.Maybe (Maybe(Just, Nothing), maybe)
import Data.StrMap (StrMap)
import Data.Time.Duration (Milliseconds(..))
import Data.Traversable (for)
import Effect (Effect)
import Effect.Aff (Aff, attempt, delay, makeAff, nonCanceler)
import Effect.Class (liftEffect)
import Effect.Exception (catchException)
import Effect.Random (randomInt)
import Foreign.Object (Object)
import Global (readInt)
import Node.Buffer (BUFFER)
import Node.Buffer as Buffer
import Node.ChildProcess (CHILD_PROCESS, ChildProcess, StdIOBehaviour, Exit(Normally), onClose, onError, defaultSpawnOptions, spawn, defaultExecOptions, execFile, pipe)
import Node.ChildProcess (ChildProcess, StdIOBehaviour, Exit(..), onClose, onError, defaultSpawnOptions, spawn, defaultExecOptions, execFile, pipe)
import Node.Encoding (Encoding(UTF8))
import Node.FS (FS)
import Node.FS.Sync (readTextFile, unlink, writeTextFile)
import Node.Path as Path
import Node.Which (which')
import PscIde (NET, quit)
import PscIde (quit)

data ServerStartResult =
Started ChildProcess
Expand Down Expand Up @@ -75,9 +72,9 @@ defaultServerArgs = {
}

-- | Start a psc-ide server instance
startServer forall eff. PscIdeServerArgs Aff (cp CHILD_PROCESS, avar AVAR | eff) ServerStartResult
startServer PscIdeServerArgs Aff ServerStartResult
startServer { stdio, exe, combinedExe, cwd, source, port, directory, outputDirectory, watch, debug, polling, editorMode, logLevel } = do
cp <- liftEff (spawn exe (
cp <- liftEffect (spawn exe (
(if combinedExe then ["ide", "server"] else []) <>
(maybe [] (\p -> ["-p", show p]) port) <>
(maybe [] (\d -> ["-d", d]) directory) <>
Expand Down Expand Up @@ -109,39 +106,39 @@ portFilePath :: String -> String
portFilePath cwd = Path.concat [ cwd, ".psc-ide-port" ]

-- | Save a port to the port file
savePort :: forall eff. Int String Eff (fs :: FS, exception :: EXCEPTION | eff) Unit
savePort :: Int String Effect Unit
savePort port cwd = writeTextFile UTF8 (portFilePath cwd) (show port)

-- | Delete the port file
deleteSavedPort :: forall eff. String Eff (fs :: FS, exception :: EXCEPTION | eff) Unit
deleteSavedPort :: String Effect Unit
deleteSavedPort cwd = unlink (portFilePath cwd)

-- | Get the saved port for the given project directory (if present)
getSavedPort :: forall eff. String Eff (fs :: FS | eff) (Maybe Int)
getSavedPort :: String Effect (Maybe Int)
getSavedPort cwd = do
text <- catchException (\_ -> pure Nothing) (Just <$> readTextFile UTF8 (portFilePath cwd))
pure $ maybe Nothing (fromNumber <<< readInt 10) text

-- | Generate a fresh port (just now, randomly with no check or retry)
pickFreshPort :: forall eff. Eff (random :: RANDOM | eff) Int
pickFreshPort :: Effect Int
pickFreshPort = randomInt 15000 16000

-- | Stop a psc-ide server.
stopServer :: forall eff. Int -> Aff (cp :: CHILD_PROCESS, net :: NET | eff) Unit
stopServer :: Int -> Aff Unit
stopServer port = void $ quit port

data Executable = Executable String (Maybe String)

findBins :: forall eff. String -> Aff (fs :: FS, buffer :: BUFFER, cp :: CHILD_PROCESS | eff) (Array Executable)
findBins :: String -> Aff (Array Executable)
findBins = findBins' { path: Nothing, pathExt: Nothing, env: Nothing }

findBins' :: forall eff. { path :: Maybe String, pathExt :: Maybe String, env :: Maybe (StrMap String) } -> String -> Aff (fs :: FS, buffer :: BUFFER, cp :: CHILD_PROCESS | eff) (Array Executable)
findBins' :: { path :: Maybe String, pathExt :: Maybe String, env :: Maybe (Object String) } -> String -> Aff (Array Executable)
findBins' { path, pathExt, env } executable = do
bins <- which' { path, pathExt } executable <|> pure []
for bins \bin -> Executable bin <$> either (const Nothing) Just <$> attempt (getVersion bin)

where
getVersion :: forall eff'. String -> Aff (buffer :: BUFFER, cp :: CHILD_PROCESS | eff') String
getVersion :: String -> Aff String
getVersion bin = makeAff $ \cb -> nonCanceler <$
execFile bin ["--version"] (defaultExecOptions { env = env }) \({error, stdout}) -> do
maybe (Right <$> Buffer.readString UTF8 0 100 stdout >>= cb) (cb <<< Left) error

0 comments on commit b499c05

Please sign in to comment.