1

I'm still having a hard time wrapping my brain around Haskell and its type system. I posted another question: Haskell Converting Int to Float and that certainly helped, but I'm still stuck. I have what I think is a simpler example posted here:

ymod2 :: Integral b => b -> [b]
ymod2 n = map (\y->(y `mod` 2)) [0..n]    

powersOfx :: (Enum b, Floating b) =>  b -> b -> [b]
powersOfx n x = map (\y->(x**y)) [0..n]

thirdLst :: (Integral a, Enum a, Enum b, Floating b) => a -> b -> [b]    
thirdLst n x = zipWith (*) (ymod2 n) (powersOfx (fromIntegral n) x)

As you can see, I have a function that takes an Integral (ymod2) and a function that takes an Enum,Floating. These are both used (via zipWith) in thirdLst. I pass thirdLst an Integral and a Floating. I do attempt to change the Integral to a Floating for use in powersOfx. When I load this into WinGHCi I get:

• Couldn't match type ‘b’ with ‘a’
  ‘b’ is a rigid type variable bound by
    the type signature for:
      thirdLst :: forall a b.
                  (Integral a, Enum a, Enum b, Floating b) =>
                  a -> b -> [b]
   // and quite a bit more which I can post if desired

I've tried various permutations. I've removed the fromIntegral, I've tried different types, but nothing seems to work. I think my central question might be how to convert types. I thought fromIntegral would do it. I realize that quite possibly, the method powersOfx could be rewritten to use different types in this contrived example. My question would remain though. That is how to make these two methods play nicely together when zipping them.

Thanks, Dave

UPDATE. Based on reading Willem's answer I was able to get my code working by replacing thirdLst with:

thirdLst :: (Integral a, Floating b, Enum b) => a -> b -> [b]    
thirdLst n x = zipWith (*) (map fromIntegral (ymod2 n)) (powersOfx (fromIntegral n) x)

I believe Willem's example is far superior and future readers should study his answer. I'm marking his answer as the correct one. Thanks Willem!

Dave
  • 8,095
  • 14
  • 56
  • 99
  • 5
    Well the type signature is `(Floating a, Integral a) => a -> a -> [a]`, but this bascially is useless, since there are no common types in the Haskell system that are both `Floating` and `Integral`. – Willem Van Onsem May 10 '18 at 16:44
  • 1
    Haskell's numeric types are a bit inconvenient. For a beginner, I think it could be easier to work with concrete types such as `Float, Double, Int, Integer` rather than using a lot of typeclass constraints. In such way, you can write less general code, but in a simpler way. When you get more familiar with the language, you can try improving the generality. – chi May 10 '18 at 19:42

2 Answers2

4

Haskell's (numerical) type system

I'm still having a hard time wrapping my brain around Haskell and its type system.

Well I think that there are some aspects about the numerical types in Haskell:

  1. there are no implicit conversions between types (not between numerical types, nor between other types), so you can not implicitly convert an Int to a Float;
  2. most operators work on the same type. For example (+) :: Num a => a -> a -> a, so that means if one of the operands is an Int, then the other operand and the result are all Ints; and
  3. the numerical operators (like (+), (-), (**)) originate from type classes. For example (**) :: Fractional a => a -> a -> a originates from the Fractional type class.

Deriving the type of the function (and why it is problematic)

Let us now emulate the Haskell compiler. You define a function:

thirdLst n x = zipWith (*) (ymod2 n) (powersOfx (fromIntegral n) x)

So we here see that the function takes two parameters n, and x, so first we assume that thirdLst has type:

thirdLst :: a -> b -> c

but we still need to analyze the types by looking at the expression. We see that the ymod2 :: Integral d => d -> [d] (we here use another name, since those are basically different variables) function is called, so that means that the type of n is a as well as d, so that means that a and d are the same type, and ymod2 n produces a list [a]. We also have to add the Integral a type, and now the type of our function is:

thirdLst :: Integral a => a -> b -> c
ymod2 n :: Integral a => [a]

We also see in the expression that the fromIntegral :: (Integral e, Num f) => e -> f is called with n as parameter, so we conclude that a ~ e (a and e are the same type), and that fromIntegral n has type Num f => f. We again add an Integral type constraint to a, but since it is already constrained that way, the constraints on a remain the same:

thirdLst :: Integral a => a -> b -> c
ymod2 n :: Integral a => [a]
fromIntegral n :: Num f => f

The fromIntegral expression is only a subexpression of (powersOfx (fromIntegral n) x), since powersOfx has type powersOfx :: (Enum g, Floating g) => g -> g -> [g]. We thus know that f ~ g, and b ~ g, we thus know that the result of the expression is [b], and we have to add Enum b and Floating b as constraints:

thirdLst :: (Integral a, Enum b, Floating b) => a -> b -> c
ymod2 n :: Integral a => [a]
fromIntegral n :: Num b => b
powersOfx (fromIntegral n) x :: (Enum b, Floating b) => [b]

This is up to now no problem, the two parameters of thirdLst, n and x have a different type, but now we use zipWith :: (h -> i -> j) -> [h] -> [i] -> [j] and we use as first argument (*) :: Num k => k -> k -> k, so as a result we know that k ~ h ~ i ~ j, and thus that our zipWith (*) has type:

