[Haskell-cafe] typeclass constraints?

Gregory Guthrie guthrie at mum.edu
Sat Nov 5 19:09:55 UTC 2016


I want to define a bunch of tests in a simple demo program, where each test is locally defined, but all can be printed in one standard place.
For example, each test result has a description::String, and a value, which can vary across tests.
   t1 = ("Sqrt(4)", sqrt(4.0))
   ...
   t2 = ("sumList:", sum [1,2,3,4])
   ...
   t3 = ("Description", value)
   ...
So each test is of type: (String, value), for various value types all of which (only) have to be members of the Show class.
Then for the summary of the tests, a loop:
   test (msg, val) = do print $ msg ++ " :: " ++ show val
   tests ts        = mapM test ts
    ...
   Do tests [t1, t2, t3]
This compiles, and assigns these types:
   test :: Show a => ([Char], a) -> IO ()
   tests :: (Traversable t, Show a) => t ([Char], a) -> IO (t ())
Which works only as long as all tests have the same type for the second argument. I assume that it is somehow specializing the type to the actual encountered type of the arguments used, even though they are all show'able.
So that they can vary on the actual types of the second argument, I tried something like this (pseudo code):
   type ATest = (Show a) => (String, a)
since that wouldn't work, I tried:
   {-# LANGUAGE RankNTypes #-}
   type ATest = forall a. (Show a) => (String, a)
Which compiles, but still fails on any variation in the value argument.
Further, I want to abstract the type of tests from the loop which prints them, but I cannot then use it to convert from:
   test :: Show a => ([Char], a) -> IO ()
to
   test :: ATest -> IO ()
The basic idea was to define and use a polymorphic type for the tests in the definition of the testing loop. So perhaps a data structure instead;
   data (Show a) => ATest =  Test (String, a)
but that also fails, although it does give the right idea; all tests have a common structure, with a second value in the Show typeclass.
I realize that generally one is recommended not to put constraints on the data type, but on the functions which use it - but here since I want a collection of tests it seems like I need a polymorphic list with consistent types.
What is the right approach for this? Am I just getting the syntax wrong?


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20161105/b72dbb14/attachment.html>


More information about the Haskell-Cafe mailing list