Using the latest version of Bound
and Control.Lens.Plated
, the following transform
call causes the programm to loop infinitely and happily munches away at my RAM. Terminating the program funnily causes the correct result to be printed, although I don't know why.
I have traced the problem to the Scope
data type. Removing it causes the program to behave as expected.
Profiling with ./program +RTS -p -h
shows Data.Data.Lens.insertHitMap.populate
to be the problematic part. Some of the profiling is attached.
Is this expected behaviour with an official workaround or is this maybe a bug?
I am using GHC version 8.0.2, all packages with exception of bound-2
are part of stack lts-8.17
. The program is compiled as ghc test.hs
. Enabling or disabling optimizations doesn't affect the problem.
As I suspect that this is a bug, I opened an issue for this on ekmett
's bound
repository (for crossreferencing purposes).
-- file: test.hs
{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable,
DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Main (main) where
import Bound
import Control.Lens hiding (List)
import Control.Lens.Plated
import Data.Deriving (deriveShow1, deriveEq1)
import Data.Data
import Data.Data.Lens (uniplate)
data Expr a = Var a
| List [Expr a]
| Apply (Expr a) (Expr a)
| Lam (Scope () Expr a)
| Nop
deriving (Functor, Foldable, Traversable, Data)
main = do
print ex
print $ transform removeTest ex
ex :: Expr String
ex = List [Apply (Var "test") $ List [Var "arg1", Var "arg2"]
,Apply (Var "two") (Var "three")]
removeTest :: Expr String -> Expr String
removeTest = \expr -> case expr of
Apply (Var "test") _ -> Nop
_ -> expr
instance Data a => Plated (Expr a) where
plate = uniplate
makeLenses ''Expr
makeBound ''Expr
deriveEq1 ''Expr
deriveShow1 ''Expr
deriving instance Show a => Show (Expr a)
deriving instance Eq a => Eq (Expr a)
Output:
List [Apply (Var "test") (List [Var "arg1",Var "arg2"])
,Apply (Var "two") (Var "three")]
^CList [Nop,Apply (Var "two") (Var "three")]
-- profiterole stats
TOT INH IND
99.9 99.9 .1 MAIN MAIN (0)
99.9 99.9 .1 MAIN MAIN (0)
99.9 99.9 34.0 Main CAF (0)
65.9 65.9 - Data.Data.Lens fromOracle (35)
65.9 65.9 - Data.Data.Lens hitTest (0)
65.9 65.9 - Data.Data.Lens hitTest.\ (35)
65.9 65.9 - Data.Data.Lens readCacheFollower (30)
65.9 65.9 - Data.Data.Lens readCacheFollower.\ (30)
65.9 65.9 - Data.Data.Lens insertHitMap (1)
65.9 65.9 - Data.Data.Lens insertHitMap.populate (1)
65.9 65.9 56.4 Data.Data.Lens insertHitMap.populate.f (1824891)
2.3 2.3 2.3 Data.HashMap.Base clone16 (2682671)
2.1 2.1 2.1 Data.HashMap.Base hash (6204631)
1.7 1.7 .4 Data.HashMap.Array copy (1620382)
1.3 1.3 1.3 Data.HashMap.Array copy.\ (1620382)
1.1 1.1 1.1 Data.Data.Lens insertHitMap.populate.fs (2189870)
.9 .9 .9 Bound.Var gfoldl (364976)
.5 .5 .5 Data.HashMap.Array new_ (810191)
.5 .5 .5 Bound.Var gunfold (364976)
.3 .3 .3 Data.HashMap.Base sparseIndex (3620621)
.2 .2 .2 Bound.Scope gfoldl (182489)
Heap profile:
I'm just gonna answer this with: it's a bug, dfeuer reported it to ekmett/lens
.
In the meantime using tinplate
instead of uniplate
is a feasible workaround.