2

So, I'm trying to write my own replacement for Prelude, and I have (^) implemented as such:

{-# LANGUAGE RebindableSyntax #-}

class Semigroup s where
    infixl 7 *
    (*) :: s -> s -> s

class (Semigroup m) => Monoid m where
    one :: m

class (Ring a) => Numeric a where
    fromIntegral :: (Integral i) => i -> a
    fromFloating :: (Floating f) => f -> a

class (EuclideanDomain i, Numeric i, Enum i, Ord i) => Integral i where
    toInteger :: i -> Integer
    quot :: i -> i -> i
    quot a b = let (q,r) = (quotRem a b) in q
    rem :: i -> i -> i
    rem a b = let (q,r) = (quotRem a b) in r
    quotRem :: i -> i -> (i, i)
    quotRem a b = let q = quot a b; r = rem a b in (q, r)

-- . . .

infixr 8 ^
(^) :: (Monoid m, Integral i) => m -> i -> m
(^) x i
    | i == 0 = one
    | True   = let (d, m) = (divMod i 2)
                   rec = (x*x) ^ d in
               if m == one then x*rec else rec

(Note that the Integral used here is one I defined, not the one in Prelude, although it is similar. Also, one is a polymorphic constant that's the identity under the monoidal operation.)

Numeric types are monoids, so I can try to do, say 2^3, but then the typechecker gives me:

*AlgebraicPrelude> 2^3

<interactive>:16:1: error:
    * Could not deduce (Integral i0) arising from a use of `^'
      from the context: Numeric m
        bound by the inferred type of it :: Numeric m => m
        at <interactive>:16:1-3
      The type variable `i0' is ambiguous
      These potential instances exist:
        instance Integral Integer -- Defined at Numbers.hs:190:10
        instance Integral Int -- Defined at Numbers.hs:207:10
    * In the expression: 2 ^ 3
      In an equation for `it': it = 2 ^ 3

<interactive>:16:3: error:
    * Could not deduce (Numeric i0) arising from the literal `3'
      from the context: Numeric m
        bound by the inferred type of it :: Numeric m => m
        at <interactive>:16:1-3
      The type variable `i0' is ambiguous
      These potential instances exist:
        instance Numeric Integer -- Defined at Numbers.hs:294:10
        instance Numeric Complex -- Defined at Numbers.hs:110:10
        instance Numeric Rational -- Defined at Numbers.hs:306:10
        ...plus four others
        (use -fprint-potential-instances to see them all)
    * In the second argument of `(^)', namely `3'
      In the expression: 2 ^ 3
      In an equation for `it': it = 2 ^ 3

I get that this arises because Int and Integer are both Integral types, but then why is it that in normal Prelude I can do this just fine? :

Prelude> :t (2^)
(2^) :: (Num a, Integral b) => b -> a
Prelude> :t 3
3 :: Num p => p
Prelude> 2^3
8

Even though the signatures for partial application in mine look identical?

*AlgebraicPrelude> :t (2^)
(2^) :: (Numeric m, Integral i) => i -> m
*AlgebraicPrelude> :t 3
3 :: Numeric a => a

How would I make it so that 2^3 would in fact work, and thus give 8?

Crazycolorz5
  • 747
  • 6
  • 12
  • If I run your program, I simply get `Ambiguous occurrence ‘^’`. You can not simply override a name in Haskell – Willem Van Onsem Oct 31 '17 at 16:14
  • In my code, I'm using RebindableSyntax. Prelude's (^) is not in scope. Edit: Also, the Monoid typeclass I'm using is also mine. – Crazycolorz5 Oct 31 '17 at 16:15
  • If it helps, the code I'm using is all in this GitHub repo: https://github.com/Crazycolorz5/AlgebraicPrelude/tree/c468d6cda1bc8abaca350c5b736f804dd489b6f3 – Crazycolorz5 Oct 31 '17 at 16:21
  • 3
    I suspect this is due to the special-ness of `Num` in the defaulting rules, although a MVCE would be much appreciated (as in something standalone that I can run to replicate the problem). – Alec Oct 31 '17 at 16:28
  • @Alec I think you're right; do you know where in the Prelude code the defaults are specified, and how I can define them myself? Also, apologies for lack of an MVCE, there's a lot of interconnected code; the Groups, Order, and Numbers modules in the repo I linked should be all that's necessary to recreate this though. – Crazycolorz5 Oct 31 '17 at 16:38
  • What is your defaulting list? I bet it doesn't include an instance of `Numeric` or `Integral`. – Daniel Wagner Oct 31 '17 at 16:44
  • To the best of my knowledge, there's no way to add arbitrary classes to the defaulting mechanism. – dfeuer Oct 31 '17 at 17:07
  • Side note: your `Numeric` class seems very surprising to me. I can't see what it could possibly be for, and especially why you would name it as you did. – dfeuer Oct 31 '17 at 17:09
  • Thanks all for your responses. If I wanted to keep the behavior of defaulting, I should make Integral subclass from Num, and then specify that as a constraint in (^). (Interestingly, it still refuses to default if I don't explicitly state the Num command, despite Integral requiring Num) – Crazycolorz5 Oct 31 '17 at 17:57

1 Answers1

1

A Hindley-Milner type system doesn't really like having to default anything. In such a system, you want types to be either properly fixed (rigid, skolem) or properly polymorphic, but the concept of “this is, like, an integer... but if you prefer, I can also cast it to something else” as many other languages have doesn't really work out.

Consequently, Haskell sucks at defaulting. It doesn't have first-class support for that, only a pretty hacky ad-hoc, hard-coded mechanism which mainly deals with built-in number types, but fails at anything more involved.

You therefore should try to not rely on defaulting. My opinion is that the standard signature for ^ is unreasonable; a better signature would be

(^) :: Num a => a -> Int -> a

The Int is probably controversial – of course Integer would be safer in a sense; however, an exponent too big to fit in Int generally means the results will be totally off the scale anyway and couldn't feasibly be calculated by iterated multiplication; so this kind of expresses the intend pretty well. And it gives best performance for the extremely common situation where you just write x^2 or similar, which is something where you very definitely don't want to have to put an extra signature in the exponent.

In the rather fewer cases where you have a concrete e.g. Integer number and want to use it in the exponent, you can always shove in an explicit fromIntegral. That's not nice, but rather less of an inconvenience.

As a general rule, I try to avoid any function-arguments that are more polymorphic than the results. Haskell's polymorphism works best “backwards”, i.e. the opposite way as in dynamic language: the caller requests what type the result should be, and the compiler figures out from this what the arguments should be. This works pretty much always, because as soon as the result is somehow used in the main program, the types in the whole computation have to be linked to a tree structure.

OTOH, inferring the type of the result is often problematic: arguments may be optional, may themselves be linked only to the result, or given as polymorphic constants like Haskell number literals. So, if i doesn't turn up in the result of ^, avoid letting in occur in the arguments either.


“Avoid” doesn't mean I don't ever write them, I just don't do so unless there's a good reason.
leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
  • Numbers mod some prime `p` can be on the scale even for very large exponents indeed, and are frequently useful. – Daniel Wagner Oct 31 '17 at 18:03
  • @DanielWagner right, but you wouldn't use `^` for that kind of stuff, would you? – leftaroundabout Oct 31 '17 at 18:48
  • [Yes, sure I would.](https://en.wikipedia.org/wiki/RSA_(cryptosystem)#Encryption) – Daniel Wagner Oct 31 '17 at 18:59
  • @DanielWagner I know about modular exponentiation, my point is that you _wouldn't calculate it with Haskell's `^` operator anyway_, but with a function that's designed around the modulo behaviour. Although – it should actually be doable, with something like [`Data.Modular`](https://hackage.haskell.org/package/modular-arithmetic-1.2.1.2/docs/Data-Modular.html)... – leftaroundabout Oct 31 '17 at 19:02
  • Why wouldn't I calculate it with Haskell's `^` operator? I can think of two objections: 1. You want a specialized operator that first reduces the exponent mod `p`. But I think the specialized one would probably call `^` once it had a small exponent -- and that "small" exponent might still be bigger than an `Int`. 2. It's hard to write a type which lets you choose the prime at runtime without running afoul of mismatches in operations like `+`. I outline an `ST`-like trick for avoiding this problem in [another answer](https://stackoverflow.com/a/38926412/791604). – Daniel Wagner Oct 31 '17 at 19:12
  • @DanielWagner you wouldn't use `^` because you don't want the giant numbers to actually ever turn up in memory, just to then mod them down in the end. It's [not necessary](https://en.wikipedia.org/wiki/Modular_exponentiation#Memory-efficient_method). – leftaroundabout Oct 31 '17 at 19:21
  • A type which represents numbers mod `p` need not ever have the large numbers turn up in memory -- presumably the implementation of `*` for that type would include a call to `mod`, and `^` calls `*`. – Daniel Wagner Oct 31 '17 at 21:18
  • So you oppose the whole `Foldable` class, I imagine? As well as `Integral`? – dfeuer Nov 01 '17 at 01:47
  • @dfeuer “oppose” is way too strong – of course these have their place. And `Integral` is perfectly sensible for stuff where you actually need the _result_ to be big numbers that can't be stored in `Int`, or conversely a tight unboxed data structure where you don't want to afford 8 bytes for a single small number. My point is you shouldn't make function-arguments terminally-polymorphic† unless you have a good reason to. For instance, it's no good idea to write a function `IsString a => a -> B`, better make it simply `Text -> B`. — †I'm not sure this term makes sense, but you get what I mean... – leftaroundabout Nov 01 '17 at 09:04