Giter Club home page Giter Club logo

should-not-typecheck's Introduction

should-not-typecheck Build Status Hackage

should-not-typecheck is a Haskell library which allows you to assert that an expression does not typecheck in your tests. It provides one function, shouldNotTypecheck, which takes an expression and will fail the test if it typechecks. shouldNotTypecheck returns an HUnit Assertion (so it can be used with both HUnit and hspec).

Example (hspec)

The secret sauce is the Deferred Type Errors GHC extension. This allows you to write an ill-typed expression which will throw an exception at run time (rather than erroring out at compile time). shouldNotTypecheck tries to catch that exception and fails the test if no deferred type error is caught.

{-# OPTIONS_GHC -fdefer-type-errors #-} -- Very important!

module Main where

import Test.Hspec (hspec, describe, it)
import Test.ShouldNotTypecheck (shouldNotTypecheck)

main :: IO ()
main = hspec $ do
  describe "Type Tests" $ do
    it "should not allow an Int to be a String" $
      shouldNotTypecheck (4 :: String)

It can be used similarly with HUnit.

NFData a constraint

Haskell is a lazy language - deferred type errors will not get evaluated unless we explicitly and deeply force (evaluate) the value. NFData is a typeclass from the deepseq library which allows you to describe how to fully evaluate an expression (convert it to Normal Form). shouldNotTypecheck uses this typeclass to fully evaluate expressions passed to it. For vanilla Haskell types you only need to derive Generic and the deepseq class will handle it for you:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics (Generic)

data SomeType a = WithSome | DataConstructors a
  deriving Generic

instance NFData a => NFData (SomeType a)

In GHC 7.10 DeriveAnyClass can be used to make it even more succinct.

With deepseq >= 1.4, this autoderiving Generic option is included with the library. With deepseq <= 1.3 you'll have to use the deepseq-generics library as well.

GADTs

With more complex datatypes, like GADTs and those existentially quantified, DeriveGeneric does not work. You will need to provide an instance for NFData yourself, but not to worry as it follows a pattern:

{-# LANGUAGE GADTs #-}

import Control.DeepSeq (NFData)

data Expr t where
  IntVal :: Int -> Expr Int
  BoolVal :: Bool -> Expr Bool
  Add :: Expr Int -> Expr Int -> Expr Int

instance NFData (Expr t) where
  rnf expr = case expr of
    IntVal i  -> rnf i -- call rnf on every subvalue
    BoolVal b -> rnf b
    Add l r   -> rnf l `seq` rnf r -- and `seq` multiple values together

-- Now we can test expressions like:
badExpr = Add (IntVal 4) (BoolVal True)
-- do not typecheck!

If you forget to specify an NFData instance for a type should-not-typecheck should warn you.

Motivation

Sometimes you want to ensure that it is impossible to type a particular expression. For example, imagine if we were making a typesafe Abstract Syntax Tree of mathematical expressions:

{-# LANGUAGE GADTs #-}

data Expr t where
  IntVal :: Int -> Expr Int
  BoolVal :: Bool -> Expr Bool
  Add :: Expr Int -> Expr Int -> Expr Int
  -- ...

We might want to make sure that Add (BoolVal True) (IntVal 4) is not well typed. However, we can't even compile code like this to put in a unit test! This is where should-not-typecheck steps in.

Limitations

Unfortunately, we can only turn on deferred type errors for the entire test file rather than just specific expressions. This means that any type error will compile but fail at runtime. For example:

{-# OPTIONS_GHC -fdefer-type-errors #-}

-- ...

main :: IO ()
main = hspec $ do
  describe 4 $ do -- Oops!
   -- ...

Will create a warning at compile time but not an error. All of the ill-typed expressions we are testing will also produce warnings and it will be hard to immediately see which ones matter. The upside is that the test-suite will still fail if there are errors.

Workaround

You can separate out the ill-typed expressions we are testing and test boilerplate into separate files and only turn on deferred type errors for the expressions. This means that type errors in test code will still be found at compile time. The downside is your tests may now be harder to read.

should-not-typecheck's People

Contributors

crogers avatar ggreif avatar markus1189 avatar

Watchers

 avatar  avatar

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    ๐Ÿ–– Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. ๐Ÿ“Š๐Ÿ“ˆ๐ŸŽ‰

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google โค๏ธ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.