{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedLists #-} {-# LANGUAGE OverloadedStrings #-} module Data.HCLSpec where import Control.Monad import Control.Monad.IO.Class import Data.HCL import Data.HCL.TestHelper import Data.Text (Text) import qualified Data.Text as Text import qualified Data.Text.IO as Text import System.Directory import System.FilePath import System.IO.Unsafe import Test.Hspec import Text.Megaparsec (Parsec, Token (..), runParser) {-# NOINLINE fs' #-} fs' :: [FilePath] fs' = unsafePerformIO $ do fs <- liftIO (getDirectoryContents "./test-fixtures") return $ filter ((== ".hcl") . takeExtension) fs spec :: Spec spec = do describe "stringParts" $ do it "parses normal strings" $ do let input = "\"something\"" testParser stringParts input [HCLStringPlain "something"] it "parses interpolated strings" $ do let input = "\"${asdf} Hello World asdfasdf ${hey}\"" testParser stringParts input [ HCLStringInterp "asdf" , HCLStringPlain " Hello World asdfasdf " , HCLStringInterp "hey" ] describe "ident" $ do it "parses alphanum" $ do let input = "asdf" testParser ident input "asdf" it "parses dashes" $ do let input = "asdf-asdf" testParser ident input "asdf-asdf" it "parses underscores" $ do let input = "asdf_asdf" testParser ident input "asdf_asdf" it "stops at whitespace" $ do let input = "asdf asdf" testParser ident input "asdf" describe "stringPlain" $ do it "parses the empty string" $ do let input = "" testParser stringPlain input "" it "parses charaters" $ do let input = "something" testParser stringPlain input "something" it "parses escape sequences" $ do let input = "bar\\\"baz\\n" testParser stringPlain input "bar\"baz\n" describe "stringPlainMultiline" $ it "parses multiline strings" $ do let input = Text.unlines [ "< it fp $ do inp <- liftIO $ Text.readFile ("test-fixtures" fp) case fp of "unterminated_block_comment.hcl" -> testFailure fp inp "multiline_no_marker.hcl" -> testFailure fp inp "multiline_bad.hcl" -> testFailure fp inp "unterminated_brace.hcl" -> testFailure fp inp _ -> case parseHCL fp inp of Left e -> error (show e) Right _ -> True `shouldBe` True