Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 1 addition & 3 deletions src/Data/IntTrie.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,8 +19,6 @@ module Data.IntTrie (

import Prelude hiding (lookup)

import Data.Typeable (Typeable)

import qualified Data.Array.Unboxed as A
import Data.Array.IArray ((!))
import qualified Data.Bits as Bits
Expand All @@ -42,7 +40,7 @@ import Control.Applicative ((<$>), (<*>))
-- | A compact mapping from sequences of small ints to small ints.
--
newtype IntTrie k v = IntTrie (A.UArray Word32 Word32)
deriving (Show, Typeable)
deriving (Show)

-- Version 0 used 16-bit integers and is no longer supported
-- (To upgrade, DELETE /server-status/tarindices to wipe the tar indices state)
Expand Down
3 changes: 1 addition & 2 deletions src/Data/StringTable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@ import qualified Data.List as List
import qualified Data.Array.Unboxed as A
import Data.Array.Unboxed ((!))
import Data.SafeCopy (base, deriveSafeCopy)
import Data.Typeable (Typeable)
import qualified Data.ByteString.Char8 as BS
import Data.Word (Word32)

Expand All @@ -29,7 +28,7 @@ data StringTable id
= StringTable
!BS.ByteString -- all the strings concatenated
!(A.UArray Int Word32) -- offset table
deriving (Show, Typeable)
deriving (Show)

$(deriveSafeCopy 0 'base ''StringTable)

Expand Down
7 changes: 3 additions & 4 deletions src/Data/TarIndex.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@ module Data.TarIndex (
) where

import Data.SafeCopy (base, deriveSafeCopy)
import Data.Typeable (Typeable)

import Codec.Archive.Tar (Entry, GenEntry(..), GenEntryContent(..), Entries, GenEntries(..), entryPath)
import qualified Data.StringTable as StringTable
Expand Down Expand Up @@ -56,16 +55,16 @@ data TarIndex = TarIndex

!(StringTable PathComponentId) -- ^ The mapping of filepath components as strings to ids.
!(IntTrie PathComponentId TarEntryOffset) -- ^ Mapping of sequences of filepath component ids to tar entry offsets.
deriving (Show, Typeable)
deriving (Show)


data TarIndexEntry = TarFileEntry !TarEntryOffset
| TarDir [(FilePath, TarIndexEntry)]
deriving (Show, Typeable)
deriving (Show)


newtype PathComponentId = PathComponentId Int
deriving (Eq, Ord, Enum, Show, Typeable)
deriving (Eq, Ord, Enum, Show)

type TarEntryOffset = Int

Expand Down
5 changes: 2 additions & 3 deletions src/Distribution/Client/Cron.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,21 +13,20 @@ import System.Random (randomRIO)
import Data.Time.Format (defaultTimeLocale, formatTime)
import Data.Time.Clock (UTCTime, getCurrentTime, addUTCTime)
import Data.Time.LocalTime (getCurrentTimeZone, utcToZonedTime)
import Data.Typeable (Typeable)

import qualified System.Posix.Signals as Posix

import Distribution.Verbosity (Verbosity)
import Distribution.Simple.Utils hiding (warn)

data ReceivedSignal = ReceivedSignal Signal UTCTime
deriving (Show, Typeable)
deriving (Show)

data Signal = SIGABRT
| SIGINT
| SIGQUIT
| SIGTERM
deriving (Show, Typeable)
deriving (Show)

instance Exception ReceivedSignal

Expand Down
2 changes: 1 addition & 1 deletion src/Distribution/Client/Mirror/Session.hs
Original file line number Diff line number Diff line change
Expand Up @@ -237,7 +237,7 @@ data MirrorError = MirrorIOError IOError
| PutPackageError PackageId ErrorResponse
| Interrupted
| InvalidOption String
deriving (Typeable,Show)
deriving (Show)

instance Exception MirrorError

Expand Down
3 changes: 1 addition & 2 deletions src/Distribution/Server/Features/AdminLog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,6 @@ import Distribution.Server.Pages.AdminLog
import Distribution.Server.Features.Users

import Data.SafeCopy (base, deriveSafeCopy)
import Data.Typeable
import Data.Maybe(mapMaybe)
import Control.Monad.Reader
import qualified Control.Monad.State as State
Expand Down Expand Up @@ -50,7 +49,7 @@ mkAdminAction gd isAdd uid = (if isAdd then Admin_GroupAddUser else Admin_GroupD

newtype AdminLog = AdminLog {
adminLog :: [(UTCTime,UserId,AdminAction,BS.ByteString)]
} deriving (Typeable, Show, MemSize)
} deriving (Show, MemSize)

deriveSafeCopy 0 'base ''AdminLog

Expand Down
5 changes: 2 additions & 3 deletions src/Distribution/Server/Features/AnalyticsPixels/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@ import Distribution.Server.Framework.MemSize (MemSize)
import Distribution.Server.Users.State ()

import Data.Text (Text)
import Data.Typeable (Typeable)
import Data.Map (Map)
import qualified Data.Map.Strict as Map
import Data.Acid (Query, Update, makeAcidic)
Expand All @@ -36,13 +35,13 @@ newtype AnalyticsPixel = AnalyticsPixel
{
analyticsPixelUrl :: Text
}
deriving (Show, Eq, Ord, NFData, Typeable, MemSize)
deriving (Show, Eq, Ord, NFData, MemSize)

newtype AnalyticsPixelsState = AnalyticsPixelsState
{
analyticsPixels :: Map PackageName (Set AnalyticsPixel)
}
deriving (Show, Eq, NFData, Typeable, MemSize)
deriving (Show, Eq, NFData, MemSize)

-- SafeCopy instances
$(deriveSafeCopy 0 'base ''AnalyticsPixel)
Expand Down
10 changes: 4 additions & 6 deletions src/Distribution/Server/Features/BuildReports/BuildReport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -106,8 +106,6 @@ import qualified Data.ByteString.Char8 as BS
import qualified Data.Map as Map
import Data.Time
( UTCTime, getCurrentTime )
import Data.Typeable
( Typeable )
import Control.Applicative
import Control.Monad

Expand Down Expand Up @@ -166,7 +164,7 @@ data BuildReport
-- | Configure outcome, did configure work ok?
testsOutcome :: Outcome
}
deriving (Eq, Typeable, Show)
deriving (Eq, Show)

packageL :: Lens' BuildReport PackageIdentifier
packageL f s = fmap (\x -> s { package = x }) (f (package s))
Expand Down Expand Up @@ -266,15 +264,15 @@ data BooleanCovg = BooleanCovg {
guards :: (Int,Int),
ifConditions :: (Int,Int),
qualifiers :: (Int,Int)
} deriving (Eq, Typeable, Show)
} deriving (Eq, Show)

data BuildCovg = BuildCovg {
expressions :: (Int,Int),
boolean :: BooleanCovg,
alternatives :: (Int,Int),
localDeclarations :: (Int,Int),
topLevel :: (Int,Int)
} deriving (Eq, Typeable, Show)
} deriving (Eq, Show)

instance MemSize BuildCovg where
memSize (BuildCovg a (BooleanCovg b c d) e f g) = memSize7 a b c d e f g
Expand Down Expand Up @@ -499,7 +497,7 @@ instance Arbitrary Outcome where
arbitrary = elements [ NotTried, Failed, Ok ]

data BuildStatus = BuildOK | BuildFailCnt Int
deriving (Eq, Ord, Typeable, Show)
deriving (Eq, Ord, Show)
instance ToJSON BuildStatus where
toJSON (BuildFailCnt a) = toJSON a
toJSON BuildOK = toJSON ((-1)::Int)
Expand Down
19 changes: 9 additions & 10 deletions src/Distribution/Server/Features/BuildReports/BuildReports.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,6 @@ import qualified Data.Map as Map
import qualified Data.Serialize as Serialize
import Data.Serialize (Serialize, get, put)
import Data.SafeCopy
import Data.Typeable (Typeable)
import qualified Data.List as L
import qualified Data.Char as Char
import Data.Maybe (fromMaybe)
Expand All @@ -59,7 +58,7 @@ import Text.StringTemplate (ToSElem(..))


newtype BuildReportId = BuildReportId Int
deriving (Eq, Ord, Typeable, Show, MemSize, Pretty)
deriving (Eq, Ord, Show, MemSize, Pretty)

incrementReportId :: BuildReportId -> BuildReportId
incrementReportId (BuildReportId n) = BuildReportId (n+1)
Expand All @@ -81,10 +80,10 @@ instance Parsec BuildReportId where
f c = Char.ord c - Char.ord '0'

newtype BuildLog = BuildLog BlobStorage.BlobId
deriving (Eq, Typeable, Show, MemSize)
deriving (Eq, Show, MemSize)

newtype TestLog = TestLog BlobStorage.BlobId
deriving (Eq, Typeable, Show, MemSize)
deriving (Eq, Show, MemSize)

data PkgBuildReports = PkgBuildReports {
-- for each report, other useful information: Maybe UserId, UTCTime
Expand All @@ -96,12 +95,12 @@ data PkgBuildReports = PkgBuildReports {
nextReportId :: !BuildReportId,
buildStatus :: !BuildStatus,
runTests :: !Bool
} deriving (Eq, Typeable, Show)
} deriving (Eq, Show)

data BuildReports = BuildReports {
reportsIndex :: !(Map.Map PackageId PkgBuildReports)

} deriving (Eq, Typeable, Show)
} deriving (Eq, Show)

emptyPkgReports :: PkgBuildReports
emptyPkgReports = PkgBuildReports {
Expand Down Expand Up @@ -300,7 +299,7 @@ data PkgBuildReports_v3 = PkgBuildReports_v3 {
reports_v3 :: !(Map BuildReportId (BuildReport, Maybe BuildLog, Maybe BuildCovg )),
nextReportId_v3 :: !BuildReportId,
buildStatus_v3 :: !BuildStatus
} deriving (Eq, Typeable, Show)
} deriving (Eq, Show)

instance SafeCopy PkgBuildReports_v3 where
version = 3
Expand All @@ -320,7 +319,7 @@ instance MemSize PkgBuildReports_v3 where
data PkgBuildReports_v2 = PkgBuildReports_v2 {
reports_v2 :: !(Map BuildReportId (BuildReport, Maybe BuildLog)),
nextReportId_v2 :: !BuildReportId
} deriving (Eq, Typeable, Show)
} deriving (Eq, Show)

instance SafeCopy PkgBuildReports_v2 where
version = 2
Expand Down Expand Up @@ -397,7 +396,7 @@ instance Serialize BuildReports_v0 where

data BuildReports_v2 = BuildReports_v2
{ reportsIndex_v2 :: !(Map.Map PackageId PkgBuildReports_v2)
} deriving (Eq, Typeable, Show)
} deriving (Eq, Show)

instance Migrate BuildReports_v2 where
type MigrateFrom BuildReports_v2 = BuildReports_v0
Expand All @@ -411,7 +410,7 @@ deriveSafeCopy 2 'extension ''BuildReports_v2

data BuildReports_v3 = BuildReports_v3
{ reportsIndex_v3 :: !(Map.Map PackageId PkgBuildReports_v3)
} deriving (Eq, Typeable, Show)
} deriving (Eq, Show)

instance Migrate BuildReports_v3 where
type MigrateFrom BuildReports_v3 = BuildReports_v2
Expand Down
4 changes: 2 additions & 2 deletions src/Distribution/Server/Features/Core/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ data PackagesState = PackagesState {
-- for the moment the update log is a 'Either', to help with the transition
-- we can change that later
}
deriving (Eq, Typeable, Show)
deriving (Eq, Show)

-- transient type used for migration which holds the fields for
-- 'ExtraEntry' carried over from 'PackagesState_v1'
Expand Down Expand Up @@ -322,7 +322,7 @@ data PackagesState_v1 = PackagesState_v1 {
-- for the moment the update log is a Maybe, to help with the transition
-- we can change that later
}
deriving (Eq, Typeable, Show)
deriving (Eq, Show)

instance Migrate PackagesState_v1 where
type MigrateFrom PackagesState_v1 = PackagesState_v0
Expand Down
3 changes: 1 addition & 2 deletions src/Distribution/Server/Features/Distro/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@ import Distribution.Server.Framework.MemSize

import Data.Acid (Query, Update, makeAcidic)
import Data.SafeCopy (base, deriveSafeCopy)
import Data.Typeable

import Data.Maybe (fromMaybe)
import Control.Monad (liftM)
Expand All @@ -27,7 +26,7 @@ data Distros = Distros {
distDistros :: !Distributions,
distVersions :: !DistroVersions
}
deriving (Eq, Typeable, Show)
deriving (Eq, Show)

deriveSafeCopy 0 'base ''Distros

Expand Down
9 changes: 4 additions & 5 deletions src/Distribution/Server/Features/Distro/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,12 +27,11 @@ import qualified Text.PrettyPrint as Disp
import qualified Data.Char as Char

import Data.SafeCopy (base, deriveSafeCopy)
import Data.Typeable


-- | Distribution names may contain letters, numbers and punctuation.
newtype DistroName = DistroName String
deriving (Eq, Ord, Read, Show, Typeable, MemSize)
deriving (Eq, Ord, Read, Show, MemSize)

instance Pretty DistroName where
pretty (DistroName name) = Disp.text name
Expand All @@ -44,21 +43,21 @@ instance Parsec DistroName where
data Distributions = Distributions {
nameMap :: !(Map.Map DistroName UserIdSet)
}
deriving (Eq, Typeable, Show)
deriving (Eq, Show)

-- | Listing of which distributions have which versions of particular
-- packages.
data DistroVersions = DistroVersions {
packageDistroMap :: !(Map.Map PackageName (Map.Map DistroName DistroPackageInfo)),
distroMap :: !(Map.Map DistroName (Set.Set PackageName))
} deriving (Eq, Typeable, Show)
} deriving (Eq, Show)

data DistroPackageInfo
= DistroPackageInfo
{ distroVersion :: Version.Version
, distroUrl :: String
}
deriving (Eq, Typeable, Show)
deriving (Eq, Show)

$(deriveSafeCopy 0 'base ''DistroName)
$(deriveSafeCopy 0 'base ''Distributions)
Expand Down
3 changes: 1 addition & 2 deletions src/Distribution/Server/Features/Documentation/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,6 @@ import Distribution.Server.Framework.MemSize

import Data.Acid (Query, Update, makeAcidic)
import Data.SafeCopy (base, deriveSafeCopy)
import Data.Typeable
import Control.Monad.Reader
import qualified Control.Monad.State as State

Expand All @@ -18,7 +17,7 @@ import qualified Data.Map as Map
---------------------------------- Documentation
data Documentation = Documentation {
documentation :: !(Map.Map PackageIdentifier BlobId)
} deriving (Typeable, Show, Eq)
} deriving (Show, Eq)

deriveSafeCopy 0 'base ''Documentation

Expand Down
3 changes: 1 addition & 2 deletions src/Distribution/Server/Features/DownloadCount/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
module Distribution.Server.Features.DownloadCount.State where

import Data.Time.Calendar (Day(..))
import Data.Typeable (Typeable)
import Data.Foldable (forM_)
import Control.Arrow (first)
import Control.Monad (liftM)
Expand Down Expand Up @@ -51,7 +50,7 @@ data InMemStats = InMemStats {
inMemToday :: !Day
, inMemCounts :: !(SimpleCountingMap PackageId)
}
deriving (Show, Eq, Typeable)
deriving (Show, Eq)

newtype OnDiskStats = OnDiskStats {
onDiskStats :: NestedCountingMap PackageName OnDiskPerPkg
Expand Down
3 changes: 1 addition & 2 deletions src/Distribution/Server/Features/HaskellPlatform/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,6 @@ import qualified Data.Map as Map
import Data.SafeCopy (base, deriveSafeCopy)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Typeable

import Distribution.Server.Framework.Instances ()
import Distribution.Server.Framework.MemSize
Expand All @@ -22,7 +21,7 @@ import Control.Monad.State (put, modify)

newtype PlatformPackages = PlatformPackages {
blessedPackages :: Map PackageName (Set Version)
} deriving (Show, Typeable, Eq, MemSize)
} deriving (Show, Eq, MemSize)

emptyPlatformPackages :: PlatformPackages
emptyPlatformPackages = PlatformPackages Map.empty
Expand Down
Loading