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

62 lines
1.9 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DataKinds, GADTs, ScopedTypeVariables, TypeFamilies, TypeOperators #-}
module SpecHelpers
( diffFilePaths
, parseFilePath
2017-12-10 19:46:17 +03:00
, readFilePair
, languageForFilePath
2018-02-07 23:20:27 +03:00
, Verbatim(..)
, verbatim
, readFileVerbatim
) where
2017-12-10 19:46:17 +03:00
import Control.Monad ((<=<))
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
import Data.Maybe (fromMaybe, fromJust)
import Data.Source
2017-11-27 21:30:38 +03:00
import Rendering.Renderer
import Semantic
2017-05-30 16:14:50 +03:00
import Semantic.Task
2017-12-10 19:46:17 +03:00
import qualified Semantic.IO as IO
import System.FilePath
2018-02-07 23:20:27 +03:00
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8)
-- | 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-12-10 19:46:17 +03:00
diffFilePaths paths = readFilePair paths >>= runTask . diffBlobPair SExpressionDiffRenderer
-- | 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 = IO.readFile path (languageForFilePath path) >>= pure . fromJust >>= runTask . parseBlob SExpressionTermRenderer
2017-12-11 19:27:13 +03:00
-- | Read two files to a BlobPair.
readFilePair :: Both FilePath -> IO BlobPair
readFilePair paths = let paths' = fmap (\p -> (p, languageForFilePath p)) paths in
runBothWith IO.readFilePair paths'
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
2018-02-07 23:20:27 +03:00
readFileVerbatim :: FilePath -> IO Verbatim
readFileVerbatim = fmap verbatim . B.readFile
2018-02-07 23:20:27 +03:00
newtype Verbatim = Verbatim B.ByteString
deriving (Eq)
instance Show Verbatim where
show (Verbatim x) = show x
verbatim :: B.ByteString -> Verbatim
verbatim = Verbatim . stripWhitespace
where
stripWhitespace :: B.ByteString -> B.ByteString
stripWhitespace = B.foldl' go B.empty
where go acc x | x `B.elem` " \t\n" = acc
| otherwise = B.snoc acc x