2017-04-19 23:25:46 +03:00
|
|
|
{-# LANGUAGE DataKinds, GADTs, ScopedTypeVariables, TypeFamilies, TypeOperators #-}
|
|
|
|
module SpecHelpers
|
2017-04-20 02:33:27 +03:00
|
|
|
( diffFilePaths
|
|
|
|
, parseFilePath
|
2017-05-10 01:49:38 +03:00
|
|
|
, readFile
|
|
|
|
, languageForFilePath
|
2017-04-19 23:25:46 +03:00
|
|
|
) where
|
2017-04-19 19:12:19 +03:00
|
|
|
|
2017-07-28 21:37:02 +03:00
|
|
|
import Control.Exception
|
2017-06-24 17:09:50 +03:00
|
|
|
import Data.Blob
|
2017-04-19 19:12:19 +03:00
|
|
|
import qualified Data.ByteString as B
|
2017-04-19 23:25:46 +03:00
|
|
|
import Data.Functor.Both
|
2017-11-27 22:17:48 +03:00
|
|
|
import Data.Language
|
2017-07-28 21:37:02 +03:00
|
|
|
import Data.Maybe (fromMaybe)
|
2017-06-24 16:59:41 +03:00
|
|
|
import Data.Source
|
2017-07-28 21:37:02 +03:00
|
|
|
import Prelude hiding (readFile)
|
2017-11-27 21:30:38 +03:00
|
|
|
import Rendering.Renderer
|
2017-04-20 02:33:27 +03:00
|
|
|
import Semantic
|
2017-05-30 16:14:50 +03:00
|
|
|
import Semantic.Task
|
2017-04-19 19:45:08 +03:00
|
|
|
import System.FilePath
|
2017-04-19 19:12:19 +03:00
|
|
|
|
2017-04-19 23:25:46 +03:00
|
|
|
-- | Returns an s-expression formatted diff for the specified FilePath pair.
|
2017-07-28 21:37:02 +03:00
|
|
|
diffFilePaths :: Both FilePath -> IO B.ByteString
|
2017-04-20 02:33:27 +03:00
|
|
|
diffFilePaths paths = do
|
2017-05-30 16:14:50 +03:00
|
|
|
blobs <- traverse readFile paths
|
2017-06-01 18:33:12 +03:00
|
|
|
runTask (diffBlobPair SExpressionDiffRenderer blobs)
|
2017-04-19 23:25:46 +03:00
|
|
|
|
|
|
|
-- | Returns an s-expression parse tree for the specified FilePath.
|
2017-07-28 21:37:02 +03:00
|
|
|
parseFilePath :: FilePath -> IO B.ByteString
|
2017-04-20 02:33:27 +03:00
|
|
|
parseFilePath path = do
|
2017-05-10 01:49:38 +03:00
|
|
|
blob <- readFile path
|
2017-05-31 19:25:40 +03:00
|
|
|
runTask (parseBlob SExpressionTermRenderer blob)
|
2017-04-21 23:56:19 +03:00
|
|
|
|
2017-06-24 17:15:31 +03:00
|
|
|
-- | Read a file to a Blob.
|
2017-04-21 23:56:19 +03:00
|
|
|
--
|
|
|
|
-- NB: This is intentionally duplicated from Command.Files because eventually
|
2017-04-24 19:17:18 +03:00
|
|
|
-- we want to be able to test a core Semantic library that has no knowledge of
|
2017-04-21 23:56:19 +03:00
|
|
|
-- the filesystem or Git. The tests, however, will still leverage reading files.
|
2017-06-24 17:15:31 +03:00
|
|
|
readFile :: FilePath -> IO Blob
|
2017-04-21 23:56:19 +03:00
|
|
|
readFile path = do
|
2017-06-24 18:32:04 +03:00
|
|
|
source <- (Just . fromBytes <$> B.readFile path) `catch` (const (pure Nothing) :: IOException -> IO (Maybe Source))
|
2017-06-24 17:15:31 +03:00
|
|
|
pure $ fromMaybe (emptyBlob path) (sourceBlob path (languageForFilePath path) <$> source)
|
2017-05-11 16:28:52 +03:00
|
|
|
|
2017-05-10 01:49:38 +03:00
|
|
|
-- | Returns a Maybe Language based on the FilePath's extension.
|
|
|
|
languageForFilePath :: FilePath -> Maybe Language
|
2017-07-28 21:37:02 +03:00
|
|
|
languageForFilePath = languageForType . takeExtension
|