See #207.
@set ghcArgs=--make ^\r
-Wall ^\r
-fno-warn-name-shadowing ^\r
+ -XRecordWildCards ^\r
src/Main.hs ^\r
-isrc ^\r
-rtsopts ^\r
"$root/src/Main.hs" \
-Wall \
-fno-warn-name-shadowing \
+ -XRecordWildCards \
-i"$root/src" \
-rtsopts \
-with-rtsopts=-I0 \
, Way
default-language: Haskell2010
+ default-extensions: RecordWildCards
other-extensions: DeriveDataTypeable
, DeriveGeneric
, FlexibleInstances
, GeneralizedNewtypeDeriving
, LambdaCase
, OverloadedStrings
- , RecordWildCards
, ScopedTypeVariables
build-depends: base >= 4.8 && < 5
, ansi-terminal == 0.6.*
-{-# LANGUAGE RecordWildCards #-}
module Rules.Actions (
build, buildWithResources, copyFile, createDirectory, removeDirectory,
copyDirectory, moveDirectory, applyPatch, fixFile, runConfigure, runMake,
-{-# LANGUAGE RecordWildCards #-}
module Rules.Compile (compilePackage) where
import Base
-{-# LANGUAGE RecordWildCards #-}
module Rules.Data (buildPackageData) where
import qualified System.Directory as IO
-{-# LANGUAGE RecordWildCards #-}
module Rules.Dependencies (buildPackageDependencies) where
import Development.Shake.Util (parseMakefile)
-{-# LANGUAGE RecordWildCards #-}
module Rules.Documentation (buildPackageDocumentation) where
import Base
-{-# LANGUAGE RecordWildCards #-}
module Rules.Library (
buildPackageLibrary, buildPackageGhciLibrary, cSources, hSources
) where
-{-# LANGUAGE RecordWildCards #-}
module Rules.Program (buildProgram) where
import Data.Char
-{-# LANGUAGE RecordWildCards #-}
module Rules.Register (registerPackage) where
import Base