StrictCheck-0.1.0: StrictCheck: Keep Your Laziness In Check

Safe HaskellNone
LanguageHaskell2010

Test.StrictCheck.Examples.Map

Description

This module showcases another type of specification different from those in Test.StrictCheck.Examples.Lists. Here, we demonstrate that StrictCheck is able to distinguish value-lazy maps from value-strict maps.

In this module, we first develop the solution of the Knapsack dynamic programming problem by taking the fixpoint of a step function of the solution table. We represent the solution table with a map, and write a specification that is critical for the termination of this solution.

Synopsis

Documentation

data Map k v Source #

We roll our own map type to avoid dealing with abstract types.

Constructors

Bin (Map k v) k v (Map k v)

A node that contains a key value pair

Empty

An empty node

Instances

Arbitrary KMap Source #

The customized generator for solution tables that only generates valid pre-fixpoints.

Methods

arbitrary :: Gen KMap #

shrink :: KMap -> [KMap] #

Produce KMap Source #

A dummy produce instance for the solution table.

Methods

produce :: Gen KMap Source #

(Eq v, Eq k) => Eq (Map k v) Source # 

Methods

(==) :: Map k v -> Map k v -> Bool #

(/=) :: Map k v -> Map k v -> Bool #

(Ord v, Ord k) => Ord (Map k v) Source # 

Methods

compare :: Map k v -> Map k v -> Ordering #

(<) :: Map k v -> Map k v -> Bool #

(<=) :: Map k v -> Map k v -> Bool #

(>) :: Map k v -> Map k v -> Bool #

(>=) :: Map k v -> Map k v -> Bool #

max :: Map k v -> Map k v -> Map k v #

min :: Map k v -> Map k v -> Map k v #

(Show v, Show k) => Show (Map k v) Source # 

Methods

showsPrec :: Int -> Map k v -> ShowS #

show :: Map k v -> String #

showList :: [Map k v] -> ShowS #

Generic (Map k v) Source # 

Associated Types

type Rep (Map k v) :: * -> * #

Methods

from :: Map k v -> Rep (Map k v) x #

to :: Rep (Map k v) x -> Map k v #

Generic (Map k v) Source # 

Associated Types

type Code (Map k v) :: [[*]] #

Methods

from :: Map k v -> Rep (Map k v) #

to :: Rep (Map k v) -> Map k v #

HasDatatypeInfo (Map k v) Source # 

Associated Types

type DatatypeInfoOf (Map k v) :: DatatypeInfo #

Methods

datatypeInfo :: proxy (Map k v) -> DatatypeInfo (Code (Map k v)) #

(Consume v, Consume k) => Consume (Map k v) Source # 

Methods

consume :: Map k v -> Input Source #

(Shaped v, Shaped k) => Shaped (Map k v) Source # 

Associated Types

type Shape (Map k v) :: (* -> *) -> * Source #

Methods

project :: (forall x. Shaped x => x -> f x) -> Map k v -> Shape (Map k v) f Source #

embed :: (forall x. Shaped x => f x -> x) -> Shape (Map k v) f -> Map k v Source #

match :: Shape (Map k v) f -> Shape (Map k v) g -> (forall (xs :: [*]). All * Shaped xs => Flattened * (Shape (Map k v)) f xs -> Maybe (Flattened * (Shape (Map k v)) g xs) -> result) -> result Source #

render :: Shape (Map k v) (K * x) -> RenderLevel x Source #

type Rep (Map k v) Source # 
type Code (Map k v) Source # 
type Code (Map k v) = GCode (Map k v)
type DatatypeInfoOf (Map k v) Source # 
type Shape (Map k v) Source # 
type Shape (Map k v) = GShape (Map k v)

type KMap = Map (Int, Int) Int Source #

A specialized map useful for knapsack. The pair of ints represent the two parameters to each knapsack sub-problem solved along the way. These two parameters determine the subsequence of items each sub-problem is concerned with, and the weight limit.

pattern Empty' :: Demand (Map (k :: Type) (v :: Type)) Source #

pattern Bin' :: Demand (Map k v) -> Demand k -> Demand v -> Demand (Map k v) -> Demand (Map (k :: Type) (v :: Type)) Source #

replaceThunk :: (Shaped k, Shaped v) => Map k v -> Map k v -> Map k v Source #

This replaces the thunk in a map partial value with the r parameter. This is very similar to the cap function in the lists example.

fromList :: [((Int, Int), Int)] -> KMap Source #

