Remove unused extractParens function and its tests
This commit is contained in:
parent
57e2c112dc
commit
73b98573f4
@ -44,18 +44,6 @@ import Utils
|
|||||||
dropWhileEnd :: (a -> Bool) -> [a] -> [a]
|
dropWhileEnd :: (a -> Bool) -> [a] -> [a]
|
||||||
dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) []
|
dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) []
|
||||||
|
|
||||||
extractParens :: String -> String
|
|
||||||
extractParens str = extractParens' str 0
|
|
||||||
where
|
|
||||||
extractParens' :: String -> Int -> String
|
|
||||||
extractParens' [] _ = []
|
|
||||||
extractParens' (s:ss) level
|
|
||||||
| s `elem` "([{" = s : extractParens' ss (level+1)
|
|
||||||
| level == 0 = extractParens' ss 0
|
|
||||||
| s `elem` "}])" && level == 1 = [s]
|
|
||||||
| s `elem` "}])" = s : extractParens' ss (level-1)
|
|
||||||
| otherwise = s : extractParens' ss level
|
|
||||||
|
|
||||||
withDirectory_ :: (MonadIO m, ExceptionMonad m) => FilePath -> m a -> m a
|
withDirectory_ :: (MonadIO m, ExceptionMonad m) => FilePath -> m a -> m a
|
||||||
withDirectory_ dir action =
|
withDirectory_ dir action =
|
||||||
gbracket (liftIO getCurrentDirectory) (liftIO . setCurrentDirectory)
|
gbracket (liftIO getCurrentDirectory) (liftIO . setCurrentDirectory)
|
||||||
|
@ -1,11 +0,0 @@
|
|||||||
module UtilsSpec where
|
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Utils
|
|
||||||
import Test.Hspec
|
|
||||||
|
|
||||||
spec :: Spec
|
|
||||||
spec = do
|
|
||||||
describe "extractParens" $ do
|
|
||||||
it "extracts the part of a string surrounded by parentheses" $ do
|
|
||||||
extractParens "asdasdasd ( hello [ world ] )()() kljlkjlkjlk" `shouldBe` "( hello [ world ] )"
|
|
||||||
extractParens "[(PackageName \"template-haskell\",InstalledPackageId \"template-haskell-2.9.0.0-8e2a49468f3b663b671c437d8579cd28\"),(PackageName \"base\",InstalledPackageId \"base-4.7.0.0-e4567cc9a8ef85f78696b03f3547b6d5\"),(PackageName \"Cabal\",InstalledPackageId \"Cabal-1.18.1.3-b9a44a5b15a8bce47d40128ac326e369\")][][]" `shouldBe` "[(PackageName \"template-haskell\",InstalledPackageId \"template-haskell-2.9.0.0-8e2a49468f3b663b671c437d8579cd28\"),(PackageName \"base\",InstalledPackageId \"base-4.7.0.0-e4567cc9a8ef85f78696b03f3547b6d5\"),(PackageName \"Cabal\",InstalledPackageId \"Cabal-1.18.1.3-b9a44a5b15a8bce47d40128ac326e369\")]"
|
|
Loading…
Reference in New Issue
Block a user