Bodigrim pushed to branch wip/warning-for-last-and-init at Glasgow Haskell Compiler / GHC

Commits:

25 changed files:

Changes:

  • compiler/GHC/Core/Utils.hs
    ... ... @@ -115,7 +115,6 @@ import GHC.Utils.Misc
    115 115
     import Data.ByteString     ( ByteString )
    
    116 116
     import Data.Function       ( on )
    
    117 117
     import Data.List           ( sort, sortBy, partition, zipWith4, mapAccumL )
    
    118
    -import qualified Data.List as Partial ( init, last )
    
    119 118
     import Data.Ord            ( comparing )
    
    120 119
     import Control.Monad       ( guard )
    
    121 120
     import qualified Data.Set as Set
    
    ... ... @@ -1896,10 +1895,10 @@ app_ok fun_ok primop_ok fun args
    1896 1895
     
    
    1897 1896
           PrimOpId op _
    
    1898 1897
             | primOpIsDiv op
    
    1899
    -        , Lit divisor <- Partial.last args
    
    1898
    +        , Lit divisor <- last args
    
    1900 1899
                 -- there can be 2 args (most div primops) or 3 args
    
    1901 1900
                 -- (WordQuotRem2Op), hence the use of last/init
    
    1902
    -        -> not (isZeroLit divisor) && all (expr_ok fun_ok primop_ok) (Partial.init args)
    
    1901
    +        -> not (isZeroLit divisor) && all (expr_ok fun_ok primop_ok) (init args)
    
    1903 1902
                   -- Special case for dividing operations that fail
    
    1904 1903
                   -- In general they are NOT ok-for-speculation
    
    1905 1904
                   -- (which primop_ok will catch), but they ARE OK
    

  • compiler/GHC/Driver/Session/Units.hs
    ... ... @@ -39,7 +39,7 @@ import System.FilePath
    39 39
     import Control.Monad
    
    40 40
     import Data.List ( partition, (\\) )
    
    41 41
     import qualified Data.Set as Set
    
    42
    -import Prelude
    
    42
    +import GHC.Prelude
    
    43 43
     import GHC.ResponseFile (expandResponse)
    
    44 44
     import Data.Bifunctor
    
    45 45
     import GHC.Data.Graph.Directed
    

  • compiler/GHC/Prelude/Basic.hs
    ... ... @@ -2,8 +2,8 @@
    2 2
     {-# OPTIONS_HADDOCK not-home #-}
    
    3 3
     {-# OPTIONS_GHC -O2 #-} -- See Note [-O2 Prelude]
    
    4 4
     
    
    5
    --- See Note [Proxies for head and tail]
    
    6
    -{-# OPTIONS_GHC -Wno-unrecognised-warning-flags -Wno-x-partial #-}
    
    5
    +-- See Note [Proxies for partial list functions]
    
    6
    +{-# OPTIONS_GHC -Wno-x-partial #-}
    
    7 7
     
    
    8 8
     -- | Custom minimal GHC "Prelude"
    
    9 9
     --
    
    ... ... @@ -24,7 +24,7 @@ module GHC.Prelude.Basic
    24 24
       , bit
    
    25 25
       , shiftL, shiftR
    
    26 26
       , setBit, clearBit
    
    27
    -  , head, tail, unzip
    
    27
    +  , head, tail, init, last, unzip
    
    28 28
     
    
    29 29
       , strictGenericLength
    
    30 30
       ) where
    
    ... ... @@ -59,7 +59,7 @@ NoImplicitPrelude. There are two motivations for this:
    59 59
     -}
    
    60 60
     
    
    61 61
     import qualified Prelude
    
    62
    -import Prelude as X hiding ((<>), Applicative(..), Foldable(..), head, tail, unzip)
    
    62
    +import Prelude as X hiding ((<>), Applicative(..), Foldable(..), head, tail, init, last, unzip)
    
    63 63
     import Control.Applicative (Applicative(..))
    
    64 64
     import Data.Foldable as X (Foldable (elem, foldMap, foldl, foldl', foldr, length, null, product, sum))
    
    65 65
     import Data.Foldable1 as X hiding (head, last)
    
    ... ... @@ -118,24 +118,35 @@ setBit = \ x i -> x Bits..|. bit i
    118 118
     clearBit :: (Num a, Bits.Bits a) => a -> Int -> a
    
    119 119
     clearBit = \ x i -> x Bits..&. Bits.complement (bit i)
    
    120 120
     
    
    121
    -{- Note [Proxies for head and tail]
    
    121
    +{- Note [Proxies for partial list functions]
    
    122 122
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    123
    -Prelude.head and Prelude.tail have recently acquired {-# WARNING in "x-partial" #-},
    
    123
    +Prelude.head, Prelude.tail, Prelude.init and Prelude.last
    
    124
    +have recently acquired {-# WARNING in "x-partial" #-},
    
    124 125
     but the GHC codebase uses them fairly extensively and insists on building warning-free.
    
    125 126
     Thus, instead of adding {-# OPTIONS_GHC -Wno-x-partial #-} to every module which
    
    126 127
     employs them, we define warning-less proxies and export them from GHC.Prelude.
    
    127 128
     -}
    
    128 129
     
    
    129
    --- See Note [Proxies for head and tail]
    
    130
    +-- See Note [Proxies for partial list functions]
    
    130 131
     head :: HasCallStack => [a] -> a
    
    131 132
     head = Prelude.head
    
    132 133
     {-# INLINE head #-}
    
    133 134
     
    
    134
    --- See Note [Proxies for head and tail]
    
    135
    +-- See Note [Proxies for partial list functions]
    
    135 136
     tail :: HasCallStack => [a] -> [a]
    
    136 137
     tail = Prelude.tail
    
    137 138
     {-# INLINE tail #-}
    
    138 139
     
    
    140
    +-- See Note [Proxies for partial list functions]
    
    141
    +init :: HasCallStack => [a] -> [a]
    
    142
    +init = Prelude.init
    
    143
    +{-# INLINE init #-}
    
    144
    +
    
    145
    +-- See Note [Proxies for partial list functions]
    
    146
    +last :: HasCallStack => [a] -> a
    
    147
    +last = Prelude.last
    
    148
    +{-# INLINE last #-}
    
    149
    +
    
    139 150
     {- |
    
    140 151
     The 'genericLength' function defined in base can't be specialised due to the
    
    141 152
     NOINLINE pragma.
    

  • ghc/GHCi/UI.hs
    ... ... @@ -145,7 +145,7 @@ import Data.Time.LocalTime ( getZonedTime )
    145 145
     import Data.Time.Format ( formatTime, defaultTimeLocale )
    
    146 146
     import Data.Version ( showVersion )
    
    147 147
     import qualified Data.Semigroup as S
    
    148
    -import Prelude hiding ((<>))
    
    148
    +import GHC.Prelude hiding ((<>))
    
    149 149
     
    
    150 150
     import GHC.Utils.Exception as Exception hiding (catch, mask, handle)
    
    151 151
     import Foreign hiding (void)
    

  • ghc/Main.hs
    ... ... @@ -2,7 +2,7 @@
    2 2
     {-# LANGUAGE LambdaCase #-}
    
    3 3
     {-# LANGUAGE NondecreasingIndentation #-}
    
    4 4
     {-# LANGUAGE TupleSections #-}
    
    5
    -{-# OPTIONS -fno-warn-incomplete-patterns -optc-DNON_POSIX_SOURCE #-}
    
    5
    +{-# OPTIONS_GHC -Wno-x-partial -Wno-incomplete-patterns -optc-DNON_POSIX_SOURCE #-}
    
    6 6
     
    
    7 7
     -----------------------------------------------------------------------------
    
    8 8
     --
    

  • hadrian/src/Settings/Warnings.hs
    ... ... @@ -72,7 +72,11 @@ ghcWarningsArgs = do
    72 72
             , package terminfo     ? pure [ "-Wno-unused-imports", "-Wno-deriving-typeable" ]
    
    73 73
             , package stm          ? pure [ "-Wno-deriving-typeable" ]
    
    74 74
             , package osString     ? pure [ "-Wno-deriving-typeable", "-Wno-unused-imports" ]
    
    75
    -        , package parsec       ? pure [ "-Wno-deriving-typeable" ]
    
    75
    +        , package parsec       ? pure [ "-Wno-deriving-typeable"
    
    76
    +                                      , "-Wno-x-partial"
    
    77
    +                                      ]
    
    78
    +
    
    79
    +        , package filepath     ? pure [ "-Wno-x-partial" ]
    
    76 80
     
    
    77 81
             , package cabal        ? pure [ "-Wno-deriving-typeable", "-Wno-incomplete-record-selectors" ]
    
    78 82
                  -- The -Wno-incomplete-record-selectors is due to
    

  • libraries/base/changelog.md
    1 1
     # Changelog for [`base` package](http://hackage.haskell.org/package/base)
    
    2 2
     
    
    3 3
     ## 4.23.0.0 *TBA*
    
    4
    +  * Add `{-# WARNING in "x-partial" #-}` to `Data.List.{init,last}`.
    
    5
    +    Use `{-# OPTIONS_GHC -Wno-x-partial #-}` to disable it.
    
    6
    +    ([CLC proposal #87](https://github.com/haskell/core-libraries-committee/issues/292))
    
    4 7
       * Remove deprecated, unstable heap representation details from `GHC.Exts` ([CLC proposal #212](https://github.com/haskell/core-libraries-committee/issues/212))
    
    5 8
       * Add `Data.List.NonEmpty.mapMaybe`. ([CLC proposal #337](https://github.com/haskell/core-libraries-committee/issues/337))
    
    6 9
       * Fix issues with toRational for types capable to represent infinite and not-a-number values ([CLC proposal #338](https://github.com/haskell/core-libraries-committee/issues/338))
    

  • libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
    1 1
     {-# LANGUAGE Trustworthy #-}
    
    2 2
     {-# LANGUAGE LambdaCase #-}
    
    3
    +{-# OPTIONS_GHC -Wno-x-partial #-}
    
    3 4
     -- | contains a prettyprinter for the
    
    4 5
     -- Template Haskell datatypes
    
    5 6
     
    

  • libraries/ghc-internal/src/GHC/Internal/Float.hs
    ... ... @@ -13,6 +13,9 @@
    13 13
     {-# OPTIONS_HADDOCK not-home #-}
    
    14 14
     {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
    
    15 15
     
    
    16
    +-- For init in formatRealFloatAlt
    
    17
    +{-# OPTIONS_GHC -Wno-x-partial #-}
    
    18
    +
    
    16 19
     -----------------------------------------------------------------------------
    
    17 20
     -- |
    
    18 21
     -- Module      :  GHC.Internal.Float
    

  • libraries/ghc-internal/src/GHC/Internal/List.hs
    ... ... @@ -190,12 +190,18 @@ tail :: HasCallStack => [a] -> [a]
    190 190
     tail (_:xs)             =  xs
    
    191 191
     tail []                 =  errorEmptyList "tail"
    
    192 192
     
    
    193
    -{-# WARNING in "x-partial" tail "This is a partial function, it throws an error on empty lists. Replace it with 'drop' 1, or use pattern matching or 'GHC.Internal.Data.List.uncons' instead. Consider refactoring to use \"Data.List.NonEmpty\"." #-}
    
    193
    +{-# WARNING in "x-partial" tail "This is a partial function, it throws an error on empty lists. Replace it with 'drop' 1, or use pattern matching or 'Data.List.uncons' instead. Consider refactoring to use \"Data.List.NonEmpty\"." #-}
    
    194 194
     
    
    195 195
     -- | \(\mathcal{O}(n)\). Extract the last element of a list, which must be
    
    196 196
     -- finite and non-empty.
    
    197 197
     --
    
    198
    --- WARNING: This function is partial. Consider using 'unsnoc' instead.
    
    198
    +-- To disable the warning about partiality put
    
    199
    +-- @{-# OPTIONS_GHC -Wno-x-partial -Wno-unrecognised-warning-flags #-}@
    
    200
    +-- at the top of the file. To disable it throughout a package put the same
    
    201
    +-- options into @ghc-options@ section of Cabal file. To disable it in GHCi
    
    202
    +-- put @:set -Wno-x-partial -Wno-unrecognised-warning-flags@ into @~/.ghci@
    
    203
    +-- config file. See also the
    
    204
    +-- [migration guide](https://github.com/haskell/core-libraries-committee/blob/main/guides/warning-for-init-and-last.md).
    
    199 205
     --
    
    200 206
     -- ==== __Examples__
    
    201 207
     --
    
    ... ... @@ -218,10 +224,18 @@ last xs = foldl (\_ x -> x) lastError xs
    218 224
     lastError :: HasCallStack => a
    
    219 225
     lastError = errorEmptyList "last"
    
    220 226
     
    
    227
    +{-# WARNING in "x-partial" last "This is a partial function, it throws an error on empty lists. Use 'Data.List.unsnoc' instead. Consider refactoring to use \"Data.List.NonEmpty\"." #-}
    
    228
    +
    
    221 229
     -- | \(\mathcal{O}(n)\). Return all the elements of a list except the last one.
    
    222 230
     -- The list must be non-empty.
    
    223 231
     --
    
    224
    --- WARNING: This function is partial. Consider using 'unsnoc' instead.
    
    232
    +-- To disable the warning about partiality put
    
    233
    +-- @{-# OPTIONS_GHC -Wno-x-partial -Wno-unrecognised-warning-flags #-}@
    
    234
    +-- at the top of the file. To disable it throughout a package put the same
    
    235
    +-- options into @ghc-options@ section of Cabal file. To disable it in GHCi
    
    236
    +-- put @:set -Wno-x-partial -Wno-unrecognised-warning-flags@ into  @~/.ghci@
    
    237
    +-- config file. See also the
    
    238
    +-- [migration guide](https://github.com/haskell/core-libraries-committee/blob/main/guides/warning-for-init-and-last.md).
    
    225 239
     --
    
    226 240
     -- ==== __Examples__
    
    227 241
     --
    
    ... ... @@ -240,6 +254,8 @@ init (x:xs) = init' x xs
    240 254
       where init' _ []     = []
    
    241 255
             init' y (z:zs) = y : init' z zs
    
    242 256
     
    
    257
    +{-# WARNING in "x-partial" init "This is a partial function, it throws an error on empty lists. Use 'Data.List.unsnoc' instead. Consider refactoring to use \"Data.List.NonEmpty\"." #-}
    
    258
    +
    
    243 259
     -- | \(\mathcal{O}(1)\). Test whether a list is empty.
    
    244 260
     --
    
    245 261
     -- >>> null []
    

  • libraries/ghc-internal/src/GHC/Internal/System/IO.hs
    1 1
     {-# LANGUAGE Trustworthy #-}
    
    2 2
     {-# LANGUAGE CPP, NoImplicitPrelude, CApiFFI #-}
    
    3
    +{-# OPTIONS_GHC -Wno-x-partial #-}
    
    3 4
     
    
    4 5
     -----------------------------------------------------------------------------
    
    5 6
     -- |
    

  • libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
    1 1
     {-# OPTIONS_HADDOCK not-home #-} -- we want users to import Language.Haskell.TH.Syntax instead
    
    2
    +{-# OPTIONS_GHC -Wno-x-partial #-}
    
    2 3
     {-# LANGUAGE CPP #-}
    
    3 4
     {-# LANGUAGE DataKinds #-}
    
    4 5
     {-# LANGUAGE DeriveGeneric #-}
    

  • libraries/template-haskell/vendored-filepath/System/FilePath/Posix.hs
    1 1
     -- Vendored from filepath v1.4.2.2
    
    2 2
     
    
    3 3
     {-# LANGUAGE PatternGuards #-}
    
    4
    +{-# OPTIONS_GHC -Wno-x-partial #-}
    
    4 5
     
    
    5 6
     -- This template expects CPP definitions for:
    
    6 7
     --     MODULE_NAME = Posix | Windows
    

  • libraries/template-haskell/vendored-filepath/System/FilePath/Windows.hs
    1 1
     -- Vendored from filepath v1.4.2.2
    
    2 2
     
    
    3 3
     {-# LANGUAGE PatternGuards #-}
    
    4
    +{-# OPTIONS_GHC -Wno-x-partial #-}
    
    4 5
     
    
    5 6
     -- This template expects CPP definitions for:
    
    6 7
     --     MODULE_NAME = Posix | Windows
    

  • testsuite/tests/driver/j-space/jspace.hs
    ... ... @@ -7,7 +7,7 @@ import System.Environment
    7 7
     import GHC.Driver.Env.Types
    
    8 8
     import GHC.Profiling
    
    9 9
     import System.Mem
    
    10
    -import Data.List (isPrefixOf)
    
    10
    +import Data.List (isPrefixOf, unsnoc)
    
    11 11
     import Control.Monad
    
    12 12
     import System.Exit
    
    13 13
     import GHC.Platform
    
    ... ... @@ -41,7 +41,9 @@ initGhcM xs = do
    41 41
           requestHeapCensus
    
    42 42
           performGC
    
    43 43
           [ys] <- filter (isPrefixOf (ghcUnitId <> ":GHC.Unit.Module.ModDetails.ModDetails")) . lines <$> readFile "jspace.hp"
    
    44
    -      let (n :: Int) = read (last (words ys))
    
    44
    +      let (n :: Int) = case unsnoc (words ys) of
    
    45
    +            Nothing -> error "input is unexpectedly empty"
    
    46
    +            Just (_, lst) -> read lst
    
    45 47
           -- The output should be 50 * 8 * word_size (i.e. 3600, or 1600 on 32-bit architectures):
    
    46 48
           -- the test contains DEPTH + WIDTH + 2 = 50 modules J, H_0, .., H_DEPTH, W_1, .., W_WIDTH,
    
    47 49
           -- and each ModDetails contains 1 (info table) + 8 word-sized fields.
    

  • testsuite/tests/rts/KeepCafsBase.hs
    1
    +{-# OPTIONS_GHC -Wno-x-partial #-}
    
    2
    +
    
    1 3
     module KeepCafsBase (x) where
    
    2 4
     
    
    3 5
     x :: Int
    

  • utils/check-exact/Main.hs
    ... ... @@ -6,6 +6,7 @@
    6 6
     {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
    
    7 7
     {-# OPTIONS_GHC -Wno-incomplete-patterns #-}
    
    8 8
     {-# OPTIONS_GHC -Wno-orphans #-}
    
    9
    +{-# OPTIONS_GHC -Wno-x-partial #-}
    
    9 10
     
    
    10 11
     import Data.Data
    
    11 12
     import Data.List (intercalate)
    

  • utils/check-exact/Transform.hs
    ... ... @@ -96,6 +96,7 @@ import GHC.Data.FastString
    96 96
     import GHC.Types.SrcLoc
    
    97 97
     
    
    98 98
     import Data.Data
    
    99
    +import Data.List (unsnoc)
    
    99 100
     import Data.List.NonEmpty (NonEmpty (..))
    
    100 101
     import qualified Data.List.NonEmpty as NE
    
    101 102
     import Data.Maybe
    
    ... ... @@ -212,8 +213,9 @@ captureTypeSigSpacing (L l (SigD x (TypeSig (AnnSig (EpUniTok dca u) mp md) ns (
    212 213
       where
    
    213 214
         -- we want DPs for the distance from the end of the ns to the
    
    214 215
         -- AnnDColon, and to the start of the ty
    
    215
    -    rd = case last ns of
    
    216
    -      L (EpAnn anc' _ _) _ -> epaLocationRealSrcSpan anc'
    
    216
    +    rd = case unsnoc ns of
    
    217
    +      Nothing -> error "unexpected empty list in 'ns' variable"
    
    218
    +      Just (_, L (EpAnn anc' _ _) _) -> epaLocationRealSrcSpan anc'
    
    217 219
         dca' = case dca of
    
    218 220
               EpaSpan ss@(RealSrcSpan r _) -> (EpaDelta ss (ss2delta (ss2posEnd rd) r) [])
    
    219 221
               _                            -> dca
    
    ... ... @@ -294,7 +296,7 @@ setEntryDP (L (EpAnn (EpaSpan ss@(RealSrcSpan r _)) an cs) a) dp
    294 296
                   where
    
    295 297
                     cs'' = setPriorComments cs []
    
    296 298
                     csd = L (EpaDelta ss dp NoComments) c:commentOrigDeltas cs'
    
    297
    -                lc = last $ (L ca c:cs')
    
    299
    +                lc = NE.last (L ca c :| cs')
    
    298 300
                     delta = case getLoc lc of
    
    299 301
                               EpaSpan (RealSrcSpan rr _) -> ss2delta (ss2pos rr) r
    
    300 302
                               EpaSpan _ -> (SameLine 0)
    

  • utils/check-exact/Utils.hs
    ... ... @@ -37,7 +37,7 @@ import GHC.Base (NonEmpty(..))
    37 37
     import GHC.Parser.Lexer (allocateComments)
    
    38 38
     
    
    39 39
     import Data.Data hiding ( Fixity )
    
    40
    -import Data.List (sortBy, partition)
    
    40
    +import Data.List (sortBy, partition, unsnoc)
    
    41 41
     import qualified Data.Map.Strict as Map
    
    42 42
     
    
    43 43
     import Debug.Trace
    
    ... ... @@ -734,8 +734,9 @@ ghead info [] = error $ "ghead "++info++" []"
    734 734
     ghead _info (h:_) = h
    
    735 735
     
    
    736 736
     glast :: String -> [a] -> a
    
    737
    -glast  info []    = error $ "glast " ++ info ++ " []"
    
    738
    -glast _info h     = last h
    
    737
    +glast info xs = case unsnoc xs of
    
    738
    +  Nothing       -> error $ "glast " ++ info ++ " []"
    
    739
    +  Just (_, lst) -> lst
    
    739 740
     
    
    740 741
     gtail :: String -> [a] -> [a]
    
    741 742
     gtail  info []    = error $ "gtail " ++ info ++ " []"
    

  • utils/ghc-pkg/Main.hs
    ... ... @@ -8,7 +8,7 @@
    8 8
     {-# LANGUAGE DataKinds #-}
    
    9 9
     {-# LANGUAGE TupleSections #-}
    
    10 10
     {-# LANGUAGE ScopedTypeVariables #-}
    
    11
    -{-# OPTIONS_GHC -fno-warn-orphans #-}
    
    11
    +{-# OPTIONS_GHC -Wno-orphans -Wno-x-partial #-}
    
    12 12
     
    
    13 13
     -- Fine if this comes from make/Hadrian or the pre-built base.
    
    14 14
     #include <ghcplatform.h>
    

  • utils/ghc-toolchain/src/GHC/Toolchain/Utils.hs
    ... ... @@ -14,6 +14,7 @@ module GHC.Toolchain.Utils
    14 14
     import Control.Exception
    
    15 15
     import Control.Monad
    
    16 16
     import Control.Monad.IO.Class
    
    17
    +import Data.List (unsnoc)
    
    17 18
     import System.Directory
    
    18 19
     import System.FilePath
    
    19 20
     import System.IO.Error
    
    ... ... @@ -67,5 +68,4 @@ isSuccess = \case
    67 68
       ExitFailure _ -> False
    
    68 69
     
    
    69 70
     lastLine :: String -> String
    
    70
    -lastLine "" = ""
    
    71
    -lastLine s  = last $ lines s
    71
    +lastLine = maybe "" snd . unsnoc . lines

  • utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
    ... ... @@ -755,7 +755,7 @@ ppHtmlIndex
    755 755
             divAlphabet
    
    756 756
               << unordList
    
    757 757
                 ( map (\str -> anchor ! [href (subIndexHtmlFile str)] << str) $
    
    758
    -                [ [c] | c <- initialChars, any ((== c) . toUpper . head . fst) index
    
    758
    +                [ [c] | c <- initialChars, any (maybe False ((== c) . toUpper . fst) . List.uncons . fst) index
    
    759 759
                     ]
    
    760 760
                       ++ [merged_name]
    
    761 761
                 )
    
    ... ... @@ -772,7 +772,7 @@ ppHtmlIndex
    772 772
               writeUtf8File (joinPath [odir, subIndexHtmlFile [c]]) (renderToString debug html)
    
    773 773
             where
    
    774 774
               html = indexPage True (Just c) index_part
    
    775
    -          index_part = [(n, stuff) | (n, stuff) <- this_ix, toUpper (head n) == c]
    
    775
    +          index_part = [(n, stuff) | (n@(headN : _), stuff) <- this_ix, toUpper headN == c]
    
    776 776
     
    
    777 777
           index :: [(String, Map GHC.Name [(Module, Bool)])]
    
    778 778
           index = sortBy cmp (Map.toAscList full_index)
    

  • utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs
    ... ... @@ -30,7 +30,7 @@ import Control.Arrow (first)
    30 30
     import Control.Monad
    
    31 31
     import Data.Char (chr, isAlpha, isSpace, isUpper)
    
    32 32
     import Data.Functor (($>))
    
    33
    -import Data.List (elemIndex, intercalate, intersperse, unfoldr)
    
    33
    +import Data.List (elemIndex, intercalate, intersperse, unfoldr, unsnoc)
    
    34 34
     import Data.Maybe (fromMaybe, mapMaybe)
    
    35 35
     import Data.Monoid
    
    36 36
     import qualified Data.Set as Set
    
    ... ... @@ -870,10 +870,10 @@ codeblock =
    870 870
       DocCodeBlock . parseParagraph . dropSpaces
    
    871 871
         <$> ("@" *> skipHorizontalSpace *> "\n" *> block' <* "@")
    
    872 872
       where
    
    873
    -    dropSpaces xs =
    
    874
    -      case splitByNl xs of
    
    875
    -        [] -> xs
    
    876
    -        ys -> case T.uncons (last ys) of
    
    873
    +    dropSpaces xs = let ys = splitByNl xs in
    
    874
    +      case unsnoc ys of
    
    875
    +        Nothing -> xs
    
    876
    +        Just (_, lastYs) -> case T.uncons lastYs of
    
    877 877
               Just (' ', _) -> case mapM dropSpace ys of
    
    878 878
                 Nothing -> xs
    
    879 879
                 Just zs -> T.intercalate "\n" zs
    

  • utils/hpc
    1
    -Subproject commit 5923da3fe77993b7afc15b5163cffcaa7da6ecf5
    1
    +Subproject commit dd43f7e139d7a4f4908d1e8af35a75939f763ef1

  • utils/hsc2hs
    1
    -Subproject commit fe3990b9f35000427b016a79330d9f195587cad8
    1
    +Subproject commit 2059c961fc28bbfd0cafdbef96d5d21f1d911b53