|
| 1 | +We analyzed the head.hackage patches to understand |
| 2 | +why code breaks on new GHC releases. |
| 3 | +Surprisingly, most breakage wasnβt caused by |
| 4 | +Template Haskellβit came from deeper semantic changes in language extensions. |
| 5 | +This post walks through the main categories of breakage, |
| 6 | +why they happened, and what they tell us about long-term stability. |
| 7 | +If you care about a smoother upgrade path for Haskell users, |
| 8 | +we invite you to participate in the Stability Working Group. |
| 9 | + |
| 10 | +The [Haskell Foundation Stability Working Group](https://blog.haskell.org/stability-working-group/) |
| 11 | +is interested in understanding |
| 12 | +why breakage occurs. |
| 13 | +This is an extension of our initial [investigation](https://jappie.me/analyzing-haskell-stability.html). |
| 14 | +We've recently done further analysis on [head.hackage](https://ghc.gitlab.haskell.org/head.hackage/), |
| 15 | +and learned surprisingly enough that the root cause |
| 16 | +of a lot of breakage isn't Template Haskell, |
| 17 | +but seems to be from language extension semantics[^meaning]. |
| 18 | +We're doing this investigation to better understand where the Haskell |
| 19 | +Foundation stability working group should focus it's efforts. |
| 20 | +About a year ago I started on analyzing the causes |
| 21 | +for all `head.hackage` patches, but I got bogged down |
| 22 | +by the sheer amount of work. |
| 23 | +Trevis suggested focusing on the |
| 24 | +most important question, |
| 25 | +why do language extension semantics cause so much breakage? |
| 26 | +So instead of being bogged down by analyzing all |
| 27 | +the patches, I just looked at the 12 patches from language extension |
| 28 | +semantics. |
| 29 | + |
| 30 | +[^meaning]: The precise meaning of features enabled by language extensions. I guess parser changes also count. |
| 31 | + |
| 32 | +This gave us the following table: |
| 33 | + |
| 34 | +| Name | Cause | Had warnings? | |
| 35 | +|-------------------------------------+----------------------------------------------+---------------| |
| 36 | +| Cabal-2.4.1.0.patch | simplified subsumption | no | |
| 37 | +| Cabal-3.0.2.0.patch | simplified subsumption | no | |
| 38 | +| Cabal-3.2.1.0.patch | simplified subsumption | no | |
| 39 | +| data-r-tree-0.6.0.patch | parser change (see 1) | no | |
| 40 | +| drinkery-0.4.patch | simplified subsumption | no | |
| 41 | +| ghc-lib-parser-9.8.1.20231121.patch | rename forall identifiers (2) | yes | |
| 42 | +| hgeometry-ipe-0.13.patch | Instances moved due to splice enforcement | no | |
| 43 | +| singletons-3.0.2.patch | add TypeAbstractions as a language extension | yes | |
| 44 | +| singletons-base-3.1.1.patch | add TypeAbstractions as a language extension | yes | |
| 45 | +| vector-space-0.16.patch | * is type (4) | yes | |
| 46 | + |
| 47 | +`th-compat-0.1.4.patch` was miscounted so I left that out. |
| 48 | +Simplified subsumption appears a lot but 3 are for Cabal, |
| 49 | +so it's only 2 real occurrences. |
| 50 | +We expect that to appear a lot however, |
| 51 | +because it was one of *the* motivating changes for a [stability working group](https://blog.haskell.org/stability-working-group/). |
| 52 | + |
| 53 | +## Simplified subsumption |
| 54 | +For the blissfully ignorant reader simplified subsumption causes you |
| 55 | +to do this under certain existential conditions: |
| 56 | +```haskell |
| 57 | +--- a/Distribution/Simple/Utils.hs |
| 58 | ++++ b/Distribution/Simple/Utils.hs |
| 59 | +@@ -1338,7 +1338,7 @@ withTempFileEx opts tmpDir template action = |
| 60 | + (\(name, handle) -> do hClose handle |
| 61 | + unless (optKeepTempFiles opts) $ |
| 62 | + handleDoesNotExist () . removeFile $ name) |
| 63 | +- (withLexicalCallStack (uncurry action)) |
| 64 | ++ (withLexicalCallStack (\x -> uncurry action x)) |
| 65 | + |
| 66 | +``` |
| 67 | +You've to insert a lambda, which apparently signifies some performance impact. |
| 68 | +This went wild with [Yesod stacks](https://www.yesodweb.com/book), |
| 69 | +whose code generation helpfully created |
| 70 | +the database alias in the template: |
| 71 | +```haskell |
| 72 | +type DB a = forall (m :: Type -> Type). |
| 73 | + (MonadUnliftIO m) => ReaderT SqlBackend m a |
| 74 | +``` |
| 75 | + |
| 76 | +So anything that now uses a query has to insert those lambdas, |
| 77 | +as you can imagine this would be in quite a few places for non-trivial commercial code bases. |
| 78 | +Which caused many issues for commercial users. |
| 79 | +You can just delete those aliases to solve the problem. |
| 80 | +Alternatively you can just enable the language extension: [DeepSubsumption](https://downloads.haskell.org/~ghc/9.12.2/docs/users_guide/exts/rank_polymorphism.html#extension-DeepSubsumption). |
| 81 | +Which restores the original behavior. |
| 82 | + |
| 83 | +## Moving of instances due to Template Haskell |
| 84 | +This change forces you to put the instances above the splice where |
| 85 | +it's being used in the same module. |
| 86 | +A dear colleague decided to generate instances in Template Haskell. |
| 87 | +That was quite the puzzle! |
| 88 | +I asked the GHC devs why they did this, |
| 89 | +and it turns out this was a soundness issue in the typechecker. |
| 90 | +Here, soundness means the type system can't be tricked into allowing invalid programs. |
| 91 | +So the community is better off, despite this causing a fair bit of work. |
| 92 | + |
| 93 | +```haskell |
| 94 | +--- a/src/Ipe/Content.hs |
| 95 | ++++ b/src/Ipe/Content.hs |
| 96 | +@@ -288,6 +288,14 @@ |
| 97 | + |
| 98 | ++instance Fractional r => IsTransformable (IpeObject r) where |
| 99 | ++ transformBy t (IpeGroup i) = IpeGroup $ i&core %~ transformBy t |
| 100 | ++ ... |
| 101 | + makePrisms ''IpeObject |
| 102 | + |
| 103 | +@@ -303,14 +311,6 @@ |
| 104 | + |
| 105 | +-instance Fractional r => IsTransformable (IpeObject r) where |
| 106 | +- transformBy t (IpeGroup i) = IpeGroup $ i&core %~ transformBy t |
| 107 | +- ... |
| 108 | +``` |
| 109 | + |
| 110 | +## (1) Parser change |
| 111 | + |
| 112 | +The parser is the component of the compiler that transforms text |
| 113 | +into a memory structure the compiler can work with. |
| 114 | +This structure is called an abstract syntax tree. |
| 115 | + |
| 116 | +```haskell |
| 117 | +- Node4 {getMBB :: {-# UNPACK #-} ! MBB, getC1 :: ! (RTree a), getC2 :: ! (RTree a), getC3 :: ! (RTree a), getC4 :: ! (RTree a) } |
| 118 | +- | Node3 {getMBB :: {-# UNPACK #-} ! MBB, getC1 :: ! (RTree a), getC2 :: ! (RTree a), getC3 :: ! (RTree a) } |
| 119 | +- | Node2 {getMBB :: {-# UNPACK #-} ! MBB, getC1 :: ! (RTree a), getC2 :: ! (RTree a) } |
| 120 | ++ Node4 {getMBB :: {-# UNPACK #-} !MBB, getC1 :: !(RTree a), getC2 :: !(RTree a), getC3 :: !(RTree a), getC4 :: !(RTree a) } |
| 121 | ++ | Node3 {getMBB :: {-# UNPACK #-} !MBB, getC1 :: !(RTree a), getC2 :: !(RTree a), getC3 :: !(RTree a) } |
| 122 | ++ | Node2 {getMBB :: {-# UNPACK #-} !MBB, getC1 :: !(RTree a), getC2 :: !(RTree a) } |
| 123 | + | Node {getMBB :: MBB, getChildren' :: [RTree a] } |
| 124 | +- | Leaf {getMBB :: {-# UNPACK #-} ! MBB, getElem :: a} |
| 125 | ++ | Leaf {getMBB :: {-# UNPACK #-} !MBB, getElem :: a} |
| 126 | + | Empty |
| 127 | + |
| 128 | +``` |
| 129 | + |
| 130 | +This is a change from all the way back in 2020, where the *core* language changed by |
| 131 | +disallowing `!` before parens. |
| 132 | +Here the bang `!` indicates strict fields. |
| 133 | +Technically this doesn't fit into the category |
| 134 | +because the core language isn't a language extension. |
| 135 | +But semantics did change! |
| 136 | +Actually I don't think we expected to find something like this at all. |
| 137 | +I'm not sure how relevant this is to discuss further because it appears |
| 138 | +quite rare for someone to do this. |
| 139 | +You can enable [StrictData](https://downloads.haskell.org/ghc/latest/docs/users_guide/exts/strict.html#extension-StrictData) |
| 140 | +in your Cabal file and delete all those bangs! |
| 141 | + |
| 142 | +* (2) Rename forall identifiers |
| 143 | +This changes the forall identifier into a keyword at term level. |
| 144 | +It already was at the type level. |
| 145 | +The issue is discussed [here](https://gitlab.haskell.org/ghc/ghc/-/issues/23719) |
| 146 | + |
| 147 | +```haskell |
| 148 | + hintExplicitForall :: Located Token -> P () |
| 149 | + hintExplicitForall tok = do |
| 150 | +- forall <- getBit ExplicitForallBit |
| 151 | ++ forAll <- getBit ExplicitForallBit |
| 152 | + rulePrag <- getBit InRulePragBit |
| 153 | +- unless (forall || rulePrag) $ addError $ mkPlainErrorMsgEnvelope (getLoc tok) $ |
| 154 | ++ unless (forAll || rulePrag) $ addError $ mkPlainErrorMsgEnvelope (getLoc tok) $ |
| 155 | + (PsErrExplicitForall (isUnicode tok)) |
| 156 | +``` |
| 157 | + |
| 158 | +## TypeAbstractions |
| 159 | + |
| 160 | +From what I understand from the [manual](https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/type_abstractions.html#type-abstractions) |
| 161 | +Is that part of the syntax for type abstractions landed in GHC 9.2, |
| 162 | +however 9.8 and onwards requires you to enable this language extension. |
| 163 | +This appears to because certain new functionality was introduced behind an |
| 164 | +old language extension flag, according to [this proposal](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0448-type-variable-scoping.rst#4type-arguments-in-constructor-patterns) |
| 165 | + |
| 166 | +This extension enables you to bind type variables in pattern matches. |
| 167 | +I don't know why this happened like this, but it happened in 2023: |
| 168 | + |
| 169 | +```haskell |
| 170 | ++-- Invisible type binders in type declarations, such as |
| 171 | ++-- |
| 172 | ++-- type family Sing @k |
| 173 | ++-- |
| 174 | ++-- require the TypeAbstractions extension. |
| 175 | ++#if __GLASGOW_HASKELL__ >= 909 |
| 176 | ++{-# LANGUAGE TypeAbstractions #-} |
| 177 | ++#endif |
| 178 | ++ |
| 179 | +``` |
| 180 | + |
| 181 | +* Star is type |
| 182 | +This change was announced via a warning. |
| 183 | +It tells users to write `Type` instead of `*` for kinds representing types. |
| 184 | +A kind is essentially the type of a type, |
| 185 | +and as a concept is used for type-level programming type safety. |
| 186 | + |
| 187 | +```haskell |
| 188 | +- type Basis v :: * |
| 189 | ++ type Basis v :: Type |
| 190 | +``` |
| 191 | + |
| 192 | + |
| 193 | +* Conclusion |
| 194 | + |
| 195 | +Often we experience these breakages as annoying and frustrating. |
| 196 | +However, if we look deeper, we find that each of them has |
| 197 | +a little story |
| 198 | +and good reasons for being introduced. |
| 199 | +If you find this all as interesting as I do, |
| 200 | +please consider joining some of the stability |
| 201 | +working group meetings! |
| 202 | + |
0 commit comments