Remove unnecesary Typeable deriving

This commit is contained in:
Juan Paucar 2020-01-17 11:48:58 -05:00
parent 804b114d91
commit c279547962
11 changed files with 7 additions and 23 deletions

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
@ -15,7 +14,6 @@ import Data.Yaml
import Data.Text (Text)
import qualified Data.Text.Encoding as TE
import qualified Data.Text.Lazy.Encoding as LTE
import Data.Typeable (Typeable)
import Database.Persist.Sqlite
import Database.Persist.TH
import Network.Mail.Mime
@ -37,7 +35,6 @@ User
verkey Text Maybe -- Used for resetting passwords
verified Bool
UniqueUser email
deriving Typeable
|]
data App = App

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, OverloadedStrings, QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
@ -32,7 +32,7 @@ import Yesod.Core
data YesodOAuthException = CredentialError String Credential
| SessionError String
deriving (Show, Typeable)
deriving Show
instance Exception YesodOAuthException

View File

@ -8,7 +8,6 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Yesod.Auth
@ -515,7 +514,6 @@ maybeAuthPair = runMaybeT $ do
newtype CachedMaybeAuth val = CachedMaybeAuth { unCachedMaybeAuth :: Maybe val }
deriving Typeable
-- | Class which states that the given site is an instance of @YesodAuth@
-- and that its @AuthId@ is a lookup key for the full user information in
@ -607,7 +605,7 @@ instance YesodAuth master => RenderMessage master AuthMessage where
renderMessage = renderAuthMessage
data AuthException = InvalidFacebookResponse
deriving (Show, Typeable)
deriving Show
instance Exception AuthException
instance YesodAuth master => YesodSubDispatch Auth master where

View File

@ -4,7 +4,6 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ViewPatterns #-}
module Yesod.Auth.Routes where

View File

@ -8,7 +8,6 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ScopedTypeVariables #-}
---------------------------------------------------------
--
@ -1037,7 +1036,7 @@ instance (key ~ Text, val ~ Text) => RedirectUrl master (Route master, Map.Map k
-- > redirect (NewsfeedR :#: storyId)
--
-- @since 1.2.9.
data Fragment a b = a :#: b deriving (Show, Typeable)
data Fragment a b = a :#: b deriving Show
instance (RedirectUrl master a, PathPiece b) => RedirectUrl master (Fragment a b) where
toTextUrl (a :#: b) = (\ua -> T.concat [ua, "#", toPathPiece b]) <$> toTextUrl a

View File

@ -1,6 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE FlexibleInstances #-}
@ -37,7 +36,6 @@ import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy.Builder as TBuilder
import Data.Time (UTCTime)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Language.Haskell.TH.Syntax (Loc)
import qualified Network.HTTP.Types as H
@ -333,7 +331,7 @@ data ErrorResponse =
| NotAuthenticated
| PermissionDenied !Text
| BadMethod !H.Method
deriving (Show, Eq, Typeable, Generic)
deriving (Show, Eq, Generic)
instance NFData ErrorResponse
----- header stuff
@ -411,7 +409,6 @@ data HandlerContents =
| HCCreated !Text
| HCWai !W.Response
| HCWaiApp !W.Application
deriving Typeable
instance Show HandlerContents where
show (HCContent status (TypedContent t _)) = "HCContent " ++ show (status, t)

View File

@ -1,5 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE PatternGuards #-}
{-# OPTIONS_GHC -fno-warn-missing-fields #-} -- QuasiQuoter
module Yesod.Routes.Parse

View File

@ -1,7 +1,6 @@
{-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE Rank2Types #-}
module YesodCoreTest.Cache
( cacheTest
@ -22,10 +21,8 @@ import qualified Data.ByteString.Lazy.Char8 as L8
data C = C
newtype V1 = V1 Int
deriving Typeable
newtype V2 = V2 Int
deriving Typeable
mkYesod "C" [parseRoutes|
/ RootR GET

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveDataTypeable, RecordWildCards #-}
{-# LANGUAGE RecordWildCards #-}
import Network.Wai.Application.Static
( StaticSettings (..), staticApp, defaultMimeType, defaultListing
, defaultMimeTypes, mimeTypeByExt
@ -25,7 +25,7 @@ data Args = Args
, verbose :: Bool
, mime :: [(String, String)]
}
deriving (Show, Data, Typeable)
deriving (Show, Data)
defaultArgs = Args "." ["index.html", "index.htm"] 3000 False False False []

View File

@ -1,4 +1,3 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
module Yesod.Default.Config

View File

@ -1,5 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Yesod.Default.Main