File: BaseSpec.hs

package info (click to toggle)
bnfc 2.9.5-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 1,252 kB
  • sloc: haskell: 16,607; yacc: 240; makefile: 85
file content (57 lines) | stat: -rw-r--r-- 2,178 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
{-# LANGUAGE ExtendedDefaultRules #-}

module BNFC.Backend.BaseSpec where

import Data.List (isInfixOf)

import System.Directory
import System.IO.Temp (withSystemTempDirectory)

import Test.Hspec

import BNFC.Backend.Base -- SUT

default(String)

spec :: Spec
spec = do
  -- -- Andreas, 2021-07-17
  -- -- I don't really believe in these unit tests; important are system tests.
  -- -- So I am not putting in much energy to maintain them.
  describe "Backend monad" $ do
    it "empty computation generates empty list of files" $
      execBackend (return ()) `shouldReturn` []
    -- -- Test broken: mkfile also puts the BNFC signature containing the version number.
    -- it "returns the file created using mkfile" $
    --   execBackend (mkfile "test.txt" "abcd")
    --     `shouldReturn` [("test.txt", "abcd\n")]
  describe "writeFiles" $ do
    it "creates the root directory if it doesn't exists" $
      withSystemTempDirectory "bnfc-test" $ \tmpdir -> do
        setCurrentDirectory tmpdir
        writeFiles "foo/bar" (return ())
        doesDirectoryExist "foo/bar" `shouldReturn` True
    it "creates a file from the bucket" $
      withSystemTempDirectory "bnfc-test" $ \tmpdir -> do
        setCurrentDirectory tmpdir
        writeFiles "." (mkfile "file.txt" id "")
        doesFileExist "file.txt"
      `shouldReturn` True
    it "put the right content in the file" $
      withSystemTempDirectory "bnfc-test" $ \tmpdir -> do
        setCurrentDirectory tmpdir
        writeFiles "." (mkfile "file.txt" id "abcd")
        readFile "file.txt" >>=
          (`shouldSatisfy` isInfixOf "abcd\n")
    it "creates subdirectories" $
      withSystemTempDirectory "bnfc-test" $ \tmpdir -> do
        setCurrentDirectory tmpdir
        writeFiles "." (mkfile "subdir/file.txt" id "abcd")
        doesDirectoryExist "subdir"
      `shouldReturn` True
    it "creates files in the root directory" $
      withSystemTempDirectory "bnfc-test" $ \tmpdir -> do
        setCurrentDirectory tmpdir
        writeFiles "root/" (mkfile "foo/bar.txt" id "abcd")
        doesFileExist "root/foo/bar.txt" `shouldReturn` True