13

Today I found this post on Quora, which claimed that

factorial(n) = def $ do    
    assert (n<=0) "Negative factorial"    
    ret <- var 1    
    i <- var n    
    while i $ do    
        ret *= i    
        i -= 1
    return ret

could be correct Haskell code. I got curious, and ended up with

factorial :: Integer -> Integer
factorial n = def $ do
  assert (n >= 0) "Negative factorial"
  ret <- var 1
  i   <- var n
  while i $ do
      ret *= i
      i   -= 1
  return ret

using var = newSTRef, canonical definitions for def, assert and while, and

a *= b = readSTRef b >>= \b -> modifySTRef a ((*) b)
a -= b = modifySTRef a ((+) (negate b))

However, (*=) and (-=) have different types:

(-=) :: Num a => STRef s a -> a -> ST s ()
(*=) :: Num a => STRef s a -> STRef s a -> ST s ()

So ret -= i wouldn't work. I've tried to create a fitting type class for this:

class (Monad m) => NumMod l r m where
  (+=) :: l -> r -> m ()
  (-=) :: l -> r -> m ()
  (*=) :: l -> r -> m ()

instance Num a => NumMod (STRef s a) (STRef s a) (ST s) where
  a += b    = readSTRef b >>= \b -> modifySTRef a ((+) b)
  a -= b    = readSTRef b >>= \b -> modifySTRef a ((+) (negate b))
  a *= b    = readSTRef b >>= \b -> modifySTRef a ((*) b)

instance (Num a) => NumMod (STRef s a) a (ST s) where
  a += b    = modifySTRef a ((+) (b))
  a -= b    = modifySTRef a ((+) (negate b))
  a *= b    = modifySTRef a ((*) (b))

That actually works, but only as long as factorial returns an Integer. As soon as I change the return type to something else it fails. I've tried to create another instance

instance (Num a, Integral b) => NumMod (STRef s a) b (ST s) where
  a += b    = modifySTRef a ((+) (fromIntegral $ b))
  a -= b    = modifySTRef a ((+) (negate . fromIntegral $ b))
  a *= b    = modifySTRef a ((*) (fromIntegral b))

which fails due to overlapping instances.

Is it actually possible to create a fitting typeclass and instances to get the factorial running for any Integral a? Or will this problem always occur?

