Messages from WARNING and DEPRECATED pragmas [GHC-63394]
Libraries may attach warning messages to functions and other entities they
export to appear when they are used. Common use cases include deprecated
functions and partial functions (such as head
and tail
).
Those messages are declared using the pragmas {-# WARNING ... #-}
and
{-# DEPRECATED ... #-}
.
For more information, see the GHC user’s guide.
{-# WARNING in "x-partial" head "This function is partial..." #-}
head :: [a] -> a
Examples
`head` is a partial function
Error Message
before/PartialHead.hs:6:3: warning: [GHC-63394] [-Wx-partial]
In the use of ‘head’
(imported from Prelude, but defined in GHC.List):
"This is a partial function, it throws an error on empty lists. Use pattern matching or Data.List.uncons instead. Consider refactoring to use Data.List.NonEmpty."
|
6 | head list
| ^^^^
PartialHead.hs
Before
module PartialHead where
example :: Int
example =
let list = 1 : 2 : 3 : [] in
head list
After
module PartialHead where
import Data.List.NonEmpty (NonEmpty((:|)))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Maybe (listToMaybe)
-- Use pattern-matching, handling the empty case explicitly.
example1 :: Int
example1 =
let list = 1 : 2 : 3 : [] in
case list of
[] -> 0
hd : _ -> hd
-- Use listToMaybe.
example2 :: Maybe Int
example2 =
let list = 1 : 2 : 3 : [] in
listToMaybe list
-- Refactor to use NonEmpty.head.
example3 :: Int
example3 =
let list :: NonEmpty Int
list = 1 :| 2 : 3 : [] in
NonEmpty.head list
`tail` is a partial function
Error Message
PartialTail.hs:6:3: warning: [GHC-63394] [-Wx-partial]
In the use of ‘tail’
(imported from Prelude, but defined in GHC.List):
"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."
|
6 | tail list
| ^^^^
PartialTail.hs
Before
module PartialTail where
example :: [Int]
example =
let list = 1 : 2 : 3 : [] in
tail list
After
module PartialTail where
import Data.List.NonEmpty (NonEmpty((:|)))
import qualified Data.List.NonEmpty as NonEmpty
-- Replace `tail` with `drop 1`.
example1 :: [Int]
example1 =
let list = 1 : 2 : 3 : [] in
drop 1 list
-- Use pattern-matching.
example2 :: [Int]
example2 =
let list = 1 : 2 : 3 : [] in
case list of
[] -> []
_ : xs -> xs
-- Refactor to use NonEmpty.tail.
example3 :: [Int]
example3 =
let list :: NonEmpty Int
list = 1 :| 2 : 3 : [] in
NonEmpty.tail list