Current non-working version of file parsing
[lsp-test.git] / src / Language / Haskell / LSP / Test / Files.hs
index 52632eb91d7b9e81b1795dc0c1b435f65d7f19b3..f59551a3719ae3e2dcf9f24b321ef7aa569eb1c1 100644 (file)
 {-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE OverloadedStrings #-}
 module Language.Haskell.LSP.Test.Files
-  ( loadSwappedFiles
-  , FileMap
-  , emptyFileMap
+  ( swapFiles
+  , rootDir
   )
 where
 
-import           Language.Haskell.LSP.Core
-import qualified Language.Haskell.LSP.Control  as Control
 import           Language.Haskell.LSP.Types        hiding ( error )
-import           Data.Default
 import           Control.Lens
-import           Control.Monad
-import           Control.Concurrent
 import           Data.Aeson
+import           Data.Aeson.Types
 import qualified Data.ByteString.Lazy.Char8    as B
-import           Data.Map                      as Map
+import qualified Data.Text                     as T
+import qualified Data.HashMap.Strict           as HashMap
 import           Data.Maybe
 import           System.Directory
-import           System.IO
+import           System.FilePath
 
-type FileMap = Map.Map FilePath FilePath
+swapFiles :: FilePath -> FilePath -> [B.ByteString] -> IO [B.ByteString]
+swapFiles recBaseDir relCurBaseDir msgs = do
+  curBaseDir <- (</> relCurBaseDir) <$> getCurrentDirectory
+  let transform uri =
+        let fp = fromMaybe (error "Couldn't transform uri") (uriToFilePath uri)
+            newFp = curBaseDir </> makeRelative recBaseDir fp
+          in filePathToUri newFp
+      newMsgs = map (mapUris transform) msgs :: [B.ByteString]
 
-emptyFileMap :: FileMap
-emptyFileMap = Map.empty
+  return newMsgs
 
-buildFiles
-  :: (HasParams a b, HasTextDocument b c, HasUri c Uri)
-  => [a]
-  -> FileMap
-  -> IO FileMap
-buildFiles ns oldMap = foldM createFile oldMap ns
- where
-  createFile map n = do
-    let fp = fromMaybe (error "Couldn't convert file path")
-                       (uriToFilePath $ n ^. params . textDocument . uri)
-    if Map.member fp map
-      then return map
-      else do
-        tmpDir        <- getTemporaryDirectory
-        (tmpFp, tmpH) <- openTempFile tmpDir "lspTestDoc"
-        readFile fp >>= hPutStr tmpH
-        return $ Map.insert fp tmpFp map
-
-swapFile :: (HasUri a Uri) => FileMap -> a -> a
-swapFile m msg = fromMaybe msg $ do
-  let oldUri = msg ^. uri
-  oldFp <- uriToFilePath oldUri
-  newFp <- Map.lookup oldFp m
-  let newUri = filePathToUri newFp
-  return $ uri .~ newUri $ msg
+rootDir :: [B.ByteString] -> FilePath
+rootDir msgs = fromMaybe (error "Couldn't find root dir") $ do
+  req <- decode (head msgs) :: Maybe InitializeRequest
+  rootUri <- req ^. params .rootUri
+  uriToFilePath rootUri
 
-loadSwappedFiles :: FileMap -> Handle -> IO ([B.ByteString], FileMap)
-loadSwappedFiles map h = do
-  fileMapVar <- newMVar map
-  msgsVar    <- newMVar []
-  nullH      <- openFile "/dev/null" WriteMode
-  Control.runWithHandles h
-                         nullH
-                         (const $ Right (), const $ return Nothing)
-                         (handlers msgsVar fileMapVar)
-                         def
-                         Nothing
-                         Nothing
-  newMap <- readMVar fileMapVar
-  msgs   <- reverse <$> readMVar msgsVar
-  return (msgs, newMap)
+mapUris :: (Uri -> Uri) -> B.ByteString -> B.ByteString
+mapUris f msg =
+  case decode msg :: Maybe Object of
+    Just obj -> encode $ HashMap.map (mapValue f) obj
+    Nothing -> error "Couldn't decode message"
 
-handlers :: MVar [B.ByteString] -> MVar FileMap -> Handlers
-handlers msgs fileMap = Handlers
-  {
-    -- Requests
-    hoverHandler                             = Just put
-  , completionHandler                        = Just put
-  , completionResolveHandler                 = Just put
-  , signatureHelpHandler                     = Just put
-  , definitionHandler                        = Just put
-  , referencesHandler                        = Just put
-  , documentHighlightHandler                 = Just put
-  , documentSymbolHandler                    = Just $ swapUri (params . textDocument)
-  , workspaceSymbolHandler                   = Just put
-  , codeActionHandler                        = Just put
-  , codeLensHandler                          = Just put
-  , codeLensResolveHandler                   = Just put
-  , documentFormattingHandler                = Just put
-  , documentRangeFormattingHandler           = Just put
-  , documentTypeFormattingHandler            = Just put
-  , renameHandler                            = Just $ swapUri (params . textDocument)
-  , documentLinkHandler                      = Just $ swapUri (params . textDocument)
-  , documentLinkResolveHandler               = Just put
-  , executeCommandHandler                    = Just put
-  , initializeRequestHandler                 = Just put
-    -- Notifications
-  , didChangeConfigurationParamsHandler      = Just put
-  , didOpenTextDocumentNotificationHandler   = Just $ swapUri (params . textDocument)
-  , didChangeTextDocumentNotificationHandler = Just $ swapUri (params . textDocument)
-  , didCloseTextDocumentNotificationHandler  = Just $ swapUri (params . textDocument)
-  , didSaveTextDocumentNotificationHandler   = Just $ swapUri (params . textDocument)
-  , willSaveWaitUntilTextDocHandler          = Just put
-  , didChangeWatchedFilesNotificationHandler = Just put
-  , initializedHandler                       = Just put
-  , willSaveTextDocumentNotificationHandler  = Just $ swapUri (params . textDocument)
-  , cancelNotificationHandler                = Just put
-  , exitNotificationHandler                  = Just put
-    -- Responses
-  , responseHandler                          = Just put
-  }
   where 
-  swapUri f msg = do
-    modifyMVar_ fileMap (buildFiles [msg])
-    map <- readMVar fileMap
-    put $ swapFile map $ msg ^. f
+    mapValue :: (Uri -> Uri) -> Value -> Value
+    mapValue f x = case parse parseJSON x :: Result VersionedTextDocumentIdentifier of
+      Success doc -> transform doc
+      Error _ -> case parse parseJSON x :: Result TextDocumentIdentifier of
+        Success doc -> transform doc
+        Error _ -> case parse parseJSON x :: Result InitializeParams of
+          Success params -> transformInit params
+          Error _ -> case parse parseJSON x :: Result Object of
+            Success obj -> Object $ HashMap.map (mapValue f) obj
+            Error _ -> x
+
+    -- parsing with just JSON
+    -- mapValueWithKey :: (Uri -> Uri) -> T.Text -> Value -> Value
+    -- mapValueWithKey f "uri" (String s) = fromMaybe (error "Couldn't convert uri") $ do
+    --   let uri = filePathToUri $ T.unpack s
+    --   String <$> (fmap T.pack (uriToFilePath $ f uri))
+    -- mapValueWithKey f _ (Array xs) = Array $ fmap (mapValue f) xs
+    -- mapValueWithKey f _ (Object x) = Object $ HashMap.mapWithKey (mapValueWithKey f) x
+
+    transform x = toJSON $ x & uri .~ f (x ^. uri)
 
-  put :: ToJSON a => a -> IO ()
-  put msg = modifyMVar_ msgs (return . (encode msg :))
+    -- transform rootUri/rootPath
+    transformInit :: InitializeParams -> Value
+    transformInit x =
+      let newRootUri = fmap f (x ^. rootUri)
+          newRootPath = do
+            fp <- T.unpack <$> x ^. rootPath
+            let uri = filePathToUri fp
+            T.pack <$> uriToFilePath (f uri)
+        in toJSON $ (rootUri .~ newRootUri) $ (rootPath .~ newRootPath) x