Is there a built-in typeclass equivalent to this? - haskell

So I have the following Haskell typeclass used for input validation.
-- Check.hs
module Check where
-- Used to ensure that the value of a variable is a good value. For example, this can be used for input validation.
class Check a where
accept :: a -> Bool
I use it, for example, to ensure that good data is passed to a shopping order.
-- Shopping.hs
module Shopping where
import Customer
import Check
import ShoppingItem
-- Stores data about a shopping order including the item
data ShoppingOrder = ShoppingOrder {
customer :: Customer, -- The customer placing the order
item :: ShoppingItem, -- The item being ordered
quantity :: Int -- The quantity being ordered
} deriving (Show,Read,Eq)
-- ShoppingItem and Customer both have instances of Check.
instance Check ShoppingOrder where
accept order = (quantity order) > 0 && (accept . item) order && (accept . customer) order
I was wondering if there was already a built-in version of the Check typeclass because the nature of data constructors would make it quite useful and I would rather work with already existing API than create my own.

While the following doesn't directly answer the question of does such a class exist?, I still find it worthwhile to point out that a composable approach to input validation is to use an Applicative sum type.
I'll start with Either, since this is built into the base library that comes with GHC. It's actually not the best choice for validation, but I'll get back to that further down.
You can write fine-grained validation functions that return Either values, for example:
validatePositive :: (Ord a, Num a) => a -> Either String a
validatePositive p = if p > 0 then Right p else Left "Not a positive number."
In this example, I'm just using a String to return error messages, but you may probably want to use something better typed, on which you can pattern-match.
*Q57153650> validatePositive (-1)
Left "Not a positive number."
*Q57153650> validatePositive 0
Left "Not a positive number."
*Q57153650> validatePositive 1
Right 1
Assume that you've also written validation functions for Customer and ShoppingItem:
validateCustomer :: Customer -> Either String Customer
validateCustomer = -- ...
validateItem :: ShoppingItem -> Either String ShoppingItem
validateItem = -- ...
(I'm just showing the types of the functions here, since I don't know how Customer or ShoppingItem are defined.)
You can now compose all of these validation functions like this:
validateOrder :: ShoppingOrder -> Either String ShoppingOrder
validateOrder (ShoppingOrder c i q) =
ShoppingOrder <$> validateCustomer c <*> validateItem i <*> validatePositive q
This illustrates the concept:
*Q57153650> :t validOrder
validOrder :: ShoppingOrder
*Q57153650> invalidOrder = validOrder { quantity = (-1) }
*Q57153650> validateOrder validOrder
Right (ShoppingOrder {customer = ..., item = ..., quantity = 2})
*Q57153650> validateOrder invalidOrder
Left "Not a positive number."
When you have a valid order, the result of validation is a Right value; if anything is incorrect, the result is a Left value that indicates what went wrong.
A limitation of the built-in Either type's Applicative instance is that if more than one thing is incorrect, you only get a message about the first incorrect (sub)value.
When it comes to data validation, one often wants to accumulate all the errors in (e.g.) a list, so that one can display a list of problems to the client. As the article I linked to above explains, you can do that by modifying the Applicative instance to collect all errors.
You don't have to implement such a type yourself, though, since various packages already do that. One that I'm aware of is the validation package, that I do admit, however, I've never used in a real project.

Related

How do I test that something is valid for all elements in a map?