A helper for building a map from a list of values.

insert :: Ord k => k -> v -> Map k v -> Map k v Source #

A simplified insert that ignores rebalancing since rebalancing is not important for the spec we will write.

lookup :: KMap -> (Int, Int) -> Maybe Int Source #

The lookup function specialized for knapsack.

keys :: Map k v -> [k] Source #

This function extracts all of the keys of a map.

(!) :: KMap -> (Int, Int) -> Int Source #

A lookup function that returns the default value `0` for keys that are not in the map. This saves us from doing repeated pattern matching when querying the solution table.

weights :: [Int] Source #

Weight parameters to the knapsack problem.

values :: [Int] Source #

Value parameters to the knapsack problem, note that this must be the same length as weights.

limit :: Int Source #

The weight limit of the knapsack problem.

solutionStep :: Map (Int, Int) Int -> Map (Int, Int) Int Source #

One step of the knapsack computation. This is a direct translation from the recurrence relation of the knapsack problem.

solution :: Map (Int, Int) Int Source #

The fixpoint of the recurrence relation, which is also the solution for the knapsack problem.

pattern Pair' :: Demand a -> Demand b -> Demand (a, b) Source #

A pattern synonym for extracting demands of each component from the demand of a pair.

iterSolution :: (Int, Int) -> Int -> Map (Int, Int) Int -> Maybe Int Source #

This function computes the nth pre-fixpoint of the knapsack solution, and looks up the value at the specified cell from the pre-fixpoint.

iterSolutionWithKey :: Key -> Int -> Map (Int, Int) Int -> Maybe Int Source #

This is the same as iterSolution, but uses a newtype wrapper for the index into the map since we want to write a customized Arbitrary instance for Key.

newtype Key Source #

The newtype wrapper of index into the knapsack solution table.

Constructors

Key 

Fields

Instances

Eq Key Source # 

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Ord Key Source # 

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

(>=) :: Key -> Key -> Bool #

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key Source # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Arbitrary Key Source #

The customized generator for Key that only generates valid keys given the problem parameters.

Methods

arbitrary :: Gen Key #

shrink :: Key -> [Key] #

Generic Key Source # 

Associated Types

type Code Key :: [[*]] #

Methods

from :: Key -> Rep Key #

to :: Rep Key -> Key #

HasDatatypeInfo Key Source # 

Associated Types

type DatatypeInfoOf Key :: DatatypeInfo #

Methods

datatypeInfo :: proxy Key -> DatatypeInfo (Code Key) #

Consume Key Source # 

Methods

consume :: Key -> Input Source #

Produce Key Source #

A dummy produce instance for the index into the solution table.

Methods

produce :: Gen Key Source #

Shaped Key Source # 

Associated Types

type Shape Key :: (* -> *) -> * Source #

Methods

project :: (forall x. Shaped x => x -> f x) -> Key -> Shape Key f Source #

embed :: (forall x. Shaped x => f x -> x) -> Shape Key f -> Key Source #

match :: Shape Key f -> Shape Key g -> (forall (xs :: [*]). All * Shaped xs => Flattened * (Shape Key) f xs -> Maybe (Flattened * (Shape Key) g xs) -> result) -> result Source #

render :: Shape Key (K * x) -> RenderLevel x Source #

type Rep Key Source # 
type Rep Key = D1 * (MetaData "Key" "Test.StrictCheck.Examples.Map" "StrictCheck-0.1.0-GjX4F07u34LCxxlyaDL9Ok" True) (C1 * (MetaCons "Key" PrefixI True) (S1 * (MetaSel (Just Symbol "getKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Int, Int))))
type Code Key Source # 
type Code Key = GCode Key
type DatatypeInfoOf Key Source # 
type Shape Key Source # 

runMapTest :: IO () Source #

This IO action ties the spec together with everything built so far, and runs the StrictCheck randomized testing framework.

iterSolution_spec :: Evaluation '[Key, Int, KMap] (Maybe Int) -> Maybe (Int, Int) Source #

This is the specification that establishes a property important for the termination of solution: given any pre-fixpoint of `pre-solution`, forcing the value at pre-solution[i][j] should not induce a demand at the (i, j) cell of the input that steps to pre-solution, since otherwise this would be an infinite loop in the fixpoint. The value-lazy Map defined in this module satisfies this property. However, if we make this Map value-strict using BangPatterns, StrictCheck will report a failure when runMapTest is executed.