Skip to content

Commit

Permalink
Add test suite (#42)
Browse files Browse the repository at this point in the history
  • Loading branch information
markus1189 authored and Gabriella439 committed Apr 29, 2017
1 parent b996489 commit ca40559
Show file tree
Hide file tree
Showing 4 changed files with 40 additions and 2 deletions.
13 changes: 13 additions & 0 deletions dhall.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -69,3 +69,16 @@ Executable dhall
GHC-Options: -Wall
Other-Modules:
Paths_dhall

Test-Suite test
Type: exitcode-stdio-1.0
Hs-Source-Dirs: tests
Main-Is: Tests.hs
Other-Modules:
Normalization
Build-Depends:
base >= 4 && < 5,
dhall,
tasty >= 0.11.2 && < 0.12,
tasty-hunit >= 0.9.2 && < 0.10,
text >= 0.11.1.0 && < 1.3
4 changes: 2 additions & 2 deletions src/Dhall/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ import qualified NeatInterpolation
Note that Dhall does not support functions from terms to types and therefore
Dhall is not a dependently typed language
-}
data Const = Type | Kind deriving (Show, Bounded, Enum)
data Const = Type | Kind deriving (Show, Eq, Bounded, Enum)

instance Buildable Const where
build = buildConst
Expand Down Expand Up @@ -287,7 +287,7 @@ data Expr s a
| Note s (Expr s a)
-- | > Embed path ~ path
| Embed a
deriving (Functor, Foldable, Traversable, Show)
deriving (Functor, Foldable, Traversable, Show, Eq)

instance Applicative (Expr s) where
pure = Embed
Expand Down
18 changes: 18 additions & 0 deletions tests/Normalization.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
{-# LANGUAGE OverloadedStrings #-}
module Normalization (normalizationTests) where

import Dhall.Core
import Test.Tasty
import Test.Tasty.HUnit

normalizationTests :: TestTree
normalizationTests = testGroup "normalization" [ constantFolding ]

constantFolding :: TestTree
constantFolding = testGroup "folding of constants" [ naturalPlus ]

naturalPlus :: TestTree
naturalPlus = testCase "natural plus" $ normalize' (NaturalPlus (NaturalLit 1) (NaturalLit 2)) @?= NaturalLit 3

normalize' :: Expr () () -> Expr () ()
normalize' = normalize
7 changes: 7 additions & 0 deletions tests/Tests.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
module Main where

import Normalization (normalizationTests)
import Test.Tasty

main :: IO ()
main = defaultMain (testGroup "Dhall Tests" [ normalizationTests ])

0 comments on commit ca40559

Please sign in to comment.