1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 08:54:07 +03:00
semantic/test/SpecHelpers.hs

47 lines
1.6 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DataKinds, GADTs, ScopedTypeVariables, TypeFamilies, TypeOperators #-}
module SpecHelpers
( diffFilePaths
, parseFilePath
, readFile
, languageForFilePath
) where
2017-07-28 21:37:02 +03:00
import Control.Exception
2017-06-24 17:09:50 +03:00
import Data.Blob
import qualified Data.ByteString as B
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)
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
import Semantic
2017-05-30 16:14:50 +03:00
import Semantic.Task
import System.FilePath
-- | 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
diffFilePaths paths = do
2017-05-30 16:14:50 +03:00
blobs <- traverse readFile paths
runTask (diffBlobPair SExpressionDiffRenderer blobs)
-- | Returns an s-expression parse tree for the specified FilePath.
2017-07-28 21:37:02 +03:00
parseFilePath :: FilePath -> IO B.ByteString
parseFilePath path = do
blob <- readFile path
runTask (parseBlob SExpressionTermRenderer blob)
2017-06-24 17:15:31 +03:00
-- | Read a file to a Blob.
--
-- 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
-- the filesystem or Git. The tests, however, will still leverage reading files.
2017-06-24 17:15:31 +03:00
readFile :: FilePath -> IO Blob
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
-- | 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