Skip to content

Commit

Permalink
A few more HLints
Browse files Browse the repository at this point in the history
  • Loading branch information
nomeata committed Sep 12, 2017
1 parent 410c20f commit 57a392b
Showing 1 changed file with 21 additions and 1 deletion.
22 changes: 21 additions & 1 deletion examples/HLint.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE BangPatterns, ScopedTypeVariables, AllowAmbiguousTypes #-}
{-# LANGUAGE BangPatterns, ScopedTypeVariables, AllowAmbiguousTypes, TypeApplications #-}
{-# OPTIONS_GHC -O -fplugin GHC.Proof.Plugin #-}

-- This modules explores which rules from hlint-1.9.41 we can prove with
Expand Down Expand Up @@ -365,12 +365,32 @@ proof81 xs = unionBy (==) xs === union xs

-- warn = foldr (>>) (return ()) ==> sequence_
-- where _ = noQuickCheck
proof82 :: forall m f. (Foldable f, Monad m) => Proof
proof82 = foldr @f (>>) (return @m ()) === sequence_

-- warn = foldr (&&) True ==> and
proof83 :: forall f. Foldable f => Proof
proof83 = foldr @f (&&) True =/= and

proof83list :: [Bool] -> Proof
proof83list xs = foldr @[] (&&) True xs =/= and xs
-- Fun fact: This one holds up to coercions! #14223

-- warn = foldl (&&) True ==> and where note = IncreasesLaziness
proof84 :: forall f. Foldable f => Proof
proof84 = foldl @f (&&) True =/= and

-- warn = foldr1 (&&) ==> and where note = RemovesError "on []"; _ = noQuickCheck
-- warn = foldl1 (&&) ==> and where note = RemovesError "on []"
-- warn = foldr (||) False ==> or
proof85 :: forall f. Foldable f => Proof
proof85 = foldr @f (||) False =/= or

-- warn = foldl (||) False ==> or where note = IncreasesLaziness
proof86 :: forall f. Foldable f => Proof
proof86 = foldl @f (||) False =/= or


-- warn = foldr1 (||) ==> or where note = RemovesError "on []"
-- warn = foldl1 (||) ==> or where note = RemovesError "on []"
-- warn = foldl (+) 0 ==> sum
Expand Down

0 comments on commit 57a392b

Please sign in to comment.