I have the following things in my application:
newtype User = User Text
newtype Counts = Counts (Map User Int)
subjectUnderTest :: Counts -> Text
An example of correct output would be
> subjectUnderTest $ fromList [(User "foo", 4), (User "bar", 4), (User "qux", 2)]
"4: foo, bar\n2: qux"
I would like to write property-based tests that verify things like "all users are represented in the output", "all counts are represented in the output" and "all users are on the same line as their corresponding count". In common for these properties is that the wording of them starts with "all ..."
How do I write a property that verifies that something is valid for each element in the Map?
I'm assuming that this question is only a simplified representation of something more complex, so here's a couple of things strategies to consider:
Split up the functionality
It looks like subjectUnderTest does two unrelated things:
It groups the values in the map by value, instead of by key.
It formats, or pretty-prints, the inverted map.
If you can split up the functionality into those two steps, they're easier to test in in isolation.
The first step, you can make parametrically polymorphic. Instead of testing a function with the type Counts -> Text, consider testing a function with the type Eq b => Map a b -> [(b, [a])]. Property-based testing is easier with parametric polymorphism, because you get certain properties for free. For example, you can be sure that the values in the output can only come from the input, because there's no way to conjure a and b values out of thin air.
You're still going to have to write tests for the properties you ask about. Write a function with a type like Eq b => Map a b -> Testable. If you want to test that all the values are there, pull them out of the map and make list of them. Sort the list and nub it. It's now a [b] value. That's your expected output.
Now call your function. It returns something like [(b, [a])]. Map it using fst, sort and nub it. That list should be equal to your expected output.
For the next step (pretty-printing), see the next section.
Roundtrips
When you want to property-base pretty-printing, the easiest approach is usually to bite the bullet and also write a parser. The printer and the parser should be the dual of each other, so if you have a function MyType -> String, your should have a parser with the type String -> Maybe MyType.
You can now write a general property like MyType -> Testable. It takes as input a value of MyType (let's call it expected). You now produce a value (let's call it actual) as actual = parse $ print expected. You can now verify that Just expected === actual.
If the particular String format is important, I'd follow it up with a few actual examples, using good old parametrised tests.
Just because you're doing property-based testing doesn't mean that a 'normal' unit test can't be useful as well.
Example
Here's a simple example of what I meant above. Assume that
invertMap :: (Ord b, Eq b) => Map a b -> [(b, [a])]
you can define one of the properties as:
allValuesAreNowKeys :: (Show a, Ord a) => Map k a -> Property
allValuesAreNowKeys m =
let expected = nub $ sort $ Map.elems m
actual = invertMap m
in expected === nub (sort $ fmap fst actual)
Since this property is still parametrically polymorphic, you'll have to add it to your test suite with a particular type, e.g.:
tests = [
testGroup "Sorting Group 1" [
testProperty "all values are now keys" (allValuesAreNowKeys :: Map String Int -> Property)]]
There are prettier ways to define lists of properties; that one is just the template used by the quickcheck-test-framework Stack template...

Redundancy regarding product types and tuples in Haskell

