Space-leak incurred by constraints

Christiaan Baaij christiaan.baaij at gmail.com
Wed Jul 6 08:08:01 UTC 2016


Hi,

The following reduced test-case:

 > {-# LANGUAGE DataKinds, TypeOperators, TypeFamilies, ConstraintKinds,
 >              FlexibleContexts, BangPatterns #-}
 > module ConstraintLeak where
 >
 > import GHC.TypeLits
 > import Data.Proxy
 >
 > type Constraint1 n
 >     = ( Constraint2 n
 >       , Constraint2 (2^n)
 >       )
 > type Constraint2 n
 >     = ( KnownNat n
 >       , ((n-1)+1) ~ n -- Comment this line to run in constant space
 >       )
 >
 > test :: Constraint1 x => Proxy x -> String
 > test !s | s == s = test s
 >
 > main :: IO ()
 > main = putStr (test (Proxy :: Proxy 3))

contains a space-leak when compiled without optimisations (i.e. -O0 or 
in GHCi). It's true that the code doesn't actually do anything (when 
compiled with -O you get "Exception <<loop>>"), but I'm using it to 
exemplify some code that runs for some time, and then prints something.

As you can see, 'test' is strict in its arguments, but it seems lazy in 
its constraints. When I look at the heap profile (-hy), I see it rapidly 
accumulating values of the following types:

- ~
- KnownNat
- (,)

The problem with these constraints, unlike a normal type-class 
constraints, is that I cannot 'seq' one of its members to force the 
dictionary and hence be strict in the constraints.

We stumbled upon this particular space-leak while trying to find a 
space-leak in our own code; we don't think it's the real culprit in our 
own code, but find it disturbing nonetheless.
GHCi is heavily used in our work-flow, meaning we often run in an -O0 
setting, so I would like to know if it is possible to plug this 
constraint-induced space-leak.

Regards,

Christiaan Baaij


More information about the Glasgow-haskell-users mailing list