@@ -41,7 +41,7 @@ import qualified Data.ByteString as B
4141import qualified Data.ByteString.Builder as BB
4242import qualified Data.ByteString.Char8 as BC8
4343import qualified Data.ByteString.Lazy as BL
44- import Data.Constraint (Constraint , Dict (.. ))
44+ import Data.Constraint (Dict (.. ))
4545import Data.Either
4646 (partitionEithers )
4747import Data.Maybe
@@ -56,7 +56,7 @@ import qualified Data.Text as T
5656import Data.Typeable
5757import GHC.Generics
5858import GHC.TypeLits
59- (KnownNat , KnownSymbol , TypeError , symbolVal )
59+ (KnownNat , KnownSymbol , symbolVal )
6060import qualified Network.HTTP.Media as NHM
6161import Network.HTTP.Types hiding
6262 (Header , ResponseHeaders )
@@ -90,7 +90,6 @@ import Servant.API.ResponseHeaders
9090import Servant.API.Status
9191 (statusFromNat )
9292import qualified Servant.Types.SourceT as S
93- import Servant.API.TypeErrors
9493import Web.HttpApiData
9594 (FromHttpApiData , parseHeader , parseQueryParam , parseUrlPiece ,
9695 parseUrlPieces )
@@ -106,8 +105,6 @@ import Servant.Server.Internal.RouteResult
106105import Servant.Server.Internal.RoutingApplication
107106import Servant.Server.Internal.ServerError
108107
109- import GHC.TypeLits
110- (ErrorMessage (.. ))
111108import Servant.API.TypeLevel
112109 (AtLeastOneFragment , FragmentUnique )
113110
@@ -814,59 +811,6 @@ instance (HasContextEntry context (NamedContext name subContext), HasServer subA
814811
815812 hoistServerWithContext _ _ nt s = hoistServerWithContext (Proxy :: Proxy subApi ) (Proxy :: Proxy subContext ) nt s
816813
817- -------------------------------------------------------------------------------
818- -- Custom type errors
819- -------------------------------------------------------------------------------
820-
821- -- Erroring instance for 'HasServer' when a combinator is not fully applied
822- instance TypeError (PartialApplication HasServer arr ) => HasServer ((arr :: a -> b ) :> sub ) context
823- where
824- type ServerT (arr :> sub ) _ = TypeError (PartialApplication (HasServer :: * -> [* ] -> Constraint ) arr )
825- route = error " unreachable"
826- hoistServerWithContext _ _ _ _ = error " unreachable"
827-
828- -- | This instance prevents from accidentally using '->' instead of ':>'
829- --
830- -- >>> serve (Proxy :: Proxy (Capture "foo" Int -> Get '[JSON] Int)) (error "...")
831- -- ...
832- -- ...No instance HasServer (a -> b).
833- -- ...Maybe you have used '->' instead of ':>' between
834- -- ...Capture' '[] "foo" Int
835- -- ...and
836- -- ...Verb 'GET 200 '[JSON] Int
837- -- ...
838- --
839- -- >>> undefined :: Server (Capture "foo" Int -> Get '[JSON] Int)
840- -- ...
841- -- ...No instance HasServer (a -> b).
842- -- ...Maybe you have used '->' instead of ':>' between
843- -- ...Capture' '[] "foo" Int
844- -- ...and
845- -- ...Verb 'GET 200 '[JSON] Int
846- -- ...
847- --
848- instance TypeError (HasServerArrowTypeError a b ) => HasServer (a -> b ) context
849- where
850- type ServerT (a -> b ) m = TypeError (HasServerArrowTypeError a b )
851- route _ _ _ = error " servant-server panic: impossible happened in HasServer (a -> b)"
852- hoistServerWithContext _ _ _ = id
853-
854- type HasServerArrowTypeError a b =
855- 'Text " No instance HasServer (a -> b)."
856- ':$$: 'Text " Maybe you have used '->' instead of ':>' between "
857- ':$$: 'ShowType a
858- ':$$: 'Text " and"
859- ':$$: 'ShowType b
860-
861- -- Erroring instances for 'HasServer' for unknown API combinators
862-
863- -- XXX: This omits the @context@ parameter, e.g.:
864- --
865- -- "There is no instance for HasServer (Bool :> …)". Do we care ?
866- instance {-# OVERLAPPABLE #-} TypeError (NoInstanceForSub HasServer ty ) => HasServer (ty :> sub ) context
867-
868- instance {-# OVERLAPPABLE #-} TypeError (NoInstanceFor (HasServer api context )) => HasServer api context
869-
870814-- | Ignore @'Fragment'@ in server handlers.
871815-- See <https://ietf.org/rfc/rfc2616.html#section-15.1.3> for more details.
872816--
0 commit comments