Skip to content
Snippets Groups Projects
Commit 39d11e5b authored by Edward Z. Yang's avatar Edward Z. Yang Committed by Edward Z. Yang
Browse files

Add some missing Typeable instances.


Signed-off-by: default avatarEdward Z. Yang <ezyang@cs.stanford.edu>
parent 2b2b37c2
No related branches found
No related tags found
No related merge requests found
Showing
with 40 additions and 19 deletions
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeFamilies #-}
-----------------------------------------------------------------------------
......@@ -119,7 +120,7 @@ data InstalledPackageInfo
haddockHTMLs :: [FilePath],
pkgRoot :: Maybe FilePath
}
deriving (Eq, Generic, Read, Show)
deriving (Eq, Generic, Typeable, Read, Show)
installedComponentId :: InstalledPackageInfo -> ComponentId
installedComponentId ipi =
......
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
......@@ -97,7 +98,7 @@ data Compiler = Compiler {
compilerProperties :: Map String String
-- ^ A key-value map for properties not covered by the above fields.
}
deriving (Eq, Generic, Show, Read)
deriving (Eq, Generic, Typeable, Show, Read)
instance Binary Compiler
......
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
......@@ -90,6 +91,7 @@ data ProgramDb = ProgramDb {
progSearchPath :: ProgramSearchPath,
configuredProgs :: ConfiguredProgs
}
deriving (Typeable)
type UnconfiguredProgram = (Program, Maybe FilePath, [ProgArg])
type UnconfiguredProgs = Map.Map String UnconfiguredProgram
......
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
......@@ -122,7 +123,7 @@ data ConfiguredProgram = ConfiguredProgram {
--
programMonitorFiles :: [FilePath]
}
deriving (Eq, Generic, Read, Show)
deriving (Eq, Generic, Read, Show, Typeable)
instance Binary ConfiguredProgram
......
......@@ -25,7 +25,7 @@ data ComponentName = CLibName
| CExeName UnqualComponentName
| CTestName UnqualComponentName
| CBenchName UnqualComponentName
deriving (Eq, Generic, Ord, Read, Show)
deriving (Eq, Generic, Ord, Read, Show, Typeable)
instance Binary ComponentName
......
{-# LANGUAGE DeriveDataTypeable #-}
module Distribution.Utils.NubList
( NubList -- opaque
, toNubList -- smart construtor
......@@ -20,7 +21,7 @@ import qualified Text.Read as R
-- | NubList : A de-duplicated list that maintains the original order.
newtype NubList a =
NubList { fromNubList :: [a] }
deriving Eq
deriving (Eq, Typeable)
-- NubList assumes that nub retains the list order while removing duplicate
-- elements (keeping the first occurence). Documentation for "Data.List.nub"
......
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
......@@ -100,6 +101,7 @@ import qualified Distribution.Compat.Graph as Graph
import Distribution.Compat.Graph (Graph, IsNode(..))
import Distribution.Compat.Binary (Binary(..))
import GHC.Generics
import Data.Typeable
import Control.Monad
import Control.Exception
( assert )
......@@ -216,6 +218,7 @@ data GenericInstallPlan ipkg srcpkg = GenericInstallPlan {
planGraph :: !(Graph (GenericPlanPackage ipkg srcpkg)),
planIndepGoals :: !IndependentGoals
}
deriving (Typeable)
-- | 'GenericInstallPlan' specialised to most commonly used types.
type InstallPlan = GenericInstallPlan
......
{-# LANGUAGE RecordWildCards, NamedFieldPuns, GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveDataTypeable #-}
-- | Functions to calculate nix-style hashes for package ids.
--
......@@ -57,6 +58,7 @@ import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.Set (Set)
import Data.Typeable
import Data.Maybe (catMaybes)
import Data.List (sortBy, intercalate)
import Data.Map (Map)
......@@ -280,7 +282,7 @@ renderPackageHashInputs PackageHashInputs{
-- package ids.
newtype HashValue = HashValue BS.ByteString
deriving (Eq, Show)
deriving (Eq, Show, Typeable)
instance Binary HashValue where
put (HashValue digest) = put digest
......
......@@ -61,6 +61,7 @@ import Data.Set (Set)
import Distribution.Compat.Binary (Binary)
import Distribution.Compat.Semigroup
import GHC.Generics (Generic)
import Data.Typeable
-------------------------------
......@@ -116,7 +117,7 @@ data ProjectConfig
projectConfigLocalPackages :: PackageConfig,
projectConfigSpecificPackage :: MapMappend PackageName PackageConfig
}
deriving (Eq, Show, Generic)
deriving (Eq, Show, Generic, Typeable)
-- | That part of the project configuration that only affects /how/ we build
-- and not the /value/ of the things we build. This means this information
......@@ -269,7 +270,7 @@ instance Binary PackageConfig
-- | Newtype wrapper for 'Map' that provides a 'Monoid' instance that takes
-- the last value rather than the first value for overlapping keys.
newtype MapLast k v = MapLast { getMapLast :: Map k v }
deriving (Eq, Show, Functor, Generic, Binary)
deriving (Eq, Show, Functor, Generic, Binary, Typeable)
instance Ord k => Monoid (MapLast k v) where
mempty = MapLast Map.empty
......@@ -283,7 +284,7 @@ instance Ord k => Semigroup (MapLast k v) where
-- | Newtype wrapper for 'Map' that provides a 'Monoid' instance that
-- 'mappend's values of overlapping keys rather than taking the first.
newtype MapMappend k v = MapMappend { getMapMappend :: Map k v }
deriving (Eq, Show, Functor, Generic, Binary)
deriving (Eq, Show, Functor, Generic, Binary, Typeable)
instance (Semigroup v, Ord k) => Monoid (MapMappend k v) where
mempty = MapMappend Map.empty
......@@ -363,7 +364,7 @@ data SolverSettings
--solverSettingOverrideReinstall :: Bool,
--solverSettingUpgradeDeps :: Bool
}
deriving (Eq, Show, Generic)
deriving (Eq, Show, Generic, Typeable)
instance Binary SolverSettings
......
......@@ -81,6 +81,7 @@ import qualified Data.ByteString.Lazy as LBS
import Distribution.Compat.Binary
import GHC.Generics (Generic)
import qualified Data.Monoid as Mon
import Data.Typeable
......@@ -112,7 +113,7 @@ data ElaboratedSharedConfig
-- used.
pkgConfigCompilerProgs :: ProgramDb
}
deriving (Show, Generic)
deriving (Show, Generic, Typeable)
--TODO: [code cleanup] no Eq instance
instance Binary ElaboratedSharedConfig
......@@ -264,7 +265,7 @@ data ElaboratedConfiguredPackage
-- | Component/package specific information
elabPkgOrComp :: ElaboratedPackageOrComponent
}
deriving (Eq, Show, Generic)
deriving (Eq, Show, Generic, Typeable)
instance Package ElaboratedConfiguredPackage where
packageId = elabPkgSourceId
......@@ -571,7 +572,7 @@ data SetupScriptStyle = SetupCustomExplicitDeps
| SetupCustomImplicitDeps
| SetupNonCustomExternalLib
| SetupNonCustomInternalLib
deriving (Eq, Show, Generic)
deriving (Eq, Show, Generic, Typeable)
instance Binary SetupScriptStyle
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeFamilies #-}
-----------------------------------------------------------------------------
-- |
......@@ -77,6 +78,7 @@ import qualified Distribution.Compat.Graph as Graph
import qualified Data.Map as Map
import Data.Map (Map)
import Data.Array ((!))
import Data.Typeable
type SolverPlanPackage = ResolverPackage UnresolvedPkgLoc
......@@ -86,6 +88,7 @@ data SolverInstallPlan = SolverInstallPlan {
planIndex :: !SolverPlanIndex,
planIndepGoals :: !IndependentGoals
}
deriving (Typeable)
{-
-- | Much like 'planPkgIdOf', but mapping back to full packages.
......
......@@ -211,7 +211,7 @@ data PackageLocation local =
--TODO:
-- * add support for darcs and other SCM style remote repos with a local cache
-- | ScmPackage
deriving (Show, Functor, Eq, Ord, Generic)
deriving (Show, Functor, Eq, Ord, Generic, Typeable)
instance Binary local => Binary (PackageLocation local)
......@@ -332,9 +332,9 @@ data BuildResult = BuildResult DocsResult TestsResult
deriving (Show, Generic)
data DocsResult = DocsNotTried | DocsFailed | DocsOk
deriving (Show, Generic)
deriving (Show, Generic, Typeable)
data TestsResult = TestsNotTried | TestsOk
deriving (Show, Generic)
deriving (Show, Generic, Typeable)
instance Binary BuildFailure
instance Binary BuildResult
......
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Distribution.Solver.Types.OptionalStanza
( OptionalStanza(..)
, enableStanzas
) where
import GHC.Generics (Generic)
import Data.Typeable
import Distribution.Compat.Binary (Binary(..))
import Distribution.Types.ComponentRequestedSpec
(ComponentRequestedSpec(..), defaultComponentRequestedSpec)
......@@ -13,7 +15,7 @@ import Data.List (foldl')
data OptionalStanza
= TestStanzas
| BenchStanzas
deriving (Eq, Ord, Enum, Bounded, Show, Generic)
deriving (Eq, Ord, Enum, Bounded, Show, Generic, Typeable)
-- | Convert a list of 'OptionalStanza' into the corresponding
-- 'ComponentRequestedSpec' which records what components are enabled.
......
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Solver.Types.PkgConfigDb
......@@ -52,7 +53,7 @@ data PkgConfigDb = PkgConfigDb (M.Map PkgconfigName (Maybe Version))
-- number failed).
| NoPkgConfigDb
-- ^ For when we could not run pkg-config successfully.
deriving (Show, Generic)
deriving (Show, Generic, Typeable)
instance Binary PkgConfigDb
......
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Distribution.Solver.Types.SourcePackage
( PackageDescriptionOverride
, SourcePackage(..)
......@@ -12,6 +13,7 @@ import Distribution.PackageDescription
import Data.ByteString.Lazy (ByteString)
import GHC.Generics (Generic)
import Distribution.Compat.Binary (Binary(..))
import Data.Typeable
-- | A package description along with the location of the package sources.
--
......@@ -21,7 +23,7 @@ data SourcePackage loc = SourcePackage {
packageSource :: loc,
packageDescrOverride :: PackageDescriptionOverride
}
deriving (Eq, Show, Generic)
deriving (Eq, Show, Generic, Typeable)
instance (Binary loc) => Binary (SourcePackage loc)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment