Pattern for generic unit test of type class instance implementations in Haskell - haskell

I was wondering if there was a known pattern for writing generic unit test code whose purpose it is to check (as a black box) the various instance (implementation of) a type class. For example:
import Test.HUnit
class M a where
foo :: a -> String
cons :: Int -> a -- some constructor
data A = A Int
data B = B Int
instance M A where
foo _ = "foo"
cons = A
instance M B where
foo _ = "bar" -- implementation error
cons = B
I would like to write a function tests returning a Test with some way of specifying to tests the particular instance to which the code applies. I was thinking adding teststo the definition of the class with a default implementation (ignoring the coupling issue between testing code and actual code for now), but I can't simply have tests :: Test, and even if I try tests:: a -> Test (so having to artificially pass a concrete element of the given type to call the function), I cannot figure out how to refer to cons and foo inside the code (type annotations like (cons 0) :: a won't do).
Assuming I have class (Eq a) => M a where ... instead, with types A and B deriving Eq, I could trick the compiler with something like (added to the definition of M):
tests :: a -> Test
tests x = let
y = (cons 0)
z = (x == y) -- compiler now knows y :: a
in
TestCase (assertEqual "foo" (foo y) "foo")
main = do
runTestTT $ TestList
[ tests (A 0)
, tests (B 0)
]
But this is all very ugly to me. Any suggestion is warmly welcome

Proxy
The current most common way of making a function polymorphic in an "internal" type is to pass a Proxy. Proxy has a single nullary constructor like (), but its type carries a phantom type. This avoids having to pass undefined or dummy values. Data.Proxy.asProxyTypeOf can then be used as an annotation.
tests :: M a => Proxy a -> Test
tests a = TestCase (assertEqual "foo" (foo (cons 0 `asProxyTypeOf` a)) "foo")
proxy
We can also generalize that type, as the Proxy is not actually being needed as a value. It's just a way of making a type variable non-ambiguous. You need to redefine asProxyTypeOf though. This is mostly a matter of style compared to the previous one. Being able to use more values as potential proxies can make some code more concise, sometimes at the cost of readability.
-- proxy is a type variable of kind * -> *
tests :: M a => proxy a -> Test
tests a = TestCase (assertEqual "foo" (foo (cons 0 `asProxyTypeOf` a)) "foo")
where
asProxyTypeOf :: a -> proxy a -> a
asProxyTypeOf = const
Scoped type variables
The function asProxyTypeOf, or your (==) trick are really a product of the inability to refer to a type variable from a signature. This is in fact allowed by the ScopedTypeVariables+RankNTypes extensions.
Explicit quantification brings the variable a into scope in the body of the function.
tests :: forall a proxy. M a => proxy a -> Test
tests _ = TestCase (assertEqual "foo" (foo (cons 0 :: a)) "foo") -- the "a" bound by the top-level signature.
Without the ScopedTypeVariables extension, cons 0 :: a would be interpreted as cons 0 :: forall a. a instead.
Here's how you use these functions:
main = runTestTT $ TestList
[ tests (Proxy :: Proxy A)
, tests (Proxy :: Proxy B)
]
Type applications
Since GHC 8, the AllowAmbiguousTypes+TypeApplications extensions make the Proxy argument unnecessary.
tests :: forall a. M a => Test
tests = TestCase (assertEqual "foo" (foo (cons 0 :: a)) "foo") -- the "a" bound by the top-level signature.
main = runTestTT $ TestList
[ tests #A
, tests #B
]

Related

Binary instance for Static Pointers

I have the following data type
data Foo a b = A (StaticPtr (a -> b)) deriving (Generic, Typeable)
I want to generate the Binary instance for this type so I can use this function on a remote node.
However, using automatic Binary instantiation doesn't work here:
instance (Binary a, Binary b) => Binary (Foo a b)
This results in
• Could not deduce (Binary (StaticPtr (a -> b)))
arising from a use of ‘binary-0.8.5.1:Data.Binary.Class.$dmput’
from the context: (Binary a, Binary b)
bound by the instance declaration
at /Users/abhiroop/Haskell/snape/app/Spec.hs:23:10-49
• In the expression:
binary-0.8.5.1:Data.Binary.Class.$dmput #Foo a b
In an equation for ‘binary-0.8.5.1:Data.Binary.Class.put’:
binary-0.8.5.1:Data.Binary.Class.put
= binary-0.8.5.1:Data.Binary.Class.$dmput #Foo a b
In the instance declaration for ‘Binary (Foo a b)’
• Could not deduce (Binary (StaticPtr (a -> b)))
arising from a use of ‘binary-0.8.5.1:Data.Binary.Class.$dmget’
from the context: (Binary a, Binary b)
bound by the instance declaration
at /Users/abhiroop/Haskell/snape/app/Spec.hs:23:10-49
• In the expression:
binary-0.8.5.1:Data.Binary.Class.$dmget #Foo a b
In an equation for ‘binary-0.8.5.1:Data.Binary.Class.get’:
binary-0.8.5.1:Data.Binary.Class.get
= binary-0.8.5.1:Data.Binary.Class.$dmget #Foo a b
In the instance declaration for ‘Binary (Foo a b)’
How do I auto generate the Binary instance here?
You can serialize a StaticPtr as a Fingerprint via staticKey and deserialize it via unsafeLookupStaticPtr below it.
You can't define a Binary instance for StaticPtr (even if you wrap it in a newtype to avoid orphans) because the lookup cannot be done purely. But you can still define and use the serializer and deserializer as regular, nonoverloaded functions.
Li-yao Xia's answer is correct. But I had to change my data types, in general, to pass them remotely. I am writing my changes here so it might be useful if someone wants to send a function remotely, there isn't many resources on this online.
So instead of having
data Foo a b = A (StaticPtr (a -> b))
I have changed my data types to look like this:
data Foo a b = A (a -> b)
or to simplify
data Foo f = A f
Here f is the function I want to send remotely.
So taking a simple example of a function like (+ 1) and imagine I want to map this over a list [1,2,3] which is present remotely. My code becomes like this:
main :: IO [Int]
main = do
let list = [1,2,3]
a = static (A (+ 1)) :: StaticPtr (Foo (Int -> Int))
t = staticKey a
-- assuming you sent t to the remote node
-- code on the remote node
x <- unsafeLookupStaticPtr t
case x of
Just sptr -> case deRefStaticPtr sptr of
A f -> return $ map f list
_ -> error "Task undefined"
Nothing -> error "Wrong function serialized"

Defining a suite of tests for a class

