[Haskell-cafe] Unused Arrow commands do not give warning
Tom Ellis
tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk
Wed Nov 6 14:17:48 UTC 2013
GHC can give you a warning when you fail to use the result of a monadic
action in a do block. The same does not hold for arrow commands in arrow
notation. (See demonstration below signature).
What would it take to add a warning for this? I am writing arrow-heavy code
at the moment and I think such a warning would be a nice feature.
Tom
% cat Test.hs
{-# LANGUAGE Arrows #-}
module Test where
import Control.Arrow (returnA, arr)
import Control.Monad.Identity (Identity(..))
foo :: Identity ()
foo = do
Identity True
return ()
bar :: () -> ()
bar = proc () -> do
arr (const True) -< ()
returnA -< ()
% ghc -fforce-recomp -Wall Test.hs
[1 of 1] Compiling Test ( Test.hs, Test.o )
Test.hs:10:5:
Warning: A do-notation statement discarded a result of type Bool.
Suppress this warning by saying "_ <-
Data.Functor.Identity.Identity
GHC.Types.True",
or by using the flag -fno-warn-unused-do-bind
More information about the Haskell-Cafe
mailing list