[GHC] #13547: Lint error in arrows program

GHC ghc-devs at haskell.org
Mon Apr 10 11:44:33 UTC 2017


#13547: Lint error in arrows program
-------------------------------------+-------------------------------------
        Reporter:  cipher1024        |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.0.1
  (CodeGen)                          |
      Resolution:                    |             Keywords:  Arrows
Operating System:  Unknown/Multiple  |         Architecture:  x86_64
 Type of failure:  Compile-time      |  (amd64)
  crash or panic                     |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  10158             |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by cipher1024):

 > Aside from some warnings, of course, which are due to minimizing the
 program down so much.

 With ghc-7.10.3, compiling with `-dcore-lint` I get a similar `Core Lint
 errors`.

 I have trimmed down the example further (see below). It seems to be a
 product of the interplay between existential types and arrow notation.

 The problem seems to come up because an existential type variable becomes
 free as a result of the following statement:

 {{{
 Cell prxy' <- id -< prxy
 }}}

 After staring at it for a minute or so, I find that I cannot desugar the
 arrow notation in `step`. The obvious candidate is:

 {{{
 step = id >>> arr (\(Cell prxy) -> prxy) >>> stepList
 }}}

 but the internal function `(\(Cell prxy) -> prxy)` cannot be given a type
 because of the existential type of `Cell`. Could this be related to the
 bug?

 ----


 {{{
 {-# LANGUAGE ExistentialQuantification #-}
 {-# LANGUAGE Arrows #-}
 module Document.Phase.Proofs2 (step) where

 import Control.Arrow
 import Control.Category

 import Data.Proxy

 import Prelude hiding (id,(.))

 data Cell1
    = forall a. Cell (Proxy a)

 data LatexParserA a g = LatexParserA
 instance Category LatexParserA where
 instance Arrow    LatexParserA  where

 -----------------------------

 stepList :: LatexParserA (Proxy rule) r
 stepList = error "urk"

 step :: LatexParserA Cell1 r
 step = proc prxy -> do
                 Cell prxy' <- id -< prxy
                 stepList -< prxy'
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13547#comment:28>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list