Skip to content

Commit

Permalink
first commit of mockfree
Browse files Browse the repository at this point in the history
  • Loading branch information
jdegoes committed May 21, 2016
0 parents commit 98e5d37
Show file tree
Hide file tree
Showing 5 changed files with 313 additions and 0 deletions.
6 changes: 6 additions & 0 deletions .gitignore
@@ -0,0 +1,6 @@
/bower_components/
/node_modules/
/.pulp-cache/
/output/
/.psci*
/src/.webpack.js
92 changes: 92 additions & 0 deletions README.md
@@ -0,0 +1,92 @@
# purescript-mockfree

`mockfree` is a purely-functional, strongly-typed mocking library for all PureScript programs that are defined by [Free](https://github.com/purescript/purescript-free) algebras.

While a proof-of-concept for a [LambdaConf 2016 talk](http://github.com/lambdaconf/lambdaconf-2016-usa), the library is nonetheless completely usable, and demonstrates the power of modeling effectful computation through descriptive data structures.

- [Module Documentation](docs/Test/Mock/Mockfree.md)
- [Example](test/Main.purs)

## Building

bower install purescript-mockfree
pulp build
pulp test

## Introduction

Integration and system testing often require writing tests that perform *effects*, such as writing to a file system or connecting to a remote API.

The problem with such tests is that they verify far more than the logic of your program: they test the reliability of third-party software and systems.

As a result, integration and system tests are often indeterministic and error-prone. In addition, because these tests often run slowly and have complex dependencies, they are not as useful to developers as unit and property tests, which run very fast and have no dependencies.

The industry has invented *mocking* as a solution to these problems. However, mocking usually sacrifices type safety, and requires a powerful dynamic programming language, or lots of hacks or code rewriting.

With a purely-functional programming language such as PureScript, we have an alternative: `Free` programs.

`Free` programs allow us to describe the effects of our program using data structures. These data structures can later be interpreted into effectful operations. However, they can also be interpreted into *non-effectful* operations that do *not* interact with external systems.

If you program in this style, then `mockfree` will let you trivially test the logic of your programs with purely-functional, strongly-typed mocks, which can be parallelized, which run in-memory, and which are completely deterministic.

Combined with a way of testing your program's final interpreters, functional mocking can totally transform the way you test functional code that has complex interactions with external systems.

With `Free`, you can test final interpreters separately, one time, in their own library; and you can test your program logic exclusively through functional mocking. All tests become fast, deterministic, and completely self-contained!

## Tutorial

Let's define a console program with the following operations:

```purescript
data ConsoleF a
= WriteLine (Op String Unit a)
| ReadLine (Op Unit String a)
```

Each operation `Op a b c` requires that we supply an `a` in order to get access to a `b`.

For example, a "write line" operation requires that we supply a `String`, and gives us access to a `Unit` value (i.e. no information), while a "read line" operation requires that we supply a `Unit` (i.e. no information) to get access to a `String`.

The `mockfree` library requires that we define polymorphic [prisms](http://github.com/purescript-contrib/purescript-profunctor-lenses) for each term in our operational algebra:

```purescript
_WriteLine :: OpPrism ConsoleF String Unit
_ReadLine :: OpPrism ConsoleF Unit String
```

While these prisms are required for `mockfree`, they are also useful for working with our algebra, and they can be shared with production code!

Once the prisms have been defined, we can create a mock spec using some combination of `expect` (for read-write operations), `expectRead` (for read-only operations), and `expectWrite` (for write-only operations):

```purescript
mockSpec :: MockSpec ConsoleF
mockSpec = do
expectWrite _WriteLine (assertEquals "What is your name?")
expectRead _ReadLine "World"
expectWrite _WriteLine (assertEquals "Hello, World!")
```

These specs can be run against a program using `runMock`:

```purescript
runMock mockSpec program :: Either String Unit
```

where `program` is a program defined by sequential execution of the individual operations:

```purescript
program :: Free ConsoleF Unit
program = do
writeOp _WriteLine "What is your name?"
name <- readOp _ReadLine
writeOp _WriteLine ("Hello, " ++ name ++ "!")
```

## Future Work

There are several ways this library could be improved:

1. **Add support for branching programs.** Currently, the mock spec is a linear sequence of instructions. Ideally, it would be a tree that forks based on runtime values and allows alternatives.
2. **Add support for infinite mock specs.** Currently, the mock spec can only model finite, bounded programs.
3. **Factor out Assertion into a library.** Currently, there is no PureScript library for non-effectful assertions that generate nice, composable errors.
4. **Factor out the Op type & helpers into a library.** These could be useful in building `Free` programs, not just in testing them.
32 changes: 32 additions & 0 deletions bower.json
@@ -0,0 +1,32 @@
{
"name": "purescript-mockfree",
"description": "A purely-functional, strongly-typed functional mocking library for Free programs",
"authors": [
"John A. De Goes <john@degoes.net>"
],
"license": "Apache 2",
"version": "0.1.0",
"moduleType": [
"node"
],
"ignore": [
"**/.*",
"node_modules",
"bower_components",
"output"
],
"dependencies": {
"purescript-profunctor-lenses": "^1.0.0-rc.1",
"purescript-free": "^1.0.0-rc.1",
"purescript-console": "^v1.0.0-rc.1",
"purescript-either": "^v1.0.0-rc.1",
"purescript-maybe": "^1.0.0-rc.1",
"purescript-foldable-traversable": "^1.0.0-rc.1",
"purescript-monoid": "^1.0.0-rc.2",
"purescript-bifunctors": "^1.0.0-rc.1",
"purescript-invariant": "^1.0.0-rc.1",
"purescript-prelude": "^1.0.0-rc.4",
"purescript-control": "^1.0.0-rc.1",
"purescript-transformers": "^1.0.0-rc.1"
}
}
96 changes: 96 additions & 0 deletions src/Test/Mock/Mockfree.purs
@@ -0,0 +1,96 @@
module Test.Mock.Mockfree
( Assertion()
, Op(..)
, OpPrism()
, MockOp(..)
, MockSpec()
, assertEquals
, expect
, expectRead
, expectWrite
, op
, readOp
, runMock
, writeOp
) where

import Prelude(class Show, class Eq, Unit(), ($), (<<<), (>>=), (<$>), (<>), (==), bind, const, id, pure, show, unit)

import Data.Either(Either(..))
import Data.List(List(..), length, reverse)
import Data.Lens.Types(PrismP())
import Data.Lens.Prism(review)
import Data.Lens.Fold(preview)
import Data.Maybe(maybe)
import Data.Tuple(Tuple(..))

import Control.Monad.State.Trans(StateT(), runStateT)
import Control.Monad.Free(Free(), foldFree, liftF)
import Control.Monad.Trans(lift)
import Control.Monad.State(State(), execState, get, modify, put)

-- ***************************************************************************
data Op a b c = Op a (b -> c)

type OpPrism f a b = forall c. PrismP (f c) (Op a b c)

-- | A helper function to create a read-only operation.
readOp :: forall f b. OpPrism f Unit b -> Free f b
readOp p = op p unit

-- | A helper function to create a write-and-read operation.
op :: forall f a b. OpPrism f a b -> a -> Free f b
op p a = liftF $ review p (Op a id)

-- | A helper function to create a write-only operation.
writeOp :: forall f a. OpPrism f a Unit -> a -> Free f Unit
writeOp p a = op p a

-- ***************************************************************************
type Assertion a = a -> Either String Unit

-- | Creates an assertion that asserts values are equal to the specified
-- | reference value.
assertEquals :: forall a. (Show a, Eq a) => a -> Assertion a
assertEquals e a = if e == a then Right unit else Left $ "Expected " <> show e <> " but found " <> show a

-- | Creates an expectation for an arbitrary `f` operation.
expect :: forall f a b. OpPrism f a b -> Assertion a -> (a -> b) -> MockSpec f
expect p a f = modify (Cons (MockOp (\f' -> f' p a f)))

-- | Creates an expectation for a read-only `f` operation.
expectRead :: forall f b. OpPrism f Unit b -> b -> MockSpec f
expectRead p b = expect p (const $ pure unit) (const b)

-- | Creates an expectation for a write-only `f` operation.
expectWrite :: forall f a. OpPrism f a Unit -> Assertion a -> MockSpec f
expectWrite p a = expect p a (const unit)

-- ***************************************************************************
data MockOp f = MockOp (forall z. (forall a b. OpPrism f a b -> Assertion a -> (a -> b) -> z) -> z)

type MockSpec f = State (List (MockOp f)) Unit

-- | Attempts to execute a single operation using a mock op, returning an
-- | error message if the expectation fails.
runOp :: forall f c. MockOp f -> f c -> Either String c
runOp (MockOp fold) fc =
fold (\prism assert aToB -> maybe (Left "Unexpected operation") (\(Op a bToC) -> const (bToC (aToB a)) <$> assert a) $ preview prism fc)

-- | Attempts to execute a Free program against a mock spec, returning an
-- | error message if the expectations are not met.
runMock :: forall f a0. MockSpec f -> Free f a0 -> Either String a0
runMock spec program = runStateT (foldFree transform program) (reverse $ execState spec Nil) >>= finalize
where
finalize :: forall a. Tuple a (List (MockOp f)) -> Either String a
finalize (Tuple a Nil) = Right a
finalize (Tuple a v) = Left $ "Unexpected early termination (" <> show (length v) <> " operation(s) remaining)"

transform :: forall a. f a -> StateT (List (MockOp f)) (Either String) a
transform fa = do
ops <- get
case ops of
Nil -> lift (Left "Unexpected operation after end of mock spec" :: Either String a)
Cons op' ops' -> do
put ops'
lift $ runOp op' fa
87 changes: 87 additions & 0 deletions test/Main.purs
@@ -0,0 +1,87 @@
module Test.Main where

import Prelude(Unit, (<>), ($), bind, const, pure, unit)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, log)
import Control.Monad.Free(Free(), liftF)

import Data.Either(either)
import Data.Maybe(Maybe(..))
import Data.Lens.Prism(prism')

import Test.Mock.Mockfree(Op(..), OpPrism(), MockSpec(), assertEquals, expectWrite, expectRead, readOp, runMock, writeOp)

data ConsoleF a
= WriteLine (Op String Unit a)
| ReadLine (Op Unit String a)

_WriteLine :: OpPrism ConsoleF String Unit
_WriteLine = prism' WriteLine deconstruct
where
deconstruct (WriteLine op) = Just op
deconstruct _ = Nothing

_ReadLine :: OpPrism ConsoleF Unit String
_ReadLine = prism' ReadLine deconstruct
where
deconstruct (ReadLine op) = Just op
deconstruct _ = Nothing

readLine :: Free ConsoleF String
readLine = readOp _ReadLine

writeLine :: String -> Free ConsoleF Unit
writeLine s = writeOp _WriteLine s

-- | Defines a mock specification for a program in `ConsoleF`.
mockSpec :: MockSpec ConsoleF
mockSpec = do
expectWrite _WriteLine (assertEquals "What is your name?")
expectRead _ReadLine "World"
expectWrite _WriteLine (assertEquals "Hello, World!")

goodProgram :: Free ConsoleF Unit
goodProgram = do
writeLine "What is your name?"
name <- readLine
writeLine ("Hello, " <> name <> "!")

informalProgram :: Free ConsoleF Unit
informalProgram = do
writeLine "What is your first name?"
name <- readLine
writeLine ("Hello, " <> name <> "!")

rudeProgram :: Free ConsoleF Unit
rudeProgram = do
writeLine "What is your name?"
writeLine ("I don't care!")

dismissiveProgram :: Free ConsoleF Unit
dismissiveProgram = do
writeLine "What is your name?"
name <- readLine
writeLine ("Goodbye, " <> name <> "!")

emptyProgram :: Free ConsoleF Unit
emptyProgram = pure unit

testProgram :: Free ConsoleF Unit -> String
testProgram program = either ((<>) "Failure: ") (const "Success!") (runMock mockSpec program)

main :: forall e. Eff (console :: CONSOLE | e) Unit
main = do
log "Testing good program"
log $ testProgram goodProgram

log "Testing informal program"
log $ testProgram informalProgram

log "Testing rude program"
log $ testProgram rudeProgram

log "Testing dismissive program"
log $ testProgram dismissiveProgram

log "Testing empty program"
log $ testProgram emptyProgram

0 comments on commit 98e5d37

Please sign in to comment.