<<loop>> when zip + unzipping a shadowed Vector type variable
module Main where
import Data.Vector.Unboxed (Vector)
import qualified Data.Vector.Unboxed as V
(|>) :: a -> (a -> b) -> b
x |> f = f x
main = do
s <- do
x <- return $ V.fromList [1,2,3,4] :: IO (Vector Int)
d <- return $ V.fromList [1,2,3,4] :: IO (Vector Int)
let
xd :: (Vector Int, Vector Int)
xd =
V.zip x d
|> V.unzip
(x,d) = xd -- here is where the error happens
-- returning xd works
-- removing the shadowing also works
in return x
print s
I do not see how the above code warrants a <<loop>> error as there is really no recursion in it. The linter always complains when I shadow variables, but I often use the above style in F# to reduce the namespace bloat. Shadowing is not a problem when the variables have different types.
Is the above really a compiler error?
Trac metadata
Trac field | Value |
---|---|
Version | 7.10.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |