Type mismatch in signature and locally introduced term - haskell

Consider the following code:
-- | Parse a 64bit word in little-endian format.
word64le :: Get ByteString e Word64
word64le = do
s <- elems 8
pure $ foldl' (.|.) 0 [shiftL (fromIntegral b) (i * 8) | (i, b) <- zip [0 .. 7] (atomize s)]
Per the comment, this reads out a Word64 from a ByteString by first pulling an 8-byte ByteString (the elems call), then unpacking it (the atomize call) and doing the obvious shift left dance. So far so good. Now this code can very obviously be generalized to other machine integral types, we just need to get hold of the number of bits of such a type and that is supplied by the FiniteBits class. So doing the generalization:
-- | Parse an integral word in little-endian format.
integralLe :: (FiniteBits w, Integral w, Bounded w) => Get ByteString e w
integralLe = do
s <- elems (fromIntegral n)
pure $ foldl' (.|.) 0 [shiftL (fromIntegral b) (i * 8) | (i, b) <- zip [0 .. n - 1] (atomize s)]
where
n = finiteBitSize (minBound :: w) `quot` 8
This does not work, with GHC complaining that "Could not deduce (Bounded w1) arising from a use of ‘minBound’ from the context: (FiniteBits w, Integral w, Bounded w)". So it seems that my type annotation minBound :: w is not enough to convince GHC that I mean the same w as in the function signature; is my diagnosis correct? And if yes, how do I tell GHC that the two w types are the same?
note(s):
on GHC 9.2 with a nightly stackage.
sorry about the poor question title, but cannot think of anything better.
edit(s):
per the comment added {-# LANGUAGE ScopedTypeVariables #-} at the top of the file but having the same error, namely "Could not deduce (Bounded w2) arising from a use of ‘minBound’ from the context: (FiniteBits w, Integral w, Bounded w) bound by the type signature for:"
Aha. If I add an explicit forall e w . in the function signature to the left of the constraint it works, even without the ScopedTypedVariables extensions (maybe because I am using language GHC2021). No on, to understand why the heck this works...

Haskell has some... let's charitably call it "weird"... rules for how type variables are scoped by default.
-- | Parse an integral word in little-endian format.
integralLe :: (FiniteBits w, Integral w, Bounded w) => Get ByteString e w
integralLe = do
s <- elems (fromIntegral n)
pure $ foldl' (.|.) 0 [shiftL (fromIntegral b) (i * 8) | (i, b) <- zip [0 .. n - 1] (atomize s)]
where
n = finiteBitSize (minBound :: w) `quot` 8
You're right that Haskell will throw an implicit forall w at the start of the integralLe type signature, but it's not actually a ScopedTypeVariables forall. By default, the scope of that variable is just that one line. It is not considered a type variable inside of any type ascriptions or signatures in where clauses, let clauses, or anything else inside the function. That's where ScopedTypeVariables comes in. With ScopedTypeVariables, an explicit forall makes the type variable available lexically to anything inside of the function body, including where blocks. (And, as you've correctly noted, ScopedTypeVariables is included in GHC2021). Hence,
integralLe :: forall w. (FiniteBits w, Integral w, Bounded w) => Get ByteString e w
will work.

Related

Not being able spot the problem in the code in Dijkstra’s Haskell implementation