In Haskell you have product types and you have tuples.
You use tuples if you don't want to associate a dedicated type with the value, and you can use product types if you wish to do so.
However I feel there is redundancy in the notation of product types
data Foo = Foo (String, Int, Char)
data Bar = Bar String Int Char
Why are there both kinds of notations? Is there any case where you would prefer one the other?
I guess you can't use record notation when using tuples, but that's just a convenience problem. Another thing might be the notion of order in tuples, as opposed to product types, but I think that's just due to the naming of the functions fst and snd.
#chi's answer is about the technical differences in terms of Haskell's evaluation model. I hope to give you some insight into the philosophy of this sort of typed programming.
In category theory we generally work with objects "up to isomorphism". Your Bar is of course isomorphic to (String, Int, Char), so from a categorical perspective they're the same thing.
bar_tuple :: Iso' Bar (String, Int, Char)
bar_tuple = iso to from
where to (Bar s i c) = (s, i, c)
from (s, i, c) = Bar s i c
In some sense tuples are a Platonic form of product type, in that they have no meaning beyond being a collection of disparate values. All the other product types can be mapped to and from a plain old tuple.
So why not use tuples everywhere, when all Haskell types ultimately boil down to a sum of products? It's about communication. As Martin Fowler says,
Any fool can write code that a computer can understand. Good programmers write code that humans can understand.
Names are important! Writing down a custom product type like
data Customer = Customer { name :: String, address :: String }
imbues the type Customer with meaning to the person reading the code, unlike (String, String) which just means "two strings".
Custom types are particularly useful when you want to enforce invariants by hiding the representation of your data and using smart constructors:
newtype NonEmpty a = NonEmpty [a]
nonEmpty :: [a] -> Maybe (NonEmpty a)
nonEmpty [] = Nothing
nonEmpty xs = Just (NonEmpty xs)
Now, if you don't export the NonEmpty constructor, you can force people to go through the nonEmpty smart constructor. If someone hands you a NonEmpty value you may safely assume that it has at least one element.
You can of course represent Customer as a tuple under the hood and expose evocatively-named field accessors,
newtype Customer = Bar (String, String)
name, address :: Customer -> String
name (Customer (n, a)) = n
address (Customer (n, a)) = a
but this doesn't really buy you much, except that it's now cheaper to convert Customer to a tuple (if, say, you're writing performance-sensitive code that works with a tuple-oriented API).
If your code is intended to solve a particular problem - which of course is the whole point of writing code - it pays to not just solve the problem, but make it look like you've solved it too. Someone - maybe you in a couple of years - is going to have to read this code and understand it with no a priori knowledge of how it works. Custom types are a very important communication tool in this regard.
The type
data Foo = Foo (String, Int, Char)
represents a double-lifted tuple. It values comprise
undefined
Foo undefined
Foo (undefined, undefined, undefined)
etc.
This is usually troublesome. Because of this, it's rare to see such definitions in actual code. We either have plain data types
data Foo = Foo String Int Char
or newtypes
newtype Foo = Foo (String, Int, Char)
The newtype can be just as inconvenient to use, but at least it
does not double-lift the tuple: undefined and Foo undefined are now equal values.
The newtype also provides zero-cost conversion between a plain tuple and Foo, in both directions.
You can see such newtypes in use e.g. when the programmer needs a different instance for some type class, than the one already associated with the tuple. Or, perhaps, it is used in a "smart constructor" idiom.
I would not expect the pattern used in Foo to be frequent. There is slight difference in what the constructor acts like: Foo :: (String, Int, Char) -> Foo as opposed to Bar :: String -> Int -> Char -> Bar. Then Foo undefined and Foo (undefined, ..., ...) are strictly speaking different things, whereas you miss one level of undefinedness in Bar.

Haskell Confusing Type Classes / Polymorphism

So basically I've past learning this part way back a month ago, and I can do more complicated stuff but I still don't understand when I need "Ord" or "Eq" etc in my type definitions. When I look it up online its just so confusing to me for some reason.
E.g.
my_min :: Ord a => a -> a -> a
my_min n1 n2 = if n1<n2 then n1 else n2
Why does this need Ord? Can you give an example of when you need Eq as well (a very simple one)? I need a very clear, basic explanation of when you need to put these, what to look out for to do that, and how to avoid using these at all if possible.
Usually I just need something like "[Int] -> Int -> [Int]" so i know ok this function takes an integer list and an integer, and returns an integer list. But when it includes Eq or Ord I have no idea.
What about this Eq type in this example I found in my lecture notes about finding two lists is identical, how does it apply?
identical :: Eq a =>[a]->[a]->Bool
identical [] [] = True
identical [] _ = False
identical _ [] = False
identical (h1:t1) (h2:t2) =
if h1==h2
then (identical t1 t2)
else False
Thank you.
Ord implies that the thing can be ordered, which means that you can say a is smaller (or greater) than b. Using only Eq is like saying: I know that these two items are not the same, but I cannot say which one is greater or smaller. For example if you take a traffic light as a data type:
data TLight = Red | Yellow | Green deriving (Show, Eq)
instance Eq TLight where
Green == Green = True
Yellow == Yellow = True
Red == Red = True
_ == _ = False
Now we can say: Red is unequal to Yellow but we cannot say what is greater. This is the reason why you could not use TLight in your my_min. You cannot say which one is greater.
To your second question: "Is there any case where you have to use Eq and Ord?":
Ord implies Eq. This means that if a type can be ordered, you can also check it for equality.
You said you have mostly dealt with [Int] -> Int -> [Int] and you then knew it takes a list of integer and an integer and returns an integer. Now if you want to generalise your function you have to ask yourself: Do the possible types I want to use in my function need any special functionality? like if they have to be able to be ordered or equated.
Lets do a few examples: Say we want to write a function which takes a list of type a and an element of type a and returns the lisy with the element consed onto it. How would it's type signature look like? Lets start with simply this:
consfunc :: [a] -> a -> [a]
Do we need any more functionality? No! Our type a can be anything because we do not need it to be able to be ordered simple because that is mot what our function should do.
Now what if we want to take a list and an element and check if the element is in the list already? The beginning type signature is:
elemfunc :: [a] -> a -> Bool
Now does our element have to be able to do something special? Yes it does, we have to be able to check if it is equal to any element in the list, which says that our type a has to be equatable, so our type signature looks like this:
elemfunc :: (Eq a) => [a] -> a -> Bool
Now what if we want to take a list and a element and insert it if it is smaller than the first element? Can you guess how the type signature would look like?
Lets begin with the standard again and ask ourselves: Do we need more than just knowing that the element and the list have to be of the same type: Yes, becuase our condition needs to perform a test that requires our type to be ordered, we have to include Ord in our type signature:
conditionalconsfunc :: (Ord a) => [a] -> a -> [a]
Edit:
Well you want to see if two lists are identical, so there are two things you have to look out for:
Your lists have to contain the same type and the things inside the list have to be equatable, hence the Eq.
If you are working with fixed types like Int, you never need class constraints. These only arise when working with polymorphic code.
You need Eq if you ever use the == or /= functions, or if you call any other functions that do. (I.e., if you call a function that has Eq in its type, then your type needs to have Eq as well.)
You need Ord if you ever use <, >, compare or similar functions. (Again, or if you call something that does.)
Note that you do not need Eq if you only do pattern matching. Thus, the following are different:
factorial 1 = 1
factorial n = n * factorial (n-1)
-- Only needs Num.
factorial n = if n == 1 then 1 else n * factorial (n-1)
-- Needs Num and Eq.
factorial n = if n < 2 then 1 else n * factorial (n-1)
-- Needs Num, Eq and Ord. (But Ord implies Eq automatically.)

Outputting the contents of a list of a custom data type

I have a custom data type Movie = String Int [(String,Int)] (Movie Name Year [(Fan,Rating)] and want to do a couple of things:
First I want to make a function that averages the Ints from the list of tuples and just outputs that number. So far I have this incomplete function:
avgRating :: [DataType] -> Int
avgRating [(Movie a b [(fan,rating)])] = sumRatings / (length [<mylist>])
Here I need a function sumRatings to recurse through the list and sum all the ratings, but i'm not sure where to start.
The other issue I have here is that i'm not sure what to put where <mylist> is as I would normally give the list a variable name and then use it there, but since I have split the list up to define other variables I can't name it.
I hope that makes sense, thanks.
I'm guessing you have a data structure defined as
data Movie = Movie String Int [(String, Int)]
While this works, it can be a bit cumbersome to work with when you have that many fields. Instead, you can leverage type aliases and record syntax as
type Name = String
type Year = Int
type Rating = Int
data Movie = Movie
{ mName :: Name
, mYear :: Year
, mRatings :: [(Name, Rating)]
} deriving (Eq, Show)
Now things are a bit more explicit and easier to work with. The mName, mYear, and mRatings functions will take a Movie and return the corresponding field from it. Your Movie constructor still works in the same way too, so it won't break existing code.
To calculate the average of the ratings, you really want a function that extracts all the ratings for a movie and aggregates them into a list:
ratings :: Movie -> [Rating]
ratings mov = map snd $ mRatings mov
Then you just need an average function. This will be a bit different because you can't calculate the average of Ints directly, you'll have to convert to a floating point type:
average :: [Rating] -> Float -- Double precision isn't really needed here
average rs = fromIntegral (sum rs) / fromIntegral (length rs)
The fromIntegral function converts an Int to a Float (the actual type signature is a bit more general). Since both the sum of Ints is an Int and the length of a list is always an Int, you need to convert both.
Now you can just compose these into a single function:
movieAvgRating :: Movie -> Float
movieAvgRating = average . ratings
Now, if you need to calculate the average ratings for several movies, you can apply ratings to each of them, aggregate them into a single list of ratings, then call average on that. I would suggest looking at the concatMap function. You'll be wanting to make a function like
moviesAvgRating :: [Movie] -> Float
moviesAvgRating movs = average $ ???
To answer your second question first, you can bind to a variable and unpack it simultaneously using #:
avgRating [(Movie a b mylist#[(fan, rating)])] = …
Note also that if you’re not going to be using variables that you unpack, it’s Haskell convention to bind them to _:
avgRating [(Movie _ _ mylist#[(fan, rating)])] = …
This helps readers focus on what’s actually important.
I don’t want to just give you the solution to your recursion problem, because learning to write recursive functions is an important and rewarding part of Haskell programming. (If you really want me to spoil it for you, let me know in a comment.) The basic idea, however, is that you need to think about two different cases: a base case (where the recursion stops) and a recursive case. As an example, consider the built-in sum function:
sum :: Num a => [a] -> a
sum [] = 0
sum (x:xs) = x + sum xs
Here, the base case is when sum gets an empty list – it simply evaluates to 0. In the recursive case, we assume that sum can already produce the sum of a smaller list, and we extend it to cover a larger list.
If you’re having trouble with recursion in general, Harold Abelson and Gerald Jay Sussman present a detailed discussion on the topic in Structure and Interpretation of Computer Programs, 2nd ed., The MIT Press (Cambridge), 1996, starting on p. 21 (§§1.1.7–1.2). It’s in Scheme, not Haskell, but the languages are sufficiently similar – at least at this conceptual level – that each can serve as a decent model for the other.

Can GADTs be used to prove type inequalities in GHC?

So, in my ongoing attempts to half-understand Curry-Howard through small Haskell exercises, I've gotten stuck at this point:
{-# LANGUAGE GADTs #-}
import Data.Void
type Not a = a -> Void
-- | The type of type equality proofs, which can only be instantiated if a = b.
data Equal a b where
Refl :: Equal a a
-- | Derive a contradiction from a putative proof of #Equal Int Char#.
intIsNotChar :: Not (Equal Int Char)
intIsNotChar intIsChar = ???
Clearly the type Equal Int Char has no (non-bottom) inhabitants, and thus semantically there ought to be an absurdEquality :: Equal Int Char -> a function... but for the life of me I can't figure out any way to write one other than using undefined.
So either:
I'm missing something, or
There is some limitation of the language that makes this an impossible task, and I haven't managed to understand what it is.
I suspect the answer is something like this: the compiler is unable to exploit the fact that there are no Equal constructors that don't have a = b. But if that is so, what makes it true?
Here's a shorter version of Philip JF's solution, which is the way dependent type theorists have been refuting equations for years.
type family Discriminate x
type instance Discriminate Int = ()
type instance Discriminate Char = Void
transport :: Equal a b -> Discriminate a -> Discriminate b
transport Refl d = d
refute :: Equal Int Char -> Void
refute q = transport q ()
In order to show that things are different, you have to catch them behaving differently by providing a computational context which results in distinct observations. Discriminate provides exactly such a context: a type-level program which treats the two types differently.
It is not necessary to resort to undefined to solve this problem. Total programming sometimes involves rejecting impossible inputs. Even where undefined is available, I would recommend not using it where a total method suffices: the total method explains why something is impossible and the typechecker confirms; undefined merely documents your promise. Indeed, this method of refutation is how Epigram dispenses with "impossible cases" whilst ensuring that a case analysis covers its domain.
As for computational behaviour, note that refute, via transport is necessarily strict in q and that q cannot compute to head normal form in the empty context, simply because no such head normal form exists (and because computation preserves type, of course). In a total setting, we'd be sure that refute would never be invoked at run time. In Haskell, we're at least certain that its argument will diverge or throw an exception before we're obliged to respond to it. A lazy version, such as
absurdEquality e = error "you have a type error likely to cause big problems"
will ignore the toxicity of e and tell you that you have a type error when you don't. I prefer
absurdEquality e = e `seq` error "sue me if this happens"
if the honest refutation is too much like hard work.
I don't understand the problem with using undefined every type is inhabited by bottom in Haskell. Our language is not strongly normalizing... You are looking for the wrong thing. Equal Int Char leads to type errors not nice well kept exceptions. See
{-# LANGUAGE GADTs, TypeFamilies #-}
data Equal a b where
Refl :: Equal a a
type family Pick cond a b
type instance Pick Char a b = a
type instance Pick Int a b = b
newtype Picker cond a b = Picker (Pick cond a b)
pick :: b -> Picker Int a b
pick = Picker
unpick :: Picker Char a b -> a
unpick (Picker x) = x
samePicker :: Equal t1 t2 -> Picker t1 a b -> Picker t2 a b
samePicker Refl x = x
absurdCoerce :: Equal Int Char -> a -> b
absurdCoerce e x = unpick (samePicker e (pick x))
you could use this to create the function you want
absurdEquality e = absurdCoerce e ()
but that will produce undefined behavior as its computation rule. false should cause programs to abort, or at the very least run for ever. Aborting is the computation rule that is akin to turning minimal logic into intiutionistic logic by adding not. The correct definition is
absurdEquality e = error "you have a type error likely to cause big problems"
as to the question in the title: essentially no. To the best of my knowledge, type inequality is not representable in a practical way in current Haskell. Coming changes to the type system may lead to this getting nicer, but as of right now, we have equalities but not inequalites.

Resources