[GHC] #12167: <<loop>> when zip + unzipping a shadowed Vector type variable

#12167: <<loop>> when zip + unzipping a shadowed Vector type variable -------------------------------------+------------------------------------- Reporter: markog | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Windows Architecture: x86_64 | Type of failure: Incorrect result (amd64) | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs 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? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12167 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12167: <<loop>> when zip + unzipping a shadowed Vector type variable -------------------------------------+------------------------------------- Reporter: markog | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): There is recursion; `x` depends on `xd`, and `xd` depends on `x`. Note that `let` in Haskell is a `letrec`. Does that address your concerns? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12167#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12167: <<loop>> when zip + unzipping a shadowed Vector type variable -------------------------------------+------------------------------------- Reporter: markog | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by markog): Well, I believe you if you say so, but I do not exactly see how. I can sort of see it. I forgot that Haskell does not read from the top down. {{{ (x,d) = xd xd = V.zip x d |> V.unzip }}} The above is a valid code fragment in Haskell while in F# it would not see the xd on the first line. I'll be more careful about shadowing in the future. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12167#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12167: <<loop>> when zip + unzipping a shadowed Vector type variable -------------------------------------+------------------------------------- Reporter: markog | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: invalid | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by markog): * status: new => closed * resolution: => invalid -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12167#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC