[Haskell-cafe] Enable -Wall by default?

MarLinn monkleyon at gmail.com
Fri Dec 11 00:44:23 UTC 2020


While I do get many of the points mentioned in this thread, I don't see 
a reason to change a default.

Because

     A) you can set your own default with magic .ghci files, and

     B) there's so much more to a well-set-up development $HOME than 
just a -Wall and a big (editor) window.

In fact quite a few of the different problems mentioned in this thread 
can be solved with a bit of tinkering.
Here is my setup as an example:

My main companion .ghci file lives with me in my $HOME. When I take it 
for walkies it runs a few others (~/.ghc/macros) to set prompts and 
default editor, to import lambdabot and hoogle, and to setup a few other 
niceties, but it also contains these two key lines:

	:set -Wall -fdefer-typed-holes -fwarn-tabs -fwarn-incomplete-uni-patterns -fwarn-incomplete-record-updates -fwarn-identities -fwarn-hi-shadowing -Wredundant-constraints
	:seti -XTemplateHaskell -XQuasiQuotes -XUnicodeSyntax -XTupleSections

There's that -Wall. I have forgotten what half of the others mean, but 
they sort of accumulated over time.

Now you might say those are too many warnings. Yes. I want all of these 
warnings when I'm finalizing a module, but not while I'm still working 
on a new one.
And what's with those extensions?

Well, I also have a default set of language extensions I almost always 
want, both in ghci and my files. And I was tired of re-typing the same 
old imports, too. So I made several templates. A tiny bit of Haskell 
scripting magic turns them into a fresh new module whenever I want to 
start a new one.

Here's one of those templates:

------------------------------------------------------------------------

	#! /usr/bin/env runghc
	{-# OPTIONS_GHC -fno-warn-unused-imports #-}
	{-# LANGUAGE
	    UnicodeSyntax
	  , OverloadedStrings
	  , TupleSections
	  , RecordWildCards
	  , MultiWayIf
	  , LambdaCase
	  #-}
	
	module §name§
	  where
	
	import           Control.Applicative
	import           Control.Arrow
	import           Control.Monad
	import           Data.Monoid
	import           Data.Either
	import           Data.Function
	import           Data.List
	import           Data.Maybe
	import           Data.Foldable
	import           Data.Traversable
	import           Data.Map.Strict         ( Map )
	import qualified Data.Map.Strict  as Map
	import           Data.Set                ( Set )
	import qualified Data.Set         as Set

------------------------------------------------------------------------

In fact when I say "Haskell scripting magic", I mean "Haskell scripting 
magic that's got its own ghci command, defined in the .ghci file".

So when I want a new module, I simply say

	:create Example
	:l Example.hs
	:e

And off I go.

When I'm done with the module I remove that one -fno-warn and start 
cleaning up.
I said those where /too/ many warnings for me, not /way/ too many 
warnings, right?

Is this a set of warnings or extension everyone wants? Absolutely not. 
Is it time to prune this to adapt to changed GHC defaults? Probably. 
Should I rework this some day to use an actual templating library like 
ginger instead of my own quickly-cobbled-together mess? Maybe. And it 
should probably also adapt to the project structure by looking into 
.cabal files. But for now, it works great for my use cases and coding style.

Don't get me wrong, changing the default might still be a good idea. But 
I also don't see a reason to be bothered by it.

Cheers.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20201211/52bed187/attachment.html>


More information about the Haskell-Cafe mailing list