Skip to content

Commit

Permalink
Derive some additional Generic instances (cabal-install)
Browse files Browse the repository at this point in the history
This is preparatory work for implementing haskell#3169
it's kept in a different commit in order to facilitate
comparing code-generation.
  • Loading branch information
hvr committed Feb 28, 2016
1 parent dd5fe69 commit 9b38b38
Show file tree
Hide file tree
Showing 5 changed files with 25 additions and 15 deletions.
4 changes: 3 additions & 1 deletion cabal-install/Distribution/Client/Config.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}

-----------------------------------------------------------------------------
-- |
Expand Down Expand Up @@ -140,6 +141,7 @@ import Data.Function
( on )
import Data.List
( nubBy )
import GHC.Generics ( Generic )

--
-- * Configuration saved in the config file
Expand All @@ -155,7 +157,7 @@ data SavedConfig = SavedConfig {
savedUploadFlags :: UploadFlags,
savedReportFlags :: ReportFlags,
savedHaddockFlags :: HaddockFlags
}
} deriving Generic

instance Monoid SavedConfig where
mempty = SavedConfig {
Expand Down
4 changes: 3 additions & 1 deletion cabal-install/Distribution/Client/GlobalFlags.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand Down Expand Up @@ -44,6 +45,7 @@ import qualified Data.Map as Map
import Data.Monoid
( Monoid(..) )
#endif
import GHC.Generics ( Generic )

import qualified Hackage.Security.Client as Sec
import qualified Hackage.Security.Util.Path as Sec
Expand Down Expand Up @@ -73,7 +75,7 @@ data GlobalFlags = GlobalFlags {
globalIgnoreSandbox :: Flag Bool,
globalIgnoreExpiry :: Flag Bool, -- ^ Ignore security expiry dates
globalHttpTransport :: Flag String
}
} deriving Generic

defaultGlobalFlags :: GlobalFlags
defaultGlobalFlags = GlobalFlags {
Expand Down
5 changes: 4 additions & 1 deletion cabal-install/Distribution/Client/Init/Types.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}

-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Client.Init.Types
Expand Down Expand Up @@ -32,6 +34,7 @@ import Distribution.Text
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (Monoid(..))
#endif
import GHC.Generics (Generic)

-- | InitFlags is really just a simple type to represent certain
-- portions of a .cabal file. Rather than have a flag for EVERY
Expand Down Expand Up @@ -72,7 +75,7 @@ data InitFlags =
, initVerbosity :: Flag Verbosity
, overwrite :: Flag Bool
}
deriving (Show)
deriving (Show, Generic)

-- the Monoid instance for Flag has later values override earlier
-- ones, which is why we want Maybe [foo] for collecting foo values,
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}

-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Client.Sandbox.PackageEnvironment
Expand Down Expand Up @@ -76,6 +78,7 @@ import qualified Text.PrettyPrint as Disp
import qualified Distribution.Compat.ReadP as Parse
import qualified Distribution.ParseUtils as ParseUtils ( Field(..) )
import qualified Distribution.Text as Text
import GHC.Generics ( Generic )


--
Expand All @@ -89,7 +92,7 @@ data PackageEnvironment = PackageEnvironment {
-- for constructing nested sandboxes (see discussion in #1196).
pkgEnvInherit :: Flag FilePath,
pkgEnvSavedConfig :: SavedConfig
}
} deriving Generic

instance Monoid PackageEnvironment where
mempty = PackageEnvironment {
Expand Down
22 changes: 11 additions & 11 deletions cabal-install/Distribution/Client/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -503,7 +503,7 @@ data SkipAddSourceDepsCheck =

data BuildExFlags = BuildExFlags {
buildOnly :: Flag SkipAddSourceDepsCheck
}
} deriving Generic

buildExOptions :: ShowOrParseArgs -> [OptionField BuildExFlags]
buildExOptions _showOrParseArgs =
Expand Down Expand Up @@ -894,7 +894,7 @@ data ReportFlags = ReportFlags {
reportUsername :: Flag Username,
reportPassword :: Flag Password,
reportVerbosity :: Flag Verbosity
}
} deriving Generic

defaultReportFlags :: ReportFlags
defaultReportFlags = ReportFlags {
Expand Down Expand Up @@ -954,7 +954,7 @@ data GetFlags = GetFlags {
getPristine :: Flag Bool,
getSourceRepository :: Flag (Maybe RepoKind),
getVerbosity :: Flag Verbosity
}
} deriving Generic

defaultGetFlags :: GetFlags
defaultGetFlags = GetFlags {
Expand Down Expand Up @@ -1039,7 +1039,7 @@ data ListFlags = ListFlags {
listSimpleOutput :: Flag Bool,
listVerbosity :: Flag Verbosity,
listPackageDBs :: [Maybe PackageDB]
}
} deriving Generic

defaultListFlags :: ListFlags
defaultListFlags = ListFlags {
Expand Down Expand Up @@ -1119,7 +1119,7 @@ instance Semigroup ListFlags where
data InfoFlags = InfoFlags {
infoVerbosity :: Flag Verbosity,
infoPackageDBs :: [Maybe PackageDB]
}
} deriving Generic

defaultInfoFlags :: InfoFlags
defaultInfoFlags = InfoFlags {
Expand Down Expand Up @@ -1520,7 +1520,7 @@ data UploadFlags = UploadFlags {
uploadPassword :: Flag Password,
uploadPasswordCmd :: Flag [String],
uploadVerbosity :: Flag Verbosity
}
} deriving Generic

defaultUploadFlags :: UploadFlags
defaultUploadFlags = UploadFlags {
Expand Down Expand Up @@ -1792,7 +1792,7 @@ initCommand = CommandUI {
data SDistExFlags = SDistExFlags {
sDistFormat :: Flag ArchiveFormat
}
deriving Show
deriving (Show, Generic)

data ArchiveFormat = TargzFormat | ZipFormat -- | ...
deriving (Show, Eq)
Expand Down Expand Up @@ -1843,7 +1843,7 @@ instance Semigroup SDistExFlags where

data Win32SelfUpgradeFlags = Win32SelfUpgradeFlags {
win32SelfUpgradeVerbosity :: Flag Verbosity
}
} deriving Generic

defaultWin32SelfUpgradeFlags :: Win32SelfUpgradeFlags
defaultWin32SelfUpgradeFlags = Win32SelfUpgradeFlags {
Expand Down Expand Up @@ -1883,7 +1883,7 @@ instance Semigroup Win32SelfUpgradeFlags where

data ActAsSetupFlags = ActAsSetupFlags {
actAsSetupBuildType :: Flag BuildType
}
} deriving Generic

defaultActAsSetupFlags :: ActAsSetupFlags
defaultActAsSetupFlags = ActAsSetupFlags {
Expand Down Expand Up @@ -1930,7 +1930,7 @@ data SandboxFlags = SandboxFlags {
sandboxSnapshot :: Flag Bool, -- FIXME: this should be an 'add-source'-only
-- flag.
sandboxLocation :: Flag FilePath
}
} deriving Generic

defaultSandboxLocation :: FilePath
defaultSandboxLocation = ".cabal-sandbox"
Expand Down Expand Up @@ -2058,7 +2058,7 @@ instance Semigroup SandboxFlags where

data ExecFlags = ExecFlags {
execVerbosity :: Flag Verbosity
}
} deriving Generic

defaultExecFlags :: ExecFlags
defaultExecFlags = ExecFlags {
Expand Down

0 comments on commit 9b38b38

Please sign in to comment.