{-# LANGUAGE TemplateHaskell #-} module TestSourceMatchSpec where import Data.Text (Text) -- for template declarations import GHC.Generics import Language.Haskell.SourceMatch import Language.Haskell.TH.Lib import System.FilePath.Posix import Test.Hspec checkTopLevelWithVariables1 :: DecsQ checkTopLevelWithVariables1 = [d| data TopLevel = C_1 { v_1 :: [T_2] } deriving (Show, Eq, GHC.Generics.Generic)|] checkTopLevelWithVariables2 :: DecsQ checkTopLevelWithVariables2 = [d| data TopLevel = TopLevel { v_1 :: [T_2] } deriving (Show, Eq, GHC.Generics.Generic)|] checkTopLevelWithVariables3 :: DecsQ checkTopLevelWithVariables3 = [d| data TopLevel = TopLevel { v_1 :: [T_2] } deriving (Eq, Show, GHC.Generics.Generic)|] checkTopLevelWithVariables4 :: DecsQ checkTopLevelWithVariables4 = [d| data TopLevel = TopLevel { v_1 :: [String] } deriving (Eq, Show, GHC.Generics.Generic)|] checkTopLevelWithVariables5 :: DecsQ checkTopLevelWithVariables5 = [d| data TopLevel = TopLevel { v :: [String] } deriving (Eq, Show, GHC.Generics.Generic)|] checkTopLevelWithVariables5file :: DecsQ checkTopLevelWithVariables5file = [d| data TopLevel = TopLevel { topLevelColorsArray :: [T_1] } deriving (Eq, Show, GHC.Generics.Generic)|] -- * Wrong decls wrongCheckTopLevelWithVariables1 :: DecsQ wrongCheckTopLevelWithVariables1 = [d| data TopLevel = C_1 { x_1 :: [T_2] } deriving (Show, Eq, GHC.Generics.Generic)|] wrongCheckTopLevelWithVariables2 :: DecsQ wrongCheckTopLevelWithVariables2 = [d| data TopLevel = CropLevel { v_1 :: [T_2] } deriving (Show, Eq, GHC.Generics.Generic)|] wrongCheckTopLevelWithVariables3 :: DecsQ wrongCheckTopLevelWithVariables3 = [d| data TopLevel = C_1 { v_1 :: [T_2] } deriving (Show, GHC.Generics.Generic)|] wrongCheckTopLevelWithVariables4 :: DecsQ wrongCheckTopLevelWithVariables4 = [d| data TopLevel = C_1 { v_1 :: Maybe T_2 } deriving (Show, Eq, GHC.Generics.Generic)|] wrongCheckTopLevelWithVariables5 :: DecsQ wrongCheckTopLevelWithVariables5 = [d| data TopLevel = C_1 { v_1 :: [T_2] , v_2 :: [T_3] } deriving (Eq, Show, GHC.Generics.Generic)|] miscFileCheck1 :: DecsQ miscFileCheck1 = [d| data ColorsArrayElt = ColorsArrayElt { colorsArrayEltHexValue :: Text, colorsArrayEltColorName :: Text } deriving (Show, Eq, GHC.Generics.Generic)|] spec :: Spec spec = describe "Key test operators" $ do describe "isStringMatchedToDecl" $ do let decl = "data TopLevel = TopLevel { v :: [String] } deriving (Show, Eq, GHC.Generics.Generic)" -- it "matches with all metavariables" $ example $ decl `stringShouldMatchDecl` checkTopLevelWithVariables1 it "matches with constructor and var-metavariable" $ example $ decl `stringShouldMatchDecl` checkTopLevelWithVariables2 it "order of deriving is unimportant" $ example $ decl `stringShouldMatchDecl` checkTopLevelWithVariables3 it "matches with type and var-metavariable" $ example $ decl `stringShouldMatchDecl` checkTopLevelWithVariables4 it "matches with full-defined declaration" $ example $ decl `stringShouldMatchDecl` checkTopLevelWithVariables5 -- it "doesn't match with wrong var-metavariable" $ example $ decl `stringShouldNotMatchDecl` wrongCheckTopLevelWithVariables1 it "doesn't match with wrong named constructor" $ example $ decl `stringShouldNotMatchDecl` wrongCheckTopLevelWithVariables2 it "doesn't match with shortened deriving list" $ example $ decl `stringShouldNotMatchDecl` wrongCheckTopLevelWithVariables3 it "doesn't match with wrong field type" $ example $ decl `stringShouldNotMatchDecl` wrongCheckTopLevelWithVariables4 it "doesn't match with different number of fields" $ example $ decl `stringShouldNotMatchDecl` wrongCheckTopLevelWithVariables5 describe "isFileMatchedToDecl" $ do -- -- File match checking -- it "matches with all metavariables" $ example $ (testFile "colors.hs") `fileShouldMatchDecl` checkTopLevelWithVariables1 it "matches with constructor and var-metavariable" $ example $ (testFile "colors.hs") `fileShouldMatchDecl` checkTopLevelWithVariables2 it "order of deriving is unimportant" $ example $ (testFile "colors.hs") `fileShouldMatchDecl` checkTopLevelWithVariables3 -- checkTopLevelWithVariables4 have other type it "matches with full-defined declaration" $ example $ (testFile "colors.hs") `fileShouldMatchDecl` checkTopLevelWithVariables5file it "doesn't match with wrong var-metavariable" $ example $ (testFile "colors.hs") `fileShouldNotMatchDecl` wrongCheckTopLevelWithVariables1 it "doesn't match with wrong named constructor" $ example $ (testFile "colors.hs") `fileShouldNotMatchDecl` wrongCheckTopLevelWithVariables2 it "doesn't match with shortened deriving list" $ example $ (testFile "colors.hs") `fileShouldNotMatchDecl` wrongCheckTopLevelWithVariables3 it "doesn't match with wrong field type" $ example $ (testFile "colors.hs") `fileShouldNotMatchDecl` wrongCheckTopLevelWithVariables4 it "doesn't match with different number of fields" $ example $ (testFile "colors.hs") `fileShouldNotMatchDecl` wrongCheckTopLevelWithVariables5 it "match with other declarations in file" $ example $ (testFile "colors.hs") `fileShouldMatchDecl` miscFileCheck1 -- * Utils for testing stringShouldMatchDecl :: (HasCallStack) => String -> DecsQ -> Expectation stringShouldMatchDecl str decl = do Right _ <- isStringMatchedToDecl str decl return () stringShouldNotMatchDecl :: (HasCallStack) => String -> DecsQ -> Expectation stringShouldNotMatchDecl str decl = do Left _ <- isStringMatchedToDecl str decl return () fileShouldMatchDecl :: (HasCallStack) => FilePath -> DecsQ -> Expectation fileShouldMatchDecl filepath decl = do Right _ <- isFileMatchedToDecl filepath decl return () fileShouldNotMatchDecl :: (HasCallStack) => FilePath -> DecsQ -> Expectation fileShouldNotMatchDecl filepath decl = do Left _ <- isFileMatchedToDecl filepath decl return () testFile :: FilePath -> FilePath testFile testFilepath = "test" "test-data" testFilepath