{-# LANGUAGE OverloadedStrings #-} module Main ( main ) where import Language.Haskell.CHs.Deps import Test.Tasty import Test.Tasty.HUnit main :: IO () main = defaultMain $ testGroup "tasty chs" [ testCase "simple import" $ getImports "{# import Data.Char #}" @?= Right ["Data.Char"] , testCase "line comment" $ getImports "-- {# import Data.Char #}" @?= Right [] , testCase "nested block comment" $ getImports "{- nested {- comment -} -} {# import Data.Char #}" @?= Right ["Data.Char"] , testCase "Not find spurious imports" $ getImports "import Data.Word\n{# import Data.Char #}" @?= Right ["Data.Char"] , testCase "Work with qualified imports + spaces" $ getImports "{# import qualified Data.Char #}" @?= Right ["Data.Char"] , testCase "Error on bad block comments" $ getImports "{- {- block comment -} {# import Data.Char #}" @?= Left "Error in nested comment at line 1, column 46" , testCase "Doesn't pick up qualified type names" $ getImports "{# fun LZ_decompress_data_position as ^ { `LZDecoderPtr' } -> `C2HSImp.CULLong' id #}" @?= Right [] ]