[Haskell-cafe] Type constraint with RankNTypes gradually slows down function?

Ben Gunton ben.gunton at gmail.com
Mon Jun 15 22:38:00 UTC 2015


When I write a function with the type constraint "embedded" in the
function's type declaration, instead of at the beginning, the function
takes longer each time it is run. The simplest example I could write is
this: http://lpaste.net/134563. "run1" is near instantaneous the first
time, but gets marginally slower after each iteration... after thousands of
iterations it takes about a millisecond to run (and keeps getting worse).
"run2" is always near instantaneous. What is happening in "run1" that makes
it slow down?

PS: The example is fairly contrived, I know "run1"'s type declaration
wouldn't be used in practice.

Thanks for any guidance!

{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}

module Main where

import Control.Monad.State.Strict
import qualified Data.Time.Clock as Clock
import Control.Exception

run1 :: (Int -> (Num Int => State Int Bool)) -> Int -> IO ()
run1 f state = do
    t1 <- Clock.getCurrentTime
    evaluate $ runState (f 1) state
    t2 <- Clock.getCurrentTime
    print $ Clock.diffUTCTime t2 t1
    run1 f state

run2 :: Num s => (Int -> State s Bool) -> s -> IO ()
run2 f state = do
    t1 <- Clock.getCurrentTime
    evaluate $ runState (f 1) state
    t2 <- Clock.getCurrentTime
    print $ Clock.diffUTCTime t2 t1
    run2 f state

main :: IO ()
main = run1 (const $ return False) 1
--main = run2 (const $ return False) 1
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150615/682e3bda/attachment.html>


More information about the Haskell-Cafe mailing list