Skip to content

Commit

Permalink
Fix warning: deriving-typeable
Browse files Browse the repository at this point in the history
  • Loading branch information
alexfmpe committed Jan 19, 2025
1 parent eea3c77 commit 71196c9
Show file tree
Hide file tree
Showing 3 changed files with 5 additions and 14 deletions.
9 changes: 3 additions & 6 deletions reflex-dom-core/src/Reflex/Dom/Xhr.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
Expand Down Expand Up @@ -174,7 +173,6 @@ import Data.Text.Encoding
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Builder as B
import Data.Traversable
import Data.Typeable

import Language.Javascript.JSaddle.Monad (JSM, askJSM, runJSM, MonadJSM, liftJSM)

Expand All @@ -183,7 +181,7 @@ data XhrRequest a
, _xhrRequest_url :: Text
, _xhrRequest_config :: XhrRequestConfig a
}
deriving (Show, Read, Eq, Ord, Typeable, Functor)
deriving (Show, Read, Eq, Ord, Functor)

data XhrRequestConfig a
= XhrRequestConfig { _xhrRequestConfig_headers :: Map Text Text
Expand All @@ -194,7 +192,7 @@ data XhrRequestConfig a
, _xhrRequestConfig_withCredentials :: Bool
, _xhrRequestConfig_responseHeaders :: XhrResponseHeaders
}
deriving (Show, Read, Eq, Ord, Typeable, Functor)
deriving (Show, Read, Eq, Ord, Functor)

data XhrResponse
= XhrResponse { _xhrResponse_status :: Word
Expand All @@ -203,12 +201,11 @@ data XhrResponse
, _xhrResponse_responseText :: Maybe Text
, _xhrResponse_headers :: Map (CI Text) Text
}
deriving (Typeable)

data XhrResponseHeaders =
OnlyHeaders (Set.Set (CI Text)) -- ^ Parse a subset of headers from the XHR Response
| AllHeaders -- ^ Parse all headers from the XHR Response
deriving (Show, Read, Eq, Ord, Typeable)
deriving (Show, Read, Eq, Ord)

instance Default XhrResponseHeaders where
def = OnlyHeaders mempty
Expand Down
5 changes: 1 addition & 4 deletions reflex-dom-core/src/Reflex/Dom/Xhr/Exception.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,9 @@
{-# LANGUAGE DeriveDataTypeable #-}

module Reflex.Dom.Xhr.Exception where

import Control.Exception (Exception (..))
import Data.Typeable

data XhrException = XhrException_Error
| XhrException_Aborted
deriving (Show, Read, Eq, Ord, Typeable)
deriving (Show, Read, Eq, Ord)

instance Exception XhrException
5 changes: 1 addition & 4 deletions reflex-dom-core/src/Reflex/Dom/Xhr/ResponseType.hs
Original file line number Diff line number Diff line change
@@ -1,18 +1,15 @@
{-# LANGUAGE DeriveDataTypeable #-}

module Reflex.Dom.Xhr.ResponseType where

import Data.ByteString (ByteString)
import Data.Text (Text)
import Data.Typeable
import GHCJS.DOM.Blob (Blob)

data XhrResponseType
= XhrResponseType_Default
| XhrResponseType_ArrayBuffer
| XhrResponseType_Blob
| XhrResponseType_Text
deriving (Show, Read, Eq, Ord, Typeable)
deriving (Show, Read, Eq, Ord)

data XhrResponseBody
= XhrResponseBody_Default Text
Expand Down

0 comments on commit 71196c9

Please sign in to comment.