zipWith (*) :: Num k => [k] -> [k] -> [k]

and now the problem arises, we see that the two arguments of zipWith (*) need to have the same type. Since ymod2 n :: Integral a => [a] and powersOfx (fromIntegral n) x :: (Enum b, Floating b) => [b] are the parameters we use for zipWith (*) this means that k ~ a ~ b, so k, a and b are all the same type. So now we conclude:

thirdLst :: (Integral a, Enum a, Floating a, Num a) => a -> a -> [a]

So that means that the two parameters need to have the same type. Now this already results in an important issue: numbers typically are not Integral and Floating at the same time. There are in the most common numerical library no number types that are both Floating and Integral at the same time. So this makes the function quite useless.

Allowing more freedom

So we will need to find more generic functions, and more freedom. Your powersOfx function is too restrictive: since the length of the list an x need to have the same type. We can construct one where the two types are independent:

import Data.List(genericTake)

powersOfx :: (Num a, Integral i) => i -> a -> [a]
powersOfx n x = genericTake (n+1) (iterate (x*) 1)

for ymod2, you basically construct a list with a certain length that looks like [0, 1, 0, 1, ...]. So we can use cycle :: [a] -> [a] for that and again an genericTake (n+1):

ymod2 :: (Num a, Integral i) => i -> [a]
ymod2 n = genericTake (n+1) (cycle [0, 1])

and then our function is:

thirdLst :: (Num c, Integral a) => a -> c -> [c]
thirdLst n x = zipWith (*) (ymod2 n) (powersOfx n x)
Mor A.
  • 3,805
  • 2
  • 16
  • 19
Willem Van Onsem
  • 443,496
  • 30
  • 428
  • 555
  • Thanks again Willem. I'm still digesting your answer but am already learning new things. I did not realize when I use zipWith that both lists must be of same type. I did some experimenting and realize if I have "let d = 2::Int" and "let e = 2.3::Float" I can't even type d*e without an error! I assumed that the d would be automatically converted to a float. So not surprising that zipWith works that way. – Dave May 10 '18 at 20:44
  • Your example is far superior but there's something to be said for "learn by doing" so I humbly add my example with what I think it the barest of modifications as an update to my question above. Incidentally, if there is a better forum for asking what I'm guessing are very beginner questions, please let me know. – Dave May 10 '18 at 20:45
  • @Dave you can check out the [IRC channel](https://wiki.haskell.org/IRC_channel) which will provide you with real-time Q&A. Of course you can keep asking here (if the question hasn't been asked and is appropriate for SO), also consider other stack-exchange forums, for example the code review stack-exchange – Mor A. May 10 '18 at 21:10
  • 1
    @Dave to your first comment: `zipWith` does not require both lists to be of the same type, however, `zipWith (+)` or `zipWith (*)` does, specifically because the functions `(+)` and `(*)` take 2 arguments of the same type. An example where it is not the case: `zipWith (,) [0..] "Hello World"` will work just fine, since the function(constructor) `(,)` is of type `(,) :: a -> b -> (a,b)` – Mor A. May 10 '18 at 21:15
  • 2
    @Dave I was inspired by Willem's answer to learn a bit more about number types in GHC. I organized the details from the base documentation in a more digestible format http://mchaver.com/posts/2018-05-12-numbers-in-ghc-prelude.html – MCH May 12 '18 at 15:35
1
ymod2 :: Integral a => a -> [a]
ymod2 n = map (\y->(y `mod` 2)) [0..n]    

powersOfx :: (Enum b, Floating b) =>  b -> b -> [b]
powersOfx n x = map (\y->(x**y)) [0..n]

thirdLst :: (Integral a, Enum b, Floating b) => a -> b -> [b]    
thirdLst n x = zipWith (*) (fromIntegral <$> ymod2 n) (powersOfx (fromIntegral n) x)
MCH
  • 2,124
  • 1
  • 19
  • 34
  • MCH, If you try this, it will certainly load. However, I get (on WinGHCi) when type "thirdLst 5 0.5", something like "Ambiguous type variable 'a0' arising from a use of 'print' prevents the constraint '(Show a0)' from being solved ...." – Dave May 10 '18 at 18:21
  • No standard type satisfies both constraints `(Integral a, Floating a)`, so `thirdLst` above is essentially unusable. – chi May 10 '18 at 19:37
  • @Dave sorry about that, I updated the answer. I think it should work now. – MCH May 11 '18 at 00:49
  • 1
    @Dave a little trick that helps sometimes, enter the function into GHCi without a type signature, like `ymod2 n = map (\y->(y `mod` 2)) [0..n]` then run `:t` on the function. `:t ymod2` and it will give you a type signature, `ymod2 :: Integral b => b -> [b]`. It is not always the right one though. – MCH May 11 '18 at 00:53
  • 1
    Thanks MCH. I'm not familiar with <$> notation. I'll look it up. Also, see my update to my question where I pose one solution and Willem had a more elegant solution than mine in his answer. Fun stuff! – Dave May 11 '18 at 15:14
  • 1
    @Dave glad you are enjoying Haskell! `map` is only for lists, `fmap` is a more general form of `map` that can be applied to other types (and replace `map` for lists), `<$>` is the infix version of `fmap`. – MCH May 11 '18 at 16:43