How to match rigid types in a type class instance? - haskell

I thought I would try modeling some numerical integration on vector quantities of different dimensionality, and figured that type classes were the way to go. I needed something to define the difference between two values and to scale it by a multiplier (to get the derivative), as well as being able to take the distance function.
So far I have:
class Integratable a where
difference :: a -> a -> a
scale :: Num b => a -> b -> a
distance :: Num b => a -> a -> b
data Num a => Vector a = Vector1D a | Vector2D a a
instance Num a => Integratable (Vector a) where
difference (Vector1D x1) (Vector1D x2) = Vector1D (x1 - x2)
scale (Vector1D x) m = Vector1D (x * m)
distance (Vector1D x1) (Vector1D x2) = x1 - x2
difference (Vector2D x1 y1) (Vector2D x2 y2) = Vector2D (x1 - x2) (y1 - y2)
scale (Vector2D x y) m = Vector2D (x * m) (y * m)
distance (Vector2D x1 y1) (Vector2D x2 y2) = sqrt((x1-x2)*(x1-x2)
+ (y1-y2)*(y1-y2))
Unfortunately there are a couple of problems here that I haven't figured out how to resolve. Firstly, the scale function gives errors. GHC can't tell that m and x are compatible since the rigid type restriction Num is given in the instance in one case, and in the Vector type in the other case... Is there a way to specify that x and m are the same type?
(I realize in fact that even if x and m are both Num, they may not be the same Num. How can I specify this? If I can't figure it out with Num, using Double would be fine, but I'd rather keep it general.)
There's a similar problem with distance. Attempting to specify that the return type is Num fails, since it can't tell in the instance definition that a is going to contain values that are compatible with b.

EDIT: It seems to me now that the article on functional dependencies from the HaskellWiki provides the key information in the best form that I can find, so I'd suggest reading that instead of my answer here. I'm not removing the rest of the content, though, as it makes clear (I hope) why FDs are useful here.
Apart from the grouping of definitions issue which Dave pointed out...
(I realize in fact that even if x and m are both Num, they may not be the same Num. How can I specify this? If I can't figure it out with Num, using Double would be fine, but I'd rather keep it general.)
This is the main problem, actually. You can't multiply an Integer by a Float, say. In effect, you need the x and the m in scale to be of the same type.
Also, a similar issue arises with distance, with the additional complication that sqrt needs a Floating argument. So I guess you'd need to mention that somewhere too. (Most likely on the instance, I guess).
EDIT: OK, since sqrt only works on Floating values, you could roll a typeclass for those to upcast Floats to Doubles when needed.
Another idea involves having a typeclass Scalable:
data Vector a = Vector1D a | Vector2D a a deriving (Show)
class Scalable a b | a -> b where
scale :: a -> b -> a
instance (Num a) => Scalable (Vector a) a where
scale (Vector1D x) m = (Vector1D (x * m))
scale (Vector2D x y) m = (Vector2D (x * m) (y * m))
This uses a so-called functional dependency in the definition of Scalable. In fact, trying to remember the syntax for that, I found this link... So I guess you should disregard my inferior attempt at being helpful and read the quality info there. ;-)
I think you should be able to use this to solve your original problem.

To fix the second error, I think you need to reorder your definitions in the instance declaration. First have the two equations for difference, then the equations for scale, then both for distance.

Related

How to use a refutation to direct the type checker in Haskell?

Does filling the hole in the following program necessarily require non-constructive means? If yes, is it still the case if x :~: y decidable?
More generally, how do I use a refutation to guide the type checker?
(I am aware that I can work around the problem by defining Choose as a GADT, I'm asking specifically for type families)
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module PropositionalDisequality where
import Data.Type.Equality
import Data.Void
type family Choose x y where
Choose x x = 1
Choose x _ = 2
lem :: (x :~: y -> Void) -> Choose x y :~: 2
lem refutation = _
If you try hard enough to implement a function, you can convince yourself
that it is not possible. If you're not convinced, the argument can be made
more formal: we enumerate programs exhaustively to find that none is possible. It turns out there's only half a dozen of meaningful cases to consider.
I wonder why this argument is not made more often.
Totally not accurate summary:
Act I: proof search is easy.
Act II: dependent types too.
Act III: Haskell is still fine for writing dependently typed programs.
I. The proof search game
First we define the search space.
We can reduce any Haskell definition to one of the form
lem = (exp)
for some expression (exp). Now we only need to find a single expression.
Look at all possible ways of making an expression in Haskell:
https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-220003
(this doesn't account for extensions, exercise for the reader).
It fits a page in a single column, so it's not that big to start with.
Moreover, most of them are sugar for some form of function application or
pattern-matching; we can also desugar away type classes with dictionary
passing, so we're left with a ridiculously small lambda calculus:
lambdas, \x -> ...
pattern-matching, case ... of ...
function application, f x
constructors, C (including integer literals)
constants, c (for primitives that cannot be written in terms of the constructs above, so various built-ins (seq) and maybe FFI if that counts)
variables (bound by lambdas and cases)
We can exclude every constant on the grounds that I think the question is
really about pure lambda calculus (or the reader can enumerate the constants,
to exclude black-magic constants like undefined, unsafeCoerce,
unsafePerformIO that make everything collapse (any type is inhabited and, for
some of those, the type system is unsound), and to be left with white-magic
constants to which the present theoretical argument can be generalized via a
well-funded thesis).
We can also reasonably assume that we want a solution with no recursion involved
(to get rid of noise like lem = lem, and fix if you felt like you couldn't
part with it before), and which actually has a normal form, or preferably, a
canonical form with respect to βη-equivalence. In other words, we refine and
examine the set of possible solutions as follows.
lem :: _ -> _ has a function type, so we can assume WLOG that its definition starts with a lambda:
-- Any solution
lem = (exp)
-- is η-equivalent to a lambda
lem = \refutation -> (exp) refutation
-- so let's assume we do have a lambda
lem = \refutation -> _hole
Now enumerate what could be under the lambda.
It could be a constructor,
which then has to be Refl, but there is no proof that Choose x y ~ 2 in
the context (here we could formalize and enumerate the type equalities the
typechecker knows about and can derive, or make the syntax of coercions
(proofs of equalities) explicit and keep playing this proof search game
with them), so this doesn't type check:
lem = \refutation -> Refl
Maybe there is some way of constructing that equality proof, but then the
expression would start with something else, which is going to be another
case of the proof.
It could be some application of a constructor C x1 x2 ..., or the
variable refutation (applied or not); but there's no possible way that's
well-typed, it has to somehow produce a (:~:), and Refl is really the
only way.
Or it could be a case. WLOG, there is no nested case on the left, nor any
constructor, because the expression could be simplified in both cases:
-- Any left-nested case expression
case (case (e) of { C x1 x2 -> (f) }) { D y1 y2 -> (g) }
-- is equivalent to a right-nested case
case (e) of { C x1 x2 -> case (f) of { D y1 y2 -> (g) } }
-- Any case expression with a nested constructor
case (C u v) of { C x1 x2 -> f x1 x2 }
-- reduces to
f u v
So the last subcase is the variable case:
lem = \refutation -> case refutation (_hole :: x :~: y) of {}
and we have to construct a x :~: y. We enumerate ways of filling the
_hole again. It's either Refl, but no proof is available, or
(skipping some steps) case refutation (_anotherHole :: x :~: y) of {},
and we have an infinite descent on our hands, which is also absurd.
A different possible argument here is that we can pull out the case
from the application, to remove this case from consideration WLOG.
-- Any application to a case
f (case e of C x1 x2 -> g x1 x2)
-- is equivalent to a case with the application inside
case e of C x1 x2 -> f (g x1 x2)
There are no more cases. The search is complete, and we didn't find an
implementation of (x :~: y -> Void) -> Choose x y :~: 2. QED.
To read more on this topic, I guess a course/book about lambda calculus up
until the normalization proof of the simply-typed lambda calculus should give
you the basic tools to start with. The following thesis contains an
introduction on the subject in its first part, but admittedly I'm a poor judge
of the difficulty of such material: Which types have a unique inhabitant?
Focusing on pure program equivalence,
by Gabriel Scherer.
Feel free to suggest more adequate resources and literature.
II. Fixing the proposition and proving it with dependent types
Your initial intuition that this should encode a valid proposition
is definitely valid. How might we fix it to make it provable?
Technically, the type we are looking at is quantified with forall:
forall x y. (x :~: y -> Void) -> Choose x y :~: 2
An important feature of forall is that it is an irrelevant quantifier.
The variables it introduces cannot be used "directly" in a term of this type. Although that aspect becomes more prominent in the presence of dependent types,
it still pervades Haskell today, providing another intuition for why this (and many other examples) is not "provable" in Haskell: if you think about why you
think that proposition is valid, you will naturally start with a case split about whether x is equal to y, but to even do such a case split you need a way to
decide which side you're on, which will of course have to look at x and y,
so they cannot be irrelevant. forall in Haskell is not at all like what most people mean with "for all".
Some discussion on the matter of relevance can be found in the thesis Dependent Types in Haskell, by Richard Eisenberg (in particular, Section 3.1.1.5 for an initial example, Section 4.3 for relevance in Dependent Haskell and Section 8.7 for comparison with other languages with dependent types).
Dependent Haskell will need a relevant quantifier to complement forall, and
which would get us closer to proving this:
foreach x y. (x :~: y -> Void) -> Choose x y :~: 2
Then we could probably write this:
lem :: foreach x y. (x :~: y -> Void) -> Choose x y :~: 2
lem x y p = case x ==? u of
Left r -> absurd (p r) -- x ~ y, that's absurd!
Right Irrefl -> Refl -- x /~ y, so Choose x y = 2
That also assumes a first-class notion of disequality /~, complementing ~,
to help Choose reduce when it is in the context and a decision function
(==?) :: foreach x y. Either (x :~: y) (x :/~: y).
Actually, that machinery isn't necessary, that just makes for a shorter
answer.
At this point I'm making stuff up because Dependent Haskell does not exist yet,
but that is easily doable in related dependently typed languages (Coq, Agda,
Idris, Lean), modulo an adequate replacement of the type family Choose
(type families are in some sense too powerful to be translated as mere
functions, so may be cheating, but I digress).
Here is a comparable program in Coq, showing also that lem applied to 1 and 2
and a suitable proof does reduce to a proof by reflexivity of choose 1 2 = 2.
https://gist.github.com/Lysxia/5a9b6996a3aae741688e7bf83903887b
III. Without dependent types
A critical source of difficulty here is that Choose is a closed type
family with overlapping instances. It is problematic because there is
no proper way to express the fact that x and y are not equal in Haskell,
to know that the first clause Choose x x does not apply.
A more fruitful avenue if you're into Pseudo-Dependent Haskell is to use a
boolean type equality:
-- In the base library
import Data.Type.Bool (If)
import Data.Type.Equality (type (==))
type Choose x y = If (x == y) 1 2
An alternative encoding of equality constraints becomes useful for this style:
type x ~~ y = ((x == y) ~ 'True)
type x /~ y = ((x == y) ~ 'False)
with that, we can get another version of the type-proposition above,
expressible in current Haskell (where SBool is the singleton type of Bool),
which essentially can be read as adding the assumption that the equality of x
and y is decidable. This does not contradict the earlier claim about "irrelevance" of forall, the function is inspecting a boolean (or rather an SBool), which postpones the inspection of x and y to whoever calls lem.
lem :: forall x y. SBool (x == y) -> ((x ~~ y) => Void) -> Choose x y :~: 2
lem decideEq p = case decideEq of
STrue -> absurd p
SFalse -> Refl

Partial Derivatives in Haskell

A while back a friend wanted help with a program that could solve for the roots of functions using Newton's method, and naturally for that I needed some way to calculate the derivative of a function numerically, and this is what I came up with:
deriv f x = (f (x+h) - f x) / h where h = 0.00001
Newton's method was a fairly easy thing to implement, and it works rather well. But now I've started to wonder - Is there some way I could use this function to solve partial derivatives in a numerical manner, or is that something that would require a full-on CAS? I would post my attempts but I have absolutely no clue what to do yet.
Please keep in mind that I am new to Haskell. Thank you!
You can certainly do much the same thing as you already implemented, only with multivariate perturbation instead. But first, as you should always do with top-level functions, add a type signature:
deriv :: (Double -> Double) -> Double -> Double
That's not the most general signature possible, but probably sufficiently general for everything you'll need. I'll call
type ℝ = Double
in the following for brevity, i.e.
deriv :: (ℝ -> ℝ) -> ℝ -> ℝ
Now what you want is, for example in ℝ²
grad :: ((ℝ,ℝ) -> ℝ) -> (ℝ,ℝ) -> (ℝ,ℝ)
grad f (x,y) = ((f (x+h,y) - f (x,y)) / h, (f (x,y+h) - f (x,y)) / h)
where h = 0.00001
It's awkward to have to write out the components individually and make the definition specific to a particular-dimensional vector space. A generic way of doing it:
import Data.VectorSpace
import Data.Basis
grad :: (HasBasis v, Scalar v ~ ℝ) => (v -> ℝ) -> v -> v
grad f x = recompose [ (e, (f (x ^+^ h*^basisValue b) - f x) ^/ h)
| (e,_) <- decompose x ]
where h = 0.00001
Note that this pre-chosen-step–finite-differentiation is always a tradeoff between inaccuracy from higher-order terms and from floating-point errors, so definitely check out automatic differentiation.
This is called automatic differentiation and there is a lot of really neat work in this area in Haskell, though I don't know how accessible it is.
From the wiki page:
A paper Beautiful Differentiation and the corresponding talk.
Forward mode libraries: ad, fad, vector-space, Data.Ring.Module.AutomaticDifferentiation
Reverse mode libraries: also ad, rad

Easy function gives compile error on conversion from Int to Double

Why does this easy function which computes the distance between 2 integer points in the plane not compile?
distance :: (Int, Int) -> (Int, Int) -> Double
distance (x, y) (u, v) = sqrt ((x - u) ^ 2 + (y - v) ^ 2)
I get the error Couldn't match expected type ‘Double’ with actual type ‘Int’.
It is frustrating such an easy mathematical function consumes so much of my time. Any explanation why this goes wrong and the most elegant way to fix this is appreciated.
This is my solution to overcome the problem
distance :: (Int, Int) -> (Int, Int) -> Double
distance (x, y) (u, v) =
let xd = fromIntegral x :: Double
yd = fromIntegral y :: Double
ud = fromIntegral u :: Double
vd = fromIntegral v :: Double
in sqrt ((xd - ud) ^ 2 + (yd - vd) ^ 2)
but there must be a more elegant way.
Most languages only do type inference (if any) “in direction of data flow”. E.g., you start with a value 2 in Java or Python, that'll be an int. You calculate something like 2 + 4, and the + operator infers from the integer arguments that the result is also int. In dynamic languages this is the only way that's possible at all (because the types are only an “associated property” of values). In static languages like C++, the inference-step is only done once at compile time, but it's still done largely “as if the types were associated properties of values”.
Not so in Haskell. Like other Hindley-Milner languages, it has a type system that works completely independent of any runtime data flow directions. It can still do forward-inference ((2::Int) + (4::Int) is unambiguously of type Int), but it's only a special case – types can just as well be inferred in the “reverse direction”, i.e. if you write (x + y) :: Int the compiler is able to infer that both x and y must have type Int as well.
This reverse-polymorphism enables many nice tricks – example:
Prelude Debug.SimpleReflect> 2 + 4 :: Expr
2 + 4
Prelude Debug.SimpleReflect> 7^3 :: Expr
7 * 7 * 7
...but it only works if the language never does implicit conversions, not even in “safe†, obvious cases” like Int -> Integer.
Usually, the type checker automatically infers the most sensible type. For your original implementation, the checker would infer the type
distance :: Floating a => (a, a) -> (a, a) -> a
and that – or perhaps the specialised version
distance :: (Double,Double) -> (Double,Double) -> Double
is a much more sensible type than your (Int, Int) -> ... attempt, because the Euclidean distance makes actually no sense on a discrete grid (you'd want something like a Taxcab distance there).
What you'd actually want is distance from the vector-space package. This is more general, works not only on 2-tuples but any suitable space.
†Int -> Double is actually not a safe conversion – try float(1000000000000000001) in Python! So even without Hindley-Milner, this is not really a very smart thing to do implicitly.
SOLVED: now I have this
distance :: (Int, Int) -> (Int, Int) -> Double
distance (x, y) (u, v) = sqrt (fromIntegral ((x - u) ^ 2 + (y - v) ^ 2))

Haskell: meaning of the error in GHCI

I'm not able to figure out what this error msg means. I want to define the function distance for the data type below... I do NOT want to use any GHC extensions.. even if the code is ugly, want to understand the error better, before I move on to using the extensions. Can someone please let me know what this error means and how I can get rid of this.
class Vector v where
distance :: v -> v -> Double
-- doesn't make sense, but WTH...
newtype OneD1 a = OD1 a
deriving (Show)
instance Vector (Maybe m) where
distance _ _ = 5.6
instance Vector (OneD1 m) where
distance (OD1 x1) (OD1 x2) = x2-x1
Prelude> :reload
[1 of 1] Compiling Main ( VectorTypeClass.hs, interpreted )
VectorTypeClass.hs:33:33:
Couldn't match expected type `Double' with actual type `m'
`m' is a rigid type variable bound by
the instance declaration
at C:\Users\byamm\Documents\Programming\Haskell\Lab\Expts\VectorTypeClass\VectorTypeClass.hs:32:10
Relevant bindings include
x2 :: m
(bound at C:\Users\byamm\Documents\Programming\Haskell\Lab\Expts\VectorTypeClass\VectorTypeClass.hs:33:27)
x1 :: m
(bound at C:\Users\byamm\Documents\Programming\Haskell\Lab\Expts\VectorTypeClass\VectorTypeClass.hs:33:18)
distance :: OneD1 m -> OneD1 m -> Double
(bound at C:\Users\byamm\Documents\Programming\Haskell\Lab\Expts\VectorTypeClass\VectorTypeClass.hs:33:4)
In the first argument of `(-)', namely `x2'
In the expression: x2 - x1
Failed, modules loaded: none.
Prelude>
instance Vector (OneD1 m) where
This promises that (OdeD1 m) is a vector, for any m. Including OneD1 String, etc.
distance (OD1 x1) (OD1 x2) = x2-x1
Here we try to apply - on two values of type m, which could be absolutely anything. There are two issues here:
m might not be a numeric type -- GHC is not reporting this error, at the moment.
the result of the difference is again of type m, but distance should produce a Double. This is the error GHC is reporting.
You need to restrict m to some numeric type, so that you can use -, and that type must admit a conversion to Double, otherwise you can't satisfy the distance signature.
One trivial way is:
instance Vector (OneD1 Double) where
distance (OD1 x1) (OD1 x2) = x2-x1
Another could be:
instance Real m => Vector (OneD1 m) where
distance (OD1 x1) (OD1 x2) = realToFrac (x2-x1)

Are there any Haskell libraries for integrating complex functions?

How to numerically integrate complex, complex-valued functions in Haskell?
Are there any existing libraries for it? numeric-tools operates only on reals.
I am aware that on complex plane there's only line integrals, so the interface I am interested in is something like this:
i = integrate f x a b precision
to calculate integral along straight line from a to b of function f on point x.
i, x, a, b are all of Complex Double or better Num a => Complex a type.
Please... :)
You can make something like this yourself. Suppose you have a function realIntegrate of type (Double -> Double) -> (Double,Double) -> Double, taking a function and a tuple containing the lower and upper bounds, returning the result to some fixed precision. You could define realIntegrate f (lo,hi) = quadRomberg defQuad (lo,hi) f using numeric-tools, for example.
Then we can make your desired function as follows - I'm ignoring the precision for now (and I don't understand what your x parameter is for!):
integrate :: (Complex Double -> Complex Double) -> Complex Double -> Complex Double -> Complex Double
integrate f a b = r :+ i where
r = realIntegrate realF (0,1)
i = realIntegrate imagF (0,1)
realF t = realPart (f (interpolate t)) -- or realF = realPart . f . interpolate
imagF t = imagPart (f (interpolate t))
interpolate t = a + (t :+ 0) * (b - a)
So we express the path from a to b as a function on the real interval from 0 to 1 by linear interpolation, take the value of f along that path, integrate the real and imaginary parts separately (I don't know if this can give numerically badly behaving results, though) and reassemble them into the final answer.
I haven't tested this code as I don't have numeric-tools installed, but at least it typechecks :-)

Resources