This question picks up where Haskell QuickCheck best practices (especially when testing type classes) left off.
I have a class and a bunch of implementations of that class. Something like this:
import Test.QuickCheck
import Control.Applicative
import Test.Framework
import Test.Framework.Providers.QuickCheck2
class C c where
f :: c -> Int
data A = A Int deriving Show
instance C A where
f (A a) = 2*a
data B = B Int deriving Show
instance C B where
f (B b) = 2*b
All of my implementations should satisfy a certain property. For example:
prop_f_is_even :: C c => c -> Property
prop_f_is_even x = property $ even (f x)
I want to test that property for each of the implementations. I can do something like this. (I'm using Test.Framework.)
instance Arbitrary A where
arbitrary = A <$> arbitrary
instance Arbitrary B where
arbitrary = B <$> arbitrary
test :: Test
test = testGroup "Whole buncha tests"
[
testProperty "prop_f_is_even - A" (prop_f_is_even :: A -> Property),
testProperty "prop_f_is_even - B" (prop_f_is_even :: B -> Property)
-- continue on for all combinations of properties and implementations
]
But in my case, I have dozens of properties to test, and a dozen or so
classes, so that approach is error-prone, and a hassle.
(A common mistake I make is to cut-and paste tests, but forget to change
the type name, so I end up testing A twice for that property, without testing B.)
I have a solution, which I'll post below in case anyone else finds it helpful.
This is my solution.
cProperties :: C t => String -> [(String, t -> Property)]
cProperties s =
[
("prop_f_is_even: " ++ s, prop_f_is_even)
-- plus any other tests that instances of C should satisfy
]
makeTests :: (Arbitrary t, Show t) => [(String, t -> Property)] -> [Test]
makeTests ts = map (\(s,t) -> testProperty s t) ts
aProperties :: [(String, A -> Property)]
aProperties = cProperties "A"
bProperties :: [(String, B -> Property)]
bProperties = cProperties "B"
easierTest :: Test
easierTest =
testGroup "tests" (makeTests aProperties ++ makeTests bProperties)
With this approach, if I want to add another property that all instances of C should satisfy, I just add it to cProperties. And if I create another instance of C, call it D, then I define dProperties similarly to aProperties and bProperties, and then update easierTest.
EDIT:
One disadvantage of this approach is that all tests in cProperties have to have the type signature t -> Property. I myself have not found this to be a hindrance because in cases where I apply this technique, I have already -- for unrelated reasons -- defined a type that encompasses all of the data for a test.
Another disadvantage is that, in ghci, I can no longer type, for example:
quickCheck prop_f_is_even
Now I have to type something like this:
quickCheck (prop_f_is_even :: A -> Property)

Haskell: how to write a monadic variadic function, with parameters using the monadic context

I'm trying to make a variadic function with a monadic return type, whose parameters also require the monadic context. (I'm not sure how to describe that second point: e.g. printf can return IO () but it's different in that its parameters are treated the same whether it ends up being IO () or String.)
Basically, I've got a data constructor that takes, say, two Char parameters. I want to provide two pointer style ID Char arguments instead, which can be automagically decoded from an enclosing State monad via a type class instance. So, instead of doing get >>= \s -> foo1adic (Constructor (idGet s id1) (idGet s id2)), I want to do fooVariadic Constructor id1 id2.
What follows is what I've got so far, Literate Haskell style in case somebody wants to copy it and mess with it.
First, the basic environment:
> {-# LANGUAGE FlexibleContexts #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> import Control.Monad.Trans.State
> data Foo = Foo0
> | Foo1 Char
> | Foo2 Bool Char
> | Foo3 Char Bool Char
> deriving Show
> type Env = (String,[Bool])
> newtype ID a = ID {unID :: Int}
> deriving Show
> class InEnv a where envGet :: Env -> ID a -> a
> instance InEnv Char where envGet (s,_) i = s !! unID i
> instance InEnv Bool where envGet (_,b) i = b !! unID i
Some test data for convenience:
> cid :: ID Char
> cid = ID 1
> bid :: ID Bool
> bid = ID 2
> env :: Env
> env = ("xy", map (==1) [0,0,1])
I've got this non-monadic version, which simply takes the environment as the first parameter. This works fine but it's not quite what I'm after. Examples:
$ mkFoo env Foo0 :: Foo
Foo0
$ mkFoo env Foo3 cid bid cid :: Foo
Foo3 'y' True 'y'
(I could use functional dependencies or type families to get rid of the need for the :: Foo type annotations. For now I'm not fussed about it, since this isn't what I'm interested in anyway.)
> mkFoo :: VarC a b => Env -> a -> b
> mkFoo = variadic
>
> class VarC r1 r2 where
> variadic :: Env -> r1 -> r2
>
> -- Take the partially applied constructor, turn it into one that takes an ID
> -- by using the given state.
> instance (InEnv a, VarC r1 r2) => VarC (a -> r1) (ID a -> r2) where
> variadic e f = \aid -> variadic e (f (envGet e aid))
>
> instance VarC Foo Foo where
> variadic _ = id
Now, I want a variadic function that runs in the following monad.
> type MyState = State Env
And basically, I have no idea how I should proceed. I've tried expressing the type class in different ways (variadicM :: r1 -> r2 and variadicM :: r1 -> MyState r2) but I haven't succeeded in writing the instances. I've also tried adapting the non-monadic solution above so that I somehow "end up" with an Env -> Foo which I could then easily turn into a MyState Foo, but no luck there either.
What follows is my best attempt thus far.
> mkFooM :: VarMC r1 r2 => r1 -> r2
> mkFooM = variadicM
>
> class VarMC r1 r2 where
> variadicM :: r1 -> r2
>
> -- I don't like this instance because it requires doing a "get" at each
> -- stage. I'd like to do it only once, at the start of the whole computation
> -- chain (ideally in mkFooM), but I don't know how to tie it all together.
> instance (InEnv a, VarMC r1 r2) => VarMC (a -> r1) (ID a -> MyState r2) where
> variadicM f = \aid -> get >>= \e -> return$ variadicM (f (envGet e aid))
>
> instance VarMC Foo Foo where
> variadicM = id
>
> instance VarMC Foo (MyState Foo) where
> variadicM = return
It works for Foo0 and Foo1, but not beyond that:
$ flip evalState env (variadicM Foo1 cid :: MyState Foo)
Foo1 'y'
$ flip evalState env (variadicM Foo2 cid bid :: MyState Foo)
No instance for (VarMC (Bool -> Char -> Foo)
(ID Bool -> ID Char -> MyState Foo))
(Here I would like to get rid of the need for the annotation, but the fact that this formulation needs two instances for Foo makes that problematic.)
I understand the complaint: I only have an instance that goes from Bool ->
Char -> Foo to ID Bool -> MyState (ID Char -> Foo). But I can't make the
instance it wants because I need MyState in there somewhere so that I can
turn the ID Bool into a Bool.
I don't know if I'm completely off track or what. I know that I could solve my basic issue (I don't want to pollute my code with the idGet s equivalents all over the place) in different ways, such as creating liftA/liftM-style functions for different numbers of ID parameters, with types like (a -> b -> ... -> z -> ret) -> ID a -> ID b -> ... -> ID z -> MyState ret, but I've spent too much time thinking about this. :-) I want to know what this variadic solution should look like.
WARNING
Preferably don't use variadic functions for this type of work. You only have a finite number of constructors, so smart constructors don't seem to be a big deal. The ~10-20 lines you would need are a lot simpler and more maintainable than a variadic solution. Also an applicative solution is much less work.
WARNING
The monad/applicative in combination with variadic functions is the problem. The 'problem' is the argument addition step used for the variadic class. The basic class would look like
class Variadic f where
func :: f
-- possibly with extra stuff
where you make it variadic by having instances of the form
instance Variadic BaseType where ...
instance Variadic f => Variadic (arg -> f) where ...
Which would break when you would start to use monads. Adding the monad in the class definition would prevent argument expansion (you would get :: M (arg -> f), for some monad M). Adding it to the base case would prevent using the monad in the expansion, as it's not possible (as far as I know) to add the monadic constraint to the expansion instance. For a hint to a complex solution see the P.S..
The solution direction of using a function which results in (Env -> Foo) is more promising. The following code still requires a :: Foo type constraint and uses a simplified version of the Env/ID for brevity.
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}
module Test where
data Env = Env
data ID a = ID
data Foo
= Foo0
| Foo1 Char
| Foo2 Char Bool
| Foo3 Char Bool Char
deriving (Eq, Ord, Show)
class InEnv a where
resolve :: Env -> ID a -> a
instance InEnv Char where
resolve _ _ = 'a'
instance InEnv Bool where
resolve _ _ = True
The Type families extension is used to make the matching stricter/better. Now the variadic function class.
class MApp f r where
app :: Env -> f -> r
instance MApp Foo Foo where
app _ = id
instance (MApp r' r, InEnv a, a ~ b) => MApp (a -> r') (ID b -> r) where
app env f i = app env . f $ resolve env i
-- using a ~ b makes this instance to match more easily and
-- then forces a and b to be the same. This prevents ambiguous
-- ID instances when not specifying there type. When using type
-- signatures on all the ID's you can use
-- (MApp r' r, InEnv a) => MApp (a -> r') (ID a -> r)
-- as constraint.
The environment Env is explicitly passed, in essence the Reader monad is unpacked preventing the problems between monads and variadic functions (for the State monad the resolve function should return a new environment). Testing with app Env Foo1 ID :: Foo results in the expected Foo1 'a'.
P.S.
You can get monadic variadic functions to work (to some extent) but it requires bending your functions (and mind) in some very strange ways. The way I've got such things to work is to 'fold' all the variadic arguments into a heterogeneous list. The unwrapping can then be done monadic-ally. Though I've done some things like that, I strongly discourage you from using such things in actual (used) code as it quickly gets incomprehensible and unmaintainable (not to speak of the type errors you would get).

Binary instance for an existential

Given an existential data type, for example:
data Foo = forall a . (Typeable a, Binary a) => Foo a
I'd like to write instance Binary Foo. I can write the serialisation (serialise the TypeRep then serialise the value), but I can't figure out how to write the deserialisation. The basic problem is that given a TypeRep you need to map back to the type dictionary for that type - and I don't know if that can be done.
This question has been asked before on the haskell mailing list http://www.haskell.org/pipermail/haskell/2006-September/018522.html, but no answers were given.
You need some way that each Binary instance can register itself (just as in your witness version). You can do this by bundling each instance declaration with an exported foreign symbol, where the symbol name is derived from the TypeRep. Then when you want to deserialize you get the name from the TypeRep and look up that symbol dynamically (with dlsym() or something similar). The value exported by the foreign export can, e.g., be the deserializer function.
It's crazy ugly, but it works.
This can be solved in GHC 7.10 and onwards using the Static Pointers Language extension:
{-# LANGUAGE StaticPointers #-}
{-# LANGUAGE InstanceSigs #-}
data Foo = forall a . (StaticFoo a, Binary a, Show a) => Foo a
class StaticFoo a where
staticFoo :: a -> StaticPtr (Get Foo)
instance StaticFoo String where
staticFoo _ = static (Foo <$> (get :: Get String))
instance Binary Foo where
put (Foo x) = do
put $ staticKey $ staticFoo x
put x
get = do
ptr <- get
case unsafePerformIO (unsafeLookupStaticPtr ptr) of
Just value -> deRefStaticPtr value :: Get Foo
Nothing -> error "Binary Foo: unknown static pointer"
A full description of the solution can be found on this blog post, and a complete snippet here.
If you could do that, you would also be able to implement:
isValidRead :: TypeRep -> String -> Bool
This would be a function that changes its behavior due to someone defining a new type! Not very pure-ish.. I think (and hope) that one can't implement this in Haskell..
I have an answer that slightly works in some situations (not enough for my purposes), but may be the best that can be done. You can add a witness function to witness any types that you have, and then the deserialisation can lookup in the witness table. The rough idea is (untested):
witnesses :: IORef [Foo]
witnesses = unsafePerformIO $ newIORef []
witness :: (Typeable a, Binary a) => a -> IO ()
witness x = modifyIORef (Foo x :)
instance Binary Foo where
put (Foo x) = put (typeOf x) >> put x
get = do
ty <- get
wits <- unsafePerformIO $ readIORef witnesses
case [Foo x | Foo x <- wits, typeOf x == ty] of
Foo x:_ -> fmap Foo $ get `asTypeOf` return x
[] -> error $ "Could not find a witness for the type: " ++ show ty
The idea is that as you go through, you call witness on values of every type that you may plausibly encounter when deserialising. When you deserialise you search this list. The obvious problem is that if you fail to call witness before deserialisation you get a crash.

Get a list of the instances in a type class in Haskell

Is there a way to programmatically get a list of instances of a type class?
It strikes me that the compiler must know this information in order to type check and compile the code, so is there some way to tell the compiler: hey, you know those instances of that class, please put a list of them right here (as strings or whatever some representation of them).
You can generate the instances in scope for a given type class using Template Haskell.
import Language.Haskell.TH
-- get a list of instances
getInstances :: Name -> Q [ClassInstance]
getInstances typ = do
ClassI _ instances <- reify typ
return instances
-- convert the list of instances into an Exp so they can be displayed in GHCi
showInstances :: Name -> Q Exp
showInstances typ = do
ins <- getInstances typ
return . LitE . stringL $ show ins
Running this in GHCi:
*Main> $(showInstances ''Num)
"[ClassInstance {ci_dfun = GHC.Num.$fNumInteger, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Integer.Type.Integer]},ClassInstance {ci_dfun = GHC.Num.$fNumInt, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Types.Int]},ClassInstance {ci_dfun = GHC.Float.$fNumFloat, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Types.Float]},ClassInstance {ci_dfun = GHC.Float.$fNumDouble, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Types.Double]}]"
Another useful technique is showing all instances in scope for a given type class using GHCi.
Prelude> :info Num
class (Eq a, Show a) => Num a where
(+) :: a -> a -> a
(*) :: a -> a -> a
(-) :: a -> a -> a
negate :: a -> a
abs :: a -> a
signum :: a -> a
fromInteger :: Integer -> a
-- Defined in GHC.Num
instance Num Integer -- Defined in GHC.Num
instance Num Int -- Defined in GHC.Num
instance Num Float -- Defined in GHC.Float
instance Num Double -- Defined in GHC.Float
Edit: The important thing to know is that the compiler is only aware of type classes in scope in any given module (or at the ghci prompt, etc.). So if you call the showInstances TH function with no imports, you'll only get instances from the Prelude. If you have other modules in scope, e.g. Data.Word, then you'll see all those instances too.
See the template haskell documentation: http://hackage.haskell.org/packages/archive/template-haskell/2.5.0.0/doc/html/Language-Haskell-TH.html
Using reify, you can get an Info record, which for a class includes its list of instances. You can also use isClassInstance and classInstances directly.
This is going to run into a lot of problems as soon as you get instance declarations like
instance Eq a => Eq [a] where
[] == [] = True
(x:xs) == (y:ys) = x == y && xs == ys
_ == _ = False
and
instance (Eq a,Eq b) => Eq (a,b) where
(a1,b1) == (a2,b2) = a1 == a2 && b1 == b2
along with a single concrete instance (e.g. instance Eq Bool).
You'll get an infinite list of instances for Eq - Bool,[Bool],[[Bool]],[[[Bool]]] and so on, (Bool,Bool), ((Bool,Bool),Bool), (((Bool,Bool),Bool),Bool) etcetera, along with various combinations of these such as ([((Bool,[Bool]),Bool)],Bool) and so forth. It's not clear how to represent these in a String; even a list of TypeRep would require some pretty smart enumeration.
The compiler can (try to) deduce whether a type is an instance of Eq for any given type, but it doesn't read in all the instance declarations in scope and then just starts deducing all possible instances, since that will never finish!
The important question is of course, what do you need this for?
I guess, it's not possible. I explain you the implementation of typeclasses (for GHC), from it, you can see, that the compiler has no need to know which types are instance of a typeclass. It only has to know, whether a specific type is instance or not.
A typeclass will be translated into a datatype. As an example, let's take Eq:
class Eq a where
(==),(/=) :: a -> a -> Bool
The typeclass will be translated into a kind of dictionary, containing all its functions:
data Eq a = Eq {
(==) :: a -> a -> Bool,
(/=) :: a -> a -> Bool
}
Each typeclass constraint is then translated into an extra argument containing the dictionary:
elem :: Eq a => a -> [a] -> Bool
elem _ [] = False
elem a (x:xs) | x == a = True
| otherwise = elem a xs
becomes:
elem :: Eq a -> a -> [a] -> Bool
elem _ _ [] = False
elem eq a (x:xs) | (==) eq x a = True
| otherwise = elem eq a xs
The important thing is, that the dictionary will be passed at runtime. Imagine, your project contains many modules. GHC doesn't have to check all the modules for instances, it just has to look up, whether an instance is defined anywhere.
But if you have the source available, I guess an old-style grep for the instances would be sufficient.
It is not possible to automatically do this for existing classes. For your own class and instances thereof you could do it. You would need to declare everything via Template Haskell (or perhaps the quasi-quoting) and it would automatically generate some strange data structure that encodes the declared instances. Defining the strange data structure and making Template Haskell do this are details left to whomever has a use case for them.
Perhaps you could add some Template Haskell or other magic to your build to include all the source files as text available at run-time (c.f. program quine). Then your program would 'grep itself'...

Resources