Zeta
  • 103,620
  • 13
  • 194
  • 236
  • One possible solution would be to use undecidable instances. – Thomas M. DuBuisson May 26 '14 at 17:58
  • @ThomasM.DuBuisson: The code above actually uses `UndecidableInstances` already (although originally for something different, namely `class Booleanizeable b where toBool :: b -> Bool` for `while`, but still, it's in there). – Zeta May 26 '14 at 18:00
  • @Zeta Just to be clear you change factorial to have a sig `factorial :: Int -> Int` and it fails to compile? – Davorak May 26 '14 at 18:10
  • @Davorak: Exactly. `Int -> Int`, `Word -> Word`, anything beside `Integer -> Integer` will fail. – Zeta May 26 '14 at 18:13
  • Guess: an interaction between undecidable instances and defaulting. Have you tried giving the literal `1` an explicit signature? – dfeuer May 26 '14 at 19:00
  • @dfeuer: `i -= (1 :: Int)` works as expected, and was my first fix, but I'm interested in something similar to `Num`'s `fromIntegral` for such situations. – Zeta May 26 '14 at 19:18
  • 3
    I think the real problem is that what you're trying to do makes very little if any sense. Conflating values with references to those values is nothing but trouble even if you can make it work somehow. – dfeuer May 26 '14 at 19:40
  • When ghc still supported impredicative polymorphism better it was possible to create variables (`var`) that could be used as both l-values and r-values by being polymorphic. That way arithmetic operators could all work with r-values and assignment operators with l-values on the left. – augustss May 26 '14 at 20:34
  • @dfeuer: I suppose that this kind of weird mechanism is bound to be trouble at one point or another. That was never disclaimed in the question. I'm interested in this from a purely theoretical point of view. If I really want to write such code, I go back to an imperative language. – Zeta May 26 '14 at 21:11
  • @Zeta are you interested in solutions without extra classes? – fizruk May 26 '14 at 21:22
  • @fizruk: I'm interested in any solution, that will enable the `factorial` to have type `factorial :: Integral a => a -> a`. – Zeta May 26 '14 at 21:25
  • 3
    I don't feel like writing out a full answer right now, so I'll just point you to [this amusing blog post](http://augustss.blogspot.com/2007/08/programming-in-c-ummm-haskell-heres.html) which presents a DSL for very C-like Haskell. It's fundamentally similar to @fizruk's answer, but with some additional cleverness to make things work properly as lvalues and rvalues. – Tikhon Jelvis May 27 '14 at 09:24
  • @TikhonJelvis yeah that's definitely smarter and cleaner than phantom types (because phantom types make `Num` instance even more awkward and demands an explicit type signature and `ScoppedTypeVariables`, so...). – fizruk May 27 '14 at 09:31
  • Related: http://stackoverflow.com/q/6622524/1139697 – Zeta Apr 21 '17 at 07:25

1 Answers1

11

The idea

Idea is simple: wrap STRef s a in a new data type and make it an instance of Num.

Solution

First, we'll need only one pragma:

{-# LANGUAGE RankNTypes #-}

import Data.STRef    (STRef, newSTRef, readSTRef, modifySTRef)
import Control.Monad (when)
import Control.Monad.ST (ST, runST)

Wrapper for STRef:

data MyRef s a
  = MySTRef (STRef s a)  -- reference (can modify)
  | MyVal a              -- pure value (modifications are ignored)

instance Num a => Num (MyRef s a) where
  fromInteger = MyVal . fromInteger

A few helpers for MyRef to resemble STRef functions:

newMyRef :: a -> ST s (MyRef s a)
newMyRef x = do
  ref <- newSTRef x
  return (MySTRef ref)

readMyRef :: MyRef s a -> ST s a
readMyRef (MySTRef x) = readSTRef x
readMyRef (MyVal   x) = return x

I'd like to implement -= and *= using a bit more general alter helper:

alter :: (a -> a -> a) -> MyRef s a -> MyRef s a -> ST s ()
alter f (MySTRef x) (MySTRef y) = readSTRef y >>= modifySTRef x . flip f
alter f (MySTRef x) (MyVal   y) = modifySTRef x (flip f y)
alter _ _ _ = return ()

(-=) :: Num a => MyRef s a -> MyRef s a -> ST s ()
(-=) = alter (-)

(*=) :: Num a => MyRef s a -> MyRef s a -> ST s ()
(*=) = alter (*)

Other functions are almost unchanged:

var :: a -> ST s (MyRef s a)
var = newMyRef

def :: (forall s. ST s (MyRef s a)) -> a
def m = runST $ m >>= readMyRef

while :: (Num a, Ord a) => MyRef s a -> ST s () -> ST s ()
while i m = go
  where
    go = do
      n <- readMyRef i
      when (n > 0) $ m >> go

assert :: Monad m => Bool -> String -> m ()
assert b str = when (not b) $ error str

factorial :: Integral a => a -> a
factorial n = def $ do
    assert (n >= 0) "Negative factorial"
    ret <- var 1
    i   <- var n
    while i $ do
      ret *= i
      i -= 1
    return ret

main :: IO ()
main = print . factorial $ 1000

Discussion

Making Num instances like this feels a bit hacky, but we don't have FromInteger type class in Haskell, so I guess it's OK.

Another itchy thing is 3 *= 10 which is return (). I think it is possible to use phantom type to indicate whether MyRef is ST or pure and allow only ST on the LHS of alter.

fizruk
  • 1,855
  • 14
  • 24
  • Oh jeez. A type with _two_ constructors. That's really simple. I shouldn't try to model such things with too little sleep, I tried to build the values with `newSTRef`, but then you end up with `ST s (STRef s a)` of course. The missing `FromInteger` class is something I would really like to see in some future version of Haskell. Often you just want to use a literal for a non-`Num` type and you end up with hacky `Num` instances, as in your answer. Either way, good work. (by the way, `newMyRef = fmap MySTRef . newSTRef`) – Zeta May 26 '14 at 21:54