#5267: Arrow command combinators
----------------------------------------+-----------------------------------
  Reporter:  peteg                      |          Owner:                  
      Type:  bug                        |         Status:  new             
  Priority:  normal                     |      Milestone:                  
 Component:  Compiler                   |        Version:  7.0.3           
Resolution:                             |       Keywords:                  
  Testcase:                             |      Blockedby:                  
Difficulty:                             |             Os:  Unknown/Multiple
  Blocking:                             |   Architecture:  Unknown/Multiple
   Failure:  GHC rejects valid program  |  
----------------------------------------+-----------------------------------
Changes (by peteg):

 * cc: peteg (added)
  * status:  closed => new
  * resolution:  invalid =>


Comment:

 Ross, thanks for the clarification. I was playing golf with code of this
 form:

 {{{
 {-# LANGUAGE Arrows #-}
 module T where

 import Prelude
 import Control.Arrow

 t = proc () ->
      do rec x <- (| (arr id) (returnA -< x) |)
         y <- arr id -< x
         returnA -< y
 }}}

 (for non-trivial arrows) and surprised to get this error. The question was
 whether one can put anything between {{{<-}}} and {{{(|}}}, as I did in
 the original bug report.

 My operators tend to be of the form:

 arrAC :: Arrow (~>) => (env ~> a) -> (env ~> a) -> (env ~> a)

 which syntactically doesn't satisfy your requirement but seems to work
 anyway. I get confused by just where the syntactic criteria kick in and
 why.

 In any case can we let this bug stand as a complaint that saying some type
 variable has the "wrong shape" is a terrible error message? GHC usually
 tells me what it was expecting.

 cheers
 peter

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

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to