Forked from
Glasgow Haskell Compiler / GHC
5501 commits behind the upstream repository.
-
PHASE 1: we never rewrite Concrete# evidence. This patch migrates all the representation polymorphism checks to the typechecker, using a new constraint form Concrete# :: forall k. k -> TupleRep '[] Whenever a type `ty` must be representation-polymorphic (e.g. it is the type of an argument to a function), we emit a new `Concrete# ty` Wanted constraint. If this constraint goes unsolved, we report a representation-polymorphism error to the user. The 'FRROrigin' datatype keeps track of the context of the representation-polymorphism check, for more informative error messages. This paves the way for further improvements, such as allowing type families in RuntimeReps and improving the soundness of typed Template Haskell. This is left as future work (PHASE 2). fixes #17907 #20277 #20330 #20423 #20426 updates haddock submodule ------------------------- Metric Decrease: T5642 -------------------------
PHASE 1: we never rewrite Concrete# evidence. This patch migrates all the representation polymorphism checks to the typechecker, using a new constraint form Concrete# :: forall k. k -> TupleRep '[] Whenever a type `ty` must be representation-polymorphic (e.g. it is the type of an argument to a function), we emit a new `Concrete# ty` Wanted constraint. If this constraint goes unsolved, we report a representation-polymorphism error to the user. The 'FRROrigin' datatype keeps track of the context of the representation-polymorphism check, for more informative error messages. This paves the way for further improvements, such as allowing type families in RuntimeReps and improving the soundness of typed Template Haskell. This is left as future work (PHASE 2). fixes #17907 #20277 #20330 #20423 #20426 updates haddock submodule ------------------------- Metric Decrease: T5642 -------------------------
Code owners
Assign users and groups as approvers for specific file changes. Learn more.
PandocArrowCmd.hs 1.25 KiB
{-
this test file was extracted from Text.Pandoc.Readers.Odt.ContentReader,
which caused a panic in GHC.Tc.Class.Instance.hasFixedRuntimeRep:
error: panic! (the 'impossible' happened)
hasFixedRuntimeRep: not of form 'TYPE rep'
ty = c_anCXp[tau:0]
ki = k_anCXl[tau:0]
frrOrig = The arrow command `returnA -< anchorElem_anC3K'
does not have a fixed runtime representation.
-}
{-# LANGUAGE Arrows #-}
{-# OPTIONS_GHC -Wno-missing-methods #-}
module PandocArrowCmd where
import Control.Arrow
import Control.Category
maybeAddAnchorFrom :: OdtReader i p
-> OdtReaderSafe i i
maybeAddAnchorFrom anchorReader =
keepingTheValue_etc_etc
>>>
proc (inlines, fAnchorElem) -> do
case fAnchorElem of
Right anchorElem -> returnA -< anchorElem
Left _ -> returnA -< inlines
-----
keepingTheValue_etc_etc :: OdtReader i (b, Either a b)
keepingTheValue_etc_etc = undefined
data OdtState
type OdtReader a b = ArrowState OdtState a b
type OdtReaderSafe a b = ArrowState OdtState a (Either () b)
newtype ArrowState state a b = ArrowState
{ runArrowState :: (state, a) -> (state, b) }
instance Category (ArrowState s) where {}
instance Arrow (ArrowState s) where {}
instance ArrowChoice (ArrowState s) where {}