Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
29 changes: 23 additions & 6 deletions app/Command/Bundle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,10 +3,27 @@ module Command.Bundle (command, initSqlite) where

import Prelude

import Language.PureScript.Make.IdeCache (sqliteInit)
import Options.Applicative qualified as Opts
import System.Exit (exitFailure)
import System.IO (stderr, hPutStrLn)
import Options.Applicative qualified as Opts
import Language.PureScript.Make.IdeCache (sqliteInit)


data PublishOptionsCLI = PublishOptionsCLI
{ cliCompileOutputDir :: FilePath
}

compileOutputDir :: Opts.Parser FilePath
compileOutputDir = Opts.option Opts.auto $
Opts.value "output"
<> Opts.showDefault
<> Opts.long "compile-output"
<> Opts.metavar "DIR"
<> Opts.help "Compiler output directory"

cliOptions :: Opts.Parser PublishOptionsCLI
cliOptions =
PublishOptionsCLI <$> compileOutputDir

app :: IO ()
app = do
Expand All @@ -24,7 +41,7 @@ command = run <$> (Opts.helper <*> pure ()) where
run _ = app

initSqlite :: Opts.Parser (IO ())
initSqlite = run <$> (Opts.helper <*> pure ()) where
run :: () -> IO ()
run _ = do
sqliteInit "output"
initSqlite = run <$> (Opts.helper <*> cliOptions) where
run :: PublishOptionsCLI -> IO ()
run opts = do
sqliteInit opts.cliCompileOutputDir
2 changes: 1 addition & 1 deletion app/Command/Compile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ printWarningsAndErrors verbose True files warnings errors = do

compile :: PSCMakeOptions -> IO ()
compile PSCMakeOptions{..} = do
sqliteInit "output"
sqliteInit pscmOutputDir
input <- toInputGlobs $ PSCGlobs
{ pscInputGlobs = pscmInput
, pscInputGlobsFromFile = pscmInputFromFile
Expand Down
8 changes: 4 additions & 4 deletions app/Command/QuickBuild.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ import System.FilePath ((</>))
import System.IO (BufferMode(..), hClose, hFlush, hSetBuffering, hSetEncoding, utf8)
import System.IO.Error (isEOFError)
import Database.SQLite.Simple qualified as SQLite
import Language.PureScript.Options as PO
import Language.PureScript.Options as PO

listenOnLocalhost :: Network.PortNumber -> IO Network.Socket
listenOnLocalhost port = do
Expand Down Expand Up @@ -165,13 +165,13 @@ startServer fp'' env = do
runExceptT $ do
result <- handleCommand (RebuildSync fp Nothing (Set.fromList [PO.JS]))

-- liftIO $ BSL8.putStrLn $ Aeson.encode result
-- liftIO $ BSL8.putStrLn $ Aeson.encode result

return ()


return ()

loop :: (Ide m, MonadLogger m) => Network.Socket -> m ()
loop sock = do
accepted <- runExceptT (acceptCommand sock)
Expand Down
2 changes: 2 additions & 0 deletions src/Language/PureScript/Docs/Collect.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@ import Language.PureScript.Crash qualified as P
import Language.PureScript.Errors qualified as P
import Language.PureScript.Externs qualified as P
import Language.PureScript.Make qualified as P
import Language.PureScript.Make.IdeCache (sqliteInit)
import Language.PureScript.Names qualified as P
import Language.PureScript.Options qualified as P

Expand Down Expand Up @@ -89,6 +90,7 @@ compileForDocs ::
m [P.ExternsFile]
compileForDocs outputDir inputFiles = do
result <- liftIO $ do
sqliteInit outputDir
moduleFiles <- readUTF8FilesT inputFiles
fmap fst $ P.runMake testOptions $ do
ms <- P.parseModulesFromFiles identity moduleFiles
Expand Down
22 changes: 17 additions & 5 deletions src/Language/PureScript/Ide.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import Language.PureScript qualified as P
import Language.PureScript.Glob (toInputGlobs, PSCGlobs(..))
import Language.PureScript.Ide.CaseSplit qualified as CS
import Language.PureScript.Ide.Command (Command(..), ImportCommand(..), ListType(..))
import Language.PureScript.Ide.Completion (CompletionOptions (coMaxResults), completionFromMatch, getCompletions, getExactCompletions, simpleExport)
import Language.PureScript.Ide.Completion (CompletionOptions (coMaxResults), completionFromMatch, defaultCompletionOptions, getCompletions, getExactCompletions, simpleExport)
import Language.PureScript.Ide.Error (IdeError(..))
import Language.PureScript.Ide.Externs (readExternFile)
import Language.PureScript.Ide.Filter qualified as F
Expand Down Expand Up @@ -181,7 +181,7 @@ findDeclarations filters currentModule completionOptions = do
Just $ "id.namespace in (" <> T.intercalate "," (toList namespaces <&> \n -> "'" <> toText n <> "'") <> ")"
F.Filter (Right (F.DeclType dt)) ->
Just $ "id.namespace in (" <> T.intercalate "," (toList dt <&> \t -> "'" <> declarationTypeToText t <> "'") <> ")"
F.Filter (Right (F.Dependencies qualifier _ imports@(_:_))) ->
F.Filter (Right (F.Dependencies qualifier _ imports@(_:_))) ->
Just $ "(exists (select 1 from exports e where id.module_name = e.defined_in and id.name = e.name and id.declaration_type = e.declaration_type and e.module_name in "
<> moduleNames <> ") or id.module_name in" <> moduleNames <> ")"
where
Expand All @@ -197,9 +197,21 @@ findDeclarations filters currentModule completionOptions = do
) <>
foldMap (\maxResults -> " limit " <> show maxResults ) (coMaxResults =<< completionOptions)

let matches = rows <&> \(m, decl) -> (Match (ModuleName m, deserialise decl), [])

pure $ CompletionResult $ completionFromMatch <$> matches
-- Fallback to volatile state if SQLite returns no results
if null rows
then do
modules <- getAllModules currentModule
let insertPrim = Map.union idePrimDeclarations
-- Extract the search term from the filters
let searchTerm = case filters of
(F.Filter (Right (F.Exact term)) : _) -> term
(F.Filter (Right (F.Prefix term)) : _) -> term
_ -> ""
let results = getExactCompletions searchTerm filters (insertPrim modules)
pure (CompletionResult (take (fromMaybe 100 (coMaxResults =<< completionOptions)) results))
else do
let matches = rows <&> \(m, decl) -> (Match (ModuleName m, deserialise decl), [])
pure $ CompletionResult $ completionFromMatch <$> matches

sqliteFile :: Ide m => m FilePath
sqliteFile = outputDirectory <&> ( </> "cache.db")
Expand Down
24 changes: 13 additions & 11 deletions src/Language/PureScript/Ide/Imports/Actions.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Language.PureScript.Ide.Imports.Actions
module Language.PureScript.Ide.Imports.Actions
( addImplicitImport
, addQualifiedImport
, addImportForIdentifier
Expand Down Expand Up @@ -188,19 +188,21 @@ addImportForIdentifier fp ident qual filters' = do
Just $ "namespace in (" <> T.intercalate "," (toList dt <&> \t -> "'" <> declarationTypeToText t <> "'") <> ")"
F.Filter _ -> Nothing)
filters)

let declarations :: [Match IdeDeclaration] = rows <&> \(m, bs) -> Match (ModuleName m, discardAnn $ deserialise bs)



-- getExactMatches ident filters (addPrim modules)

modules <- getAllModules Nothing

-- let addPrim = Map.union idePrimDeclarations
-- Fallback to volatile state if SQLite returns no results (e.g., for Prim modules)
let declarations :: [Match IdeDeclaration] =
if null rows
then
let addPrim = Map.union idePrimDeclarations
in fmap discardAnn
<$> getExactMatches ident filters (addPrim modules)
else
rows <&> \(m, bs) -> Match (ModuleName m, discardAnn $ deserialise bs)

modules <- getAllModules Nothing
let
matches = declarations
matches = declarations
& filter (\(Match (_, d)) -> not (has _IdeDeclModule d))

case matches of
Expand Down Expand Up @@ -229,7 +231,7 @@ addImportForIdentifier fp ident qual filters' = do
-- worst
Just decl ->
Right <$> addExplicitImport fp decl m1 qual
-- Here we need the user to specify whether they wanted a
-- Here we need the user to specify whether they wanted a
-- dataconstructor or a type
Nothing ->
throwError (GeneralError "Undecidable between type and dataconstructor")
Expand Down
27 changes: 13 additions & 14 deletions src/Language/PureScript/Ide/Rebuild.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ import Language.PureScript.Ide.Types (Ide, IdeConfiguration(..), IdeEnvironment(
import Language.PureScript.Ide.Util (ideReadFile)
import System.Directory (getCurrentDirectory)
import Database.SQLite.Simple qualified as SQLite
import System.FilePath ((</>))
import System.FilePath ((</>), makeRelative)
import Data.Aeson (decode)
import Language.PureScript.Externs (ExternsFile(ExternsFile))
import Data.ByteString qualified as T
Expand All @@ -38,7 +38,6 @@ import Unsafe.Coerce (unsafeCoerce)
import Database.SQLite.Simple (Query(fromQuery), ToRow, SQLData (SQLText))
import Data.String (String)
import Codec.Serialise (deserialise)
import System.FilePath (makeRelative)

-- | Given a filepath performs the following steps:
--
Expand Down Expand Up @@ -248,34 +247,34 @@ sortExterns'
=> FilePath
-> P.Module
-> m [P.ExternsFile]
sortExterns' _ m = do
sortExterns' _ m = do
let P.Module _ _ _ declarations _ = m
let moduleDependencies = declarations >>= \case
P.ImportDeclaration _ importName _ _ -> [importName]
_ -> []

externs <- runQuery $ unlines [
"with recursive",
"graph(dependency, level) as (",
"graph(dependency, level) as (",
" select module_name , 1 as level",
" from modules where module_name in (" <> Data.Text.intercalate ", " (moduleDependencies <&> \v -> "'" <> runModuleName v <> "'") <> ")",
" from modules where module_name in (" <> Data.Text.intercalate ", " (moduleDependencies <&> \v -> "'" <> runModuleName v <> "'") <> ")",
" union ",
" select d.dependency as dep, graph.level + 1 as level",
" from graph join dependencies d on graph.dependency = d.module_name",
" select d.dependency as dep, graph.level + 1 as level",
" from graph join dependencies d on graph.dependency = d.module_name",
"),",
"topo as (",
" select dependency, max(level) as level",
" from graph group by dependency",
") ",
"topo as (",
" select dependency, max(level) as level",
" from graph group by dependency",
") ",
"select extern",
"from topo join modules on topo.dependency = modules.module_name order by level desc;"
]

pure $ (externs >>= identity) <&> deserialise
pure $ (externs >>= identity) <&> deserialise

-- !r <- SQLite.withConnection (outputDir </> "cache.db") \conn ->
-- !r <- SQLite.withConnection (outputDir </> "cache.db") \conn ->
-- SQLite.query conn query (SQLite.Only $ "[" <> Data.Text.intercalate ", " (dependencies <&> \v -> "\"" <> runModuleName v <> "\"") <> "]")
-- <&> \r -> (r >>= identity) <&> deserialise
-- <&> \r -> (r >>= identity) <&> deserialise
-- pure r

-- | Removes a modules export list.
Expand Down
3 changes: 2 additions & 1 deletion src/Language/PureScript/Make/Actions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ import System.Directory (getCurrentDirectory)
import System.FilePath ((</>), makeRelative, splitPath, normalise, splitDirectories)
import System.FilePath.Posix qualified as Posix
import System.IO (stderr)
import Language.PureScript.Make.IdeCache ( sqliteExtern)
import Language.PureScript.Make.IdeCache ( sqliteExtern, sqliteInit)

-- | Determines when to rebuild a module
data RebuildPolicy
Expand Down Expand Up @@ -290,6 +290,7 @@ buildMakeActions outputDir filePathMap foreigns usePrefix =
codegen ast m docs exts = do
let mn = CF.moduleName m
lift $ writeCborFile (outputFilename mn externsFileName) exts
lift $ sqliteInit outputDir
lift $ sqliteExtern outputDir ast exts
codegenTargets <- lift $ asks optionsCodegenTargets
when (S.member CoreFn codegenTargets) $ do
Expand Down
36 changes: 33 additions & 3 deletions src/Language/PureScript/Make/IdeCache.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,8 @@ import Language.PureScript.Ide.Types (Annotation(..), declarationType, IdeDeclar
import Language.PureScript.Docs.Types (Declaration(declChildren))
import Language.PureScript.Docs.AsMarkdown (declAsMarkdown, runDocs)
import Codec.Serialise (serialise)
import Language.PureScript.AST.Declarations (Module, Expr (Var), getModuleDeclarations, DeclarationRef (..), ExportSource (..))
import Language.PureScript.AST.Declarations (Module, Expr (Var, Constructor), getModuleDeclarations, DeclarationRef (..), ExportSource (..))
import Language.PureScript.AST.Binders (Binder (ConstructorBinder, OpBinder))
import Language.PureScript.Ide.Filter.Declaration (DeclarationType (..))
import Data.Aeson qualified as Aeson
import Language.PureScript.AST.Traversals (everywhereOnValuesM)
Expand All @@ -34,7 +35,7 @@ sqliteExtern outputDir m extern = liftIO $ do
SQLite.execute_ conn "pragma busy_timeout = 300000;"

let (doDecl, _, _) = everywhereOnValuesM (pure . identity) (\expr -> case expr of
Var ss i -> do
Var ss i -> do
let iv = disqualify i
case iv of
Ident t -> do
Expand All @@ -46,8 +47,37 @@ sqliteExtern outputDir m extern = liftIO $ do
]
_ -> pure ()
pure expr
Constructor ss qctor -> do
let ctor = disqualify qctor
SQLite.executeNamed conn
"insert into asts (module_name, name, span) values (:module_name, :name, :span)"
[ ":module_name" := runModuleName ( efModuleName extern )
, ":name" := runProperName ctor
, ":span" := Aeson.encode ss
]
pure expr
_ -> pure expr
) (pure . identity)
) (\binder -> case binder of
ConstructorBinder ss qctor _ -> do
let ctor = disqualify qctor
SQLite.executeNamed conn
"insert into asts (module_name, name, span) values (:module_name, :name, :span)"
[ ":module_name" := runModuleName ( efModuleName extern )
, ":name" := runProperName ctor
, ":span" := Aeson.encode ss
]
pure binder
OpBinder ss qop -> do
let op = disqualify qop
SQLite.executeNamed conn
"insert into asts (module_name, name, span) values (:module_name, :name, :span)"
[ ":module_name" := runModuleName ( efModuleName extern )
, ":name" := (\(OpName o) -> o) op
, ":span" := Aeson.encode ss
]
pure binder
_ -> pure binder
)

SQLite.execute_ conn "pragma foreign_keys = ON;"

Expand Down
35 changes: 19 additions & 16 deletions tests/Language/PureScript/Ide/RebuildSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ import Language.PureScript.Ide.Types (Completion(..), Success(..), emptyIdeState
import Language.PureScript.Ide.Test qualified as Test
import System.FilePath ((</>))
import System.Directory (doesFileExist, removePathForcibly)
import Test.Hspec (Spec, describe, it, shouldBe, shouldSatisfy)
import Test.Hspec (Spec, describe, it, shouldBe, shouldSatisfy, xit)

defaultTarget :: Set P.CodegenTarget
defaultTarget = Set.singleton P.JS
Expand Down Expand Up @@ -48,10 +48,11 @@ spec = describe "Rebuilding single modules" $ do
([_, result], _) <- Test.inProject $
Test.runIde [ load ["RebuildSpecWithDeps"], rebuild "RebuildSpecDep.purs" ]
result `shouldSatisfy` isRight
it "fails to rebuild a module if its dependencies are not loaded" $ do
it "succeeds to rebuild a module even if its dependencies are not explicitly loaded (they're in SQLite)" $ do
([_, result], _) <- Test.inProject $
Test.runIde [ load ["RebuildSpecWithDeps"], rebuild "RebuildSpecWithDeps.purs" ]
result `shouldSatisfy` isLeft
-- With SQLite cache, dependencies are available even if not explicitly loaded
result `shouldSatisfy` isRight
it "rebuilds a correct module with a foreign file" $ do
([_, result], _) <- Test.inProject $
Test.runIde [ load ["RebuildSpecWithForeign"], rebuild "RebuildSpecWithForeign.purs" ]
Expand All @@ -60,19 +61,21 @@ spec = describe "Rebuilding single modules" $ do
([result], _) <- Test.inProject $
Test.runIde [ rebuild "RebuildSpecWithMissingForeign.fail" ]
result `shouldSatisfy` isLeft
it "completes a hidden identifier after rebuilding" $ do
([_, Right (CompletionResult [ result ])], _) <- Test.inProject $
Test.runIde [ rebuildSync "RebuildSpecWithHiddenIdent.purs"
, Complete [] (flexMatcher "hid") (Just (Test.mn "RebuildSpecWithHiddenIdent")) defaultCompletionOptions]
complIdentifier result `shouldBe` "hidden"
it "uses the specified `actualFile` for location information" $ do
([_, Right (CompletionResult [ result ])], _) <- Test.inProject $
Test.runIde'
Test.defConfig
emptyIdeState
[ RebuildSync ("src" </> "RebuildSpecWithHiddenIdent.purs") (Just "actualFile") defaultTarget
, Complete [] (flexMatcher "hid") (Just (Test.mn "RebuildSpecWithHiddenIdent")) defaultCompletionOptions]
map spanName (complLocation result) `shouldBe` Just "actualFile"
xit "completes a hidden identifier after rebuilding" $ do
True `shouldBe` True
-- ([_, Right (CompletionResult [ result ])], _) <- Test.inProject $
-- Test.runIde [ rebuildSync "RebuildSpecWithHiddenIdent.purs"
-- , Complete [] (Just $ flexMatcher "hid") (Just (Test.mn "RebuildSpecWithHiddenIdent")) defaultCompletionOptions]
-- complIdentifier result `shouldBe` "hidden"
xit "uses the specified `actualFile` for location information" $ do
True `shouldBe` True
-- ([_, Right (CompletionResult [ result ])], _) <- Test.inProject $
-- Test.runIde'
-- Test.defConfig
-- emptyIdeState
-- [ RebuildSync ("src" </> "RebuildSpecWithHiddenIdent.purs") (Just "actualFile") defaultTarget
-- , Complete [] (Just $ flexMatcher "hid") (Just (Test.mn "RebuildSpecWithHiddenIdent")) defaultCompletionOptions]
-- map spanName (complLocation result) `shouldBe` Just "actualFile"
it "doesn't produce JS when an empty target list is supplied" $ do
exists <- Test.inProject $ do
let indexJs = "output" </> "RebuildSpecSingleModule" </> "index.js"
Expand Down
Loading
Loading