I understand that asking “why my code does not work” is not the best question. However, I am asking as I wish to learn more about using monads in Haskell in an algorithmic context for graph theory problems, and took the following code as a starting point to understand how the ST monad would be used in such an algorithm.
I made progress on some simpler algorithms (quick sort) and progressed to Dijkstra’s algorithm. I was unable to compile the following implementation (written in 2012) of Dijkstra’s algorithm: http://www.rosettacode.org/wiki/Dijkstra%27s_algorithm#Haskell
The error I get is the following :
• Non type-variable argument
in the constraint: MArray (STArray s) e0 m
(Use FlexibleContexts to permit this)
• When checking the inferred type
f :: forall (m :: * -> *).
(MArray (STArray s) e0 m, MArray (STArray s) v m) =>
Set (a0, v) -> (v, a0) -> m (Set (a0, v))
In the expression:
let
edges = adj_list ! u
f vertex_queue (v, weight) = do ...
in foldM f vertex_queue' edges >>= aux
In a case alternative:
Just ((dist, u), vertex_queue')
-> let
edges = adj_list ! u
f vertex_queue (v, weight) = ...
in foldM f vertex_queue' edges >>= aux
|
18 | f vertex_queue (v, weight) = do
(PS : this is not for a school assignment, this is just self-motivated), I have tried everything I knew in Haskell (including proper indentations) but couldn’t succeed.
As the error says, the algorithm makes use of the FlexibleContexts extension [haskell.org]. Normally only constraints of the form C t, or C (q t1 t2 … tn) can be used, with C a typeclass and q, t and ti type variables. By enabling the FlexibleContexts, the constraints can also make use of type constructors.
The compiler detects that the type constraints use (MArray (STArray s) e0 m, MArray (STArray s) v m) as context, so with STArray as a type constructor, which is not allowed. The compiler detects this and raises an error that mentions:
(Use FlexibleContexts to permit this)
The compiler thus gives advise on what might fix the problem, although I agree it is a bit "cryptic".
You thus can enable this with a language pragma in the head of the file:
{-# LANGUAGE FlexibleContexts #-}
--- rest of the file &vellip;

Haskell: Non type-variable argument in the constraint

I created some functions to get some comfort with 2D geometry.
In this example I use Geom2D from CubicBezier package.
Complete code of my program: https://gist.github.com/nskeip/3784d651ac646a67c5f246f048949af4
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts #-}
import Geom2D
left :: (Num a) => Point a -> a -> Point a
left (Point x y) n = Point (x - n) y
right :: (Num a) => Point a -> a -> Point a
right (Point x y) n = Point (x + n) y
up :: (Num a) => Point a -> a -> Point a
up (Point x y) n = Point x (y - n)
down :: (Num a) => Point a -> a -> Point a
down (Point x y) n = Point x (y + n)
They work like this:
> (Point 0 0) `up` 10
Point 0.0 -10.0
Where Point is defined like this:
data Point a = Point {
pointX :: !a,
pointY :: !a
} deriving (Eq, Ord, Functor, Foldable, Traversable)
And everything was fine untill I thought: "Hey, it would be nice to make that functions (actualy, operators) work with thigs like Line - not only Point"
So I declared a class (not taking left and right to keep thigs simple):
class Num n => Moving p n where
up' :: n -> p -> p
down' :: n -> p -> p
up' n = down' (-n)
down' n = up' (-n)
And an instance of Moving for Point a data type:
instance Num a => Moving (Point a) a where
up' n (Point x y) = Point x (y - n)
But when I try to use it, I got an error:
✗ ghci ./uno.hs
GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( uno.hs, interpreted )
Ok, modules loaded: Main.
*Main> let p = Point { pointX = 0, pointY = 0 }
*Main> up' 10 p
<interactive>:3:1:
Non type-variable argument in the constraint: Moving (Point a) n
(Use FlexibleContexts to permit this)
When checking that ‘it’ has the inferred type
it :: forall n a. (Num a, Moving (Point a) n) => Point a
And the thing that confuses me much: I put the FlexibleContexts pragma to the pragma listing in the head, but ghcu still suggest me to get it included.
How can I fix my class / instance to get parametric polymorphism working? :)
And the thing that confuses me much: I put the FlexibleContexts pragma to the pragma listing in the head, but ghcu still suggest me to get it included.
This only enables the extension in the module itself. To write this code in GHCi, you need to enable the extension in GHCi: :set -XFlexibleContexts.
But this is only part of the problem. It looks like for your class p should determine n: you can only move a Point a up and down by a, right? But as it stands, nothing stops you from defining more Moving (Point a) SomeOtherType instances, and the compiler doesn't assume you won't. So a and n in the inferred type are completely unrelated, where you want them to be the same. This can be fixed by adding the FunctionalDependencies extension and changing the class declaration to say
class Num n => Moving p n | p -> n where
which means exactly that there can't be instances with same p and different n.
I think that's enough to make it work. The code will still be underdetermined because it allows any numeric a, but defaulting rules will pick Integer.

Special runtime representation of [] type?

Consider the simple definition of a length-indexed vector:
data Nat = Z | S Nat
infixr 5 :>
data Vec (n :: Nat) a where
V0 :: Vec 'Z a
(:>) :: a -> Vec n a -> Vec ('S n) a
Naturally I would at some point need the following function:
vec2list :: Vec n a -> [a]
However, this function is really just a fancy identity. I believe that the runtime representations of these two types are the same, so
vec2list :: Vec n a -> [a]
vec2list = unsafeCoerce
should work. Alas, it does not:
>vec2list ('a' :> 'b' :> 'c' :> V0)
""
Every input simply returns the empty list. So I assume my understand is lacking. To test it, I define the following:
data List a = Nil | Cons a (List a) deriving (Show)
vec2list' :: Vec n a -> List a
vec2list' = unsafeCoerce
test1 = vec2list' ('a' :> 'b' :> 'c' :> V0)
data SomeVec a = forall n . SomeVec (Vec n a)
list'2vec :: List a -> SomeVec a
list'2vec x = SomeVec (unsafeCoerce x)
Surprisingly this works! It certainly isn't an issue with the GADT then (my initial thought).
I think that the List type is really identical at runtime to []. I try to test this too:
list2list :: [a] -> List a
list2list = unsafeCoerce
test2 = list2list "abc"
and it works! Based on this fact, I have to conclude that [a] and List a must have the same runtime representation. And yet, the following
list2list' :: List a -> [a]
list2list' = unsafeCoerce
test3 = list2list' (Cons 'a' (Cons 'b' (Cons 'c' Nil)))
does not work. list2list' again always returns the empty list. I believe that "having identical runtime representations" must be a symmetric relation, so this doesn't seem to make sense.
I began to think maybe there's something funny with "primitive" types - but I always believed that [] is only special syntactically, not semantically. It seems that's the case:
data Pair a b = Pair a b deriving (Show, Eq, Ord)
tup2pair :: (a,b) -> Pair a b
tup2pair = unsafeCoerce
pair2tup :: Pair a b -> (a,b)
pair2tup = unsafeCoerce
The first function works and the second does not - same as the in the case of List and []. Although in this case, pair2tup segfaults as opposed to always returning the empty list.
It seems to be consistently asymmetric with respect to types which use "built-in" syntax. Back to the Vec example, the following
list2vec :: [a] -> SomeVec a
list2vec x = SomeVec (unsafeCoerce x)
works just fine as well! The GADT really isn't special.
The question is: how do the runtime representations of types which use "built-in" syntax differ from those that do not?
Alternatively, how does one write a zero-cost coercion from Vec n a to [a]? This doesn't answer the question but solves the problem.
Testing was done with GHC 7.10.3.
As noted by a commenter, this behaviour is only present when interpreting. When compiled, all functions work as expected. The question still applies, just to runtime representation when interpreting.
Now to answer your main question, this thread appears to have the answer: start ghci with -fobject-code:
$ ghci /tmp/vec.hs
GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( /tmp/vec.hs, interpreted )
Ok, modules loaded: Main.
*Main> print $ vec2list ('a' :> 'b' :> 'c' :> V0)
""
With -fobject-code:
$ ghci -fobject-code /tmp/vec.hs
GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( /tmp/vec.hs, /tmp/vec.o )
Ok, modules loaded: Main.
Prelude Main> print $ vec2list ('a' :> 'b' :> 'c' :> V0)
"abc"
The modules that contain [] and (,) are all compiled, which causes their runtime representation to be different from isomorphic datatypes in interpreted modules. According to Simon Marlow on the thread I linked, interpreted modules add annotations for the debugger. I think this also explains why tup2pair works and pair2tup doesn't: missing annotations isn't a problem for interpreted modules, but the compiled modules choke on the extra annotations.
-fobject-code has some downsides: longer compilation time, only brings exported functions in scope, but it has the additional advantage that running the code is much faster.
To answer only your alternative question, you could create a newtype with a non-exported constructor to give a list a type-level length and a zero-cost coercion to lists:
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
module Vec (Nat(..), Vec, v0, (>:>), vec2list) where
data Nat = Z | S Nat
newtype Vec (n :: Nat) a = Vec { unVec :: [a] }
v0 :: Vec Z a
v0 = Vec []
infixr 5 >:>
(>:>) :: a -> Vec n a -> Vec ('S n) a
a >:> (Vec as) = Vec (a : as)
vec2list :: Vec n a -> [a]
vec2list (Vec as) = as
As long as the Vec constructor is not in scope (so only v0 and >:> can be used to construct vectors) the invariant that the type-level number represents the length can't be violated.
(This approach definitely has my preference over unsafeCoerce, as anything with unsafeCoerce could break with every update of GHC or on different platforms.)

How to overload a function for multiplying [Double] in Haskell (ad-hoc polymorphism)?

The way to have ad-hoc polymorphism (function overloading) in Haskell is through type classes (see answers to this, this and this question, among others).
But I'm struggling to define an overloaded mult (product) function for the following cases:
mult: [Double] -> Double -> [Double]
mult: Double -> [Double] -> [Double]
mult: [Double] -> [Double] -> [Double]
Thanks
(At least, case 1 [Double]*Double and case 3 [Double]*[Double] would be necessary).
As always, statements like "I'm trying (with no success) this" are not quite as useful as you would like: it's good that you included your code, but if you are getting an error message from the compiler, tell us what it is! They're very instructive, and are printed for a reason.
I just tried what you wrote, and this is in fact the error message you are (probably) getting:
*Multiplication> mul 1 [2]
Non type-variable argument
in the constraint: Multipliable ta [t] tc
(Use FlexibleContexts to permit this)
When checking that ‘it’ has the inferred type
it :: forall ta tc t. (Num ta, Num t, Multipliable ta [t] tc) => tc
Now, you could try just turning on FlexibleContexts, but that doesn't seem to solve the problem. But, as is often the case when the compiler is telling you it's having trouble inferring types, you should try adding some explicit types and see if that helps:
*Multiplication> mul (1::Double) [2 :: Double]
[2.0]
Basically, the compiler can't be sure which overload of mul you want: 1 and 2 are polymorphic and could be any numeric type, and while there is only one suitable overload for mul now, the compiler doesn't make such an inference unless it can prove no other overload could ever exist in this context. Fully specifying the argument types is enough to resolve the problem.
An alternative approach to this particular problem is to use a typeclass for each argument, to convert it into the canonical type [Double], rather than a typeclass for the arguments as a whole. This is a more specific solution than general ad hoc polymorphism, and not all problems will fit, but for something like treating a single number like a list of numbers it should be fine:
module Multiplication where
import Control.Monad (liftM2)
class AsDoubles a where
doubles :: a -> [Double]
instance AsDoubles Double where
doubles = return
instance AsDoubles [Double] where
doubles = id
mult :: (AsDoubles a, AsDoubles b) => a -> b -> [Double]
mult x y = liftM2 (*) (doubles x) (doubles y)
*Multiplication> mult [(1 :: Double)..5] [(1 :: Double)..3]
[1.0,2.0,3.0, -- whitespace added for readability
2.0,4.0,6.0,
3.0,6.0,9.0,
4.0,8.0,12.0,
5.0,10.0,15.0]
I've managed to do it this way. Certainly not very nice.
I think anyone should consider the comments and critics by leftaroundaobut to the question, that I quote below for convenience and relevance.
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances #-}
class Multipliable ta tb tc | ta tb -> tc where
mul :: ta -> tb -> tc
instance Multipliable [Double] Double [Double] where
mul p k = map (*k) p --mul p k = map (\a -> k * a) p
instance Multipliable Double [Double] [Double] where
mul k p = map (*k) p --mul p k = map (\a -> k * a) p
instance Multipliable [Double] [Double] [Double] where
mul p q = p -- dummy implementation
r = [1.0, 2.0, 3.0] :: [Double]
r1 = (mul :: [Double] -> Double -> [Double]) r 2.0
r2 = (mul :: Double -> [Double] -> [Double]) 2.0 r
r3 = (mul :: [Double] -> [Double] -> [Double]) r1 r2
main = do
print r1
print r2
print r3
Why do you want this anyway? Just because Matlab allows multiplying
anything you throw at it doesn't mean this is a good idea. Check out
vector-space for properly dealing with
multidimensional-multiplications. Alternatively, if you don't care so
much for mathematical elegance, you can use hmatrix (which is in fact
a lot like Matlab/Octave in Haskell), or linear.
I think it's a bad idea in general, and really unnecessary in Haskell because you can just write map (*x) ys or zipWith (*) xs ys
to make you intent explicit. This of course doesn't work for
polymorphic code that's supposed to handle both scalars and vectors –
however, writing such code to just deal with scalars or lists of any
length is rather asking for trouble. It's awkward to specify which
list needs to have a length matching which other list and what length
the result will be etc.. This is where vector-space or linear shine,
because they check dimensions at compile time.

Pattern matching on length using this GADT:

I've defined the following GADT:
data Vector v where
Zero :: Num a => Vector a
Scalar :: Num a => a -> Vector a
Vector :: Num a => [a] -> Vector [a]
TVector :: Num a => [a] -> Vector [a]
If it's not obvious, I'm trying to implement a simple vector space. All vector spaces need vector addition, so I want to implement this by making Vector and instance of Num. In a vector space, it doesn't make sense to add vectors of different lengths, and this is something I would like to enforce. One way I thought to do it would be using guards:
instance Num (Vector v) where
(Vector a) + (Vector b) | length a == length b =
Vector $ zipWith (+) a b
| otherwise =
error "Only add vectors with the same length."
There is nothing really wrong with this approach, but I feel like there has to be a way to do this with pattern matching. Perhaps one way to do it would be to define a new data type VectorLength, which would look something like this:
data Length l where
AnyLength :: Nat a => Length a
FixedLength :: Nat a -> Length a
Then, a length component could be added to the Vector data type, something like this:
data Vector (Length l) v where
Zero :: Num a => Vector AnyLength a
-- ...
Vector :: Num a => [a] -> Vector (length [a]) [a]
I know this isn't correct syntax, but this is the general idea I'm playing with. Finally, you could define addition to be
instance Num (Vector v) where
(Vector l a) + (Vector l b) = Vector $ zipWith (+) a b
Is such a thing possible, or is there any other way to use pattern matching for this purpose?
What you're looking for is something (in this instance confusingly) named a Vector as well. Generally, these are used in dependently typed languages where you'd write something like
data Vec (n :: Natural) a where
Nil :: Vec 0 a
Cons :: a -> Vec n a -> Vec (n + 1) a
But that's far from valid Haskell (or really any language). Some very recent extensions to GHC are beginning to enable this kind of expression but they're not there yet.
You might be interested in fixed-vector which does a best approximation of a fixed Vector available in relatively stable GHC. It uses a number of tricks between type families and continuations to create classes of fixed-size vectors.
Just to add to the example in the other answer - this nearly works already in GHC 7.6:
{-# LANGUAGE DataKinds, GADTs, KindSignatures, TypeOperators #-}
import GHC.TypeLits
data Vector (n :: Nat) a where
Nil :: Vector 0 a
Cons :: a -> Vector n a -> Vector (n + 1) a
That code compiles fine, it just doesn't work quite the way you'd hope. Let's check it out in ghci:
*Main> :t Nil
Nil :: Vector 0 a
Good so far...
*Main> :t Cons "foo" Nil
Cons "foo" Nil :: Vector (0 + 1) [Char]
Well, that's a little odd... Why does it say (0 + 1) instead of 1?
*Main> :t Cons "foo" Nil :: Vector 1 String
<interactive>:1:1:
Couldn't match type `0 + 1' with `1'
Expected type: Vector 1 String
Actual type: Vector (0 + 1) String
In the return type of a call of `Cons'
In the expression: Cons "foo" Nil :: Vector 1 String
Uh. Oops. That'd be why it says (0 + 1) instead of 1. It doesn't know that those are the same. This will be fixed (at least this case will) in GHC 7.8, which is due out... In a couple months, I think?

Resources