Skip to content

Commit

Permalink
Merge pull request #1743 from haskell-servant/tidy-servant-package
Browse files Browse the repository at this point in the history
Remove useless extensions in servant package
  • Loading branch information
tchoutri authored Apr 25, 2024
2 parents 62f3c4f + 7c0e466 commit 534e8c9
Show file tree
Hide file tree
Showing 16 changed files with 24 additions and 31 deletions.
3 changes: 0 additions & 3 deletions servant/src/Servant/API/Alternative.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_HADDOCK not-home #-}
Expand Down
2 changes: 1 addition & 1 deletion servant/src/Servant/API/BasicAuth.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE KindSignatures #-}

{-# LANGUAGE PolyKinds #-}

module Servant.API.BasicAuth where
Expand Down
2 changes: 1 addition & 1 deletion servant/src/Servant/API/ContentTypes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -397,7 +397,7 @@ instance MimeUnrender PlainText String where

-- | @Right . id@
instance MimeUnrender OctetStream ByteString where
mimeUnrender _ = Right . id
mimeUnrender _ = Right

-- | @Right . toStrict@
instance MimeUnrender OctetStream BS.ByteString where
Expand Down
2 changes: 1 addition & 1 deletion servant/src/Servant/API/Experimental/Auth.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE KindSignatures #-}

{-# LANGUAGE PolyKinds #-}
module Servant.API.Experimental.Auth where

Expand Down
2 changes: 1 addition & 1 deletion servant/src/Servant/API/Fragment.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-}

{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Fragment (Fragment) where

Expand Down
2 changes: 1 addition & 1 deletion servant/src/Servant/API/Modifiers.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE KindSignatures #-}

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
Expand Down
2 changes: 1 addition & 1 deletion servant/src/Servant/API/QueryParam.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-}

{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.QueryParam (QueryFlag, QueryParam, QueryParam', QueryParams) where

Expand Down
3 changes: 0 additions & 3 deletions servant/src/Servant/API/QueryString.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
Expand All @@ -11,9 +10,7 @@
module Servant.API.QueryString (QueryString, DeepQuery, FromDeepQuery (..), ToDeepQuery (..), generateDeepParam) where

import Data.Bifunctor (Bifunctor (first))
#if MIN_VERSION_base(4,9,0)
import Data.Kind (Type)
#endif
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Text (Text)
Expand Down
4 changes: 2 additions & 2 deletions servant/src/Servant/API/ResponseHeaders.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}

{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
Expand Down Expand Up @@ -184,7 +184,7 @@ instance {-# OVERLAPPABLE #-} ( KnownSymbol h, ToHttpApiData v , new ~ Headers '
-- responses if the list is empty).
instance (AddHeader mods h v old new) => AddHeader mods h v (Union '[old]) (Union '[new]) where
addOptionalHeader hdr resp =
SOP.Z $ SOP.I $ addOptionalHeader hdr $ SOP.unI $ SOP.unZ $ resp
SOP.Z $ SOP.I $ addOptionalHeader hdr $ SOP.unI $ SOP.unZ resp

instance
( AddHeader mods h v old new, AddHeader mods h v (Union oldrest) (Union newrest)
Expand Down
4 changes: 2 additions & 2 deletions servant/src/Servant/API/Stream.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,8 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}


{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
Expand Down
2 changes: 1 addition & 1 deletion servant/src/Servant/API/TypeLevel.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand Down
4 changes: 2 additions & 2 deletions servant/src/Servant/API/UVerb.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
Expand All @@ -10,7 +10,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}


-- | An alternative to 'Verb' for end-points that respond with a resource value of any of an
-- open union of types, and specific status codes for each type in this union. (`UVerb` is
Expand Down
4 changes: 2 additions & 2 deletions servant/src/Servant/API/UVerb/Union.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitNamespaces #-}

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
Expand Down
2 changes: 1 addition & 1 deletion servant/src/Servant/API/Verbs.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE KindSignatures #-}

{-# LANGUAGE PolyKinds #-}
module Servant.API.Verbs
( module Servant.API.Verbs
Expand Down
5 changes: 2 additions & 3 deletions servant/src/Servant/Links.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,9 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE QuantifiedConstraints #-}
Expand All @@ -13,8 +12,8 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_HADDOCK not-home #-}
{-# LANGUAGE MultiParamTypeClasses #-}

-- | Type safe generation of internal links.
--
Expand Down
12 changes: 6 additions & 6 deletions servant/src/Servant/Types/SourceT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,7 @@ instance (Applicative m, Show1 m, Show a) => Show (SourceT m a) where
-- fromStepT (Effect (Just (Yield 1 (Yield 2 (Yield 3 Stop)))))
instance MFunctor SourceT where
hoist f (SourceT m) = SourceT $ \k -> k $
Effect $ f $ fmap (hoist f) $ m return
Effect $ f $ fmap (hoist f) $ m pure

-- | >>> source "xy" <> source "z" :: SourceT Identity Char
-- fromStepT (Effect (Identity (Yield 'x' (Yield 'y' (Yield 'z' Stop)))))
Expand Down Expand Up @@ -197,7 +197,7 @@ instance (QC.Arbitrary a, Monad m) => QC.Arbitrary (StepT m a) where
| otherwise = QC.frequency
[ (1, pure Stop)
, (1, Skip <$> arb')
, (1, Effect . return <$> arb')
, (1, Effect . pure <$> arb')
, (8, Yield <$> QC.arbitrary <*> arb')
]
where
Expand Down Expand Up @@ -235,7 +235,7 @@ runSourceT :: Monad m => SourceT m a -> ExceptT String m [a]
runSourceT (SourceT m) = ExceptT (m (runExceptT . runStepT))

runStepT :: Monad m => StepT m a -> ExceptT String m [a]
runStepT Stop = return []
runStepT Stop = pure []
runStepT (Error err) = throwError err
runStepT (Skip s) = runStepT s
runStepT (Yield x s) = fmap (x :) (runStepT s)
Expand All @@ -246,9 +246,9 @@ runStepT (Effect ms) = lift ms >>= runStepT
-- Identity (Just ('f',Yield 'o' (Yield 'o' Stop)))
--
uncons :: Monad m => StepT m a -> m (Maybe (a, StepT m a))
uncons Stop = return Nothing
uncons Stop = pure Nothing
uncons (Skip s) = uncons s
uncons (Yield x s) = return (Just (x, s))
uncons (Yield x s) = pure (Just (x, s))
uncons (Effect ms) = ms >>= uncons
uncons (Error _) =
-}
Expand Down Expand Up @@ -298,7 +298,7 @@ foreachStep
-> StepT m a
-> m ()
foreachStep f g = go where
go Stop = return ()
go Stop = pure ()
go (Skip s) = go s
go (Yield x s) = g x >> go s
go (Error err) = f err
Expand Down

0 comments on commit 534e8c9

Please sign in to comment.