Skip to content

Commit afa8778

Browse files
committed
Move erroring instances of HasClient to separate file
1 parent 9a4c874 commit afa8778

File tree

4 files changed

+53
-19
lines changed

4 files changed

+53
-19
lines changed

servant-client-core/servant-client-core.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,8 @@ library
4444

4545
other-modules:
4646
Servant.Client.Core.Internal
47+
Servant.Client.Core.HasClient.Internal
48+
Servant.Client.Core.HasClient.TypeErrors
4749

4850
-- Bundled with GHC: Lower bound to not force re-installs
4951
-- text and mtl are bundled starting with GHC-8.4
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
-- | Wrapper for Servant.Client.Core.HasClient.Internal, which brings in scope the
2+
-- instance declarations in Servant.Client.Core.HasClient.TypeErrors
3+
module Servant.Client.Core.HasClient
4+
( module Servant.Client.Core.HasClient.Internal
5+
) where
6+
7+
import Servant.Client.Core.HasClient.Internal
8+
import Servant.Client.Core.HasClient.TypeErrors ()

servant-client-core/src/Servant/Client/Core/HasClient/Internal.hs

Lines changed: 2 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@
1414
{-# LANGUAGE TypeOperators #-}
1515
{-# LANGUAGE UndecidableInstances #-}
1616

17-
module Servant.Client.Core.HasClient (
17+
module Servant.Client.Core.HasClient.Internal (
1818
clientIn,
1919
HasClient (..),
2020
EmptyClient (..),
@@ -62,7 +62,7 @@ import Data.Text
6262
import Data.Proxy
6363
(Proxy (Proxy))
6464
import GHC.TypeLits
65-
(KnownNat, KnownSymbol, TypeError, symbolVal)
65+
(KnownNat, KnownSymbol, symbolVal)
6666
import Network.HTTP.Types
6767
(Status)
6868
import qualified Network.HTTP.Types as H
@@ -88,7 +88,6 @@ import Servant.API.Status
8888
import Servant.API.TypeLevel (FragmentUnique, AtLeastOneFragment)
8989
import Servant.API.Modifiers
9090
(FoldRequired, RequiredArgument, foldRequiredArgument)
91-
import Servant.API.TypeErrors
9291
import Servant.API.UVerb
9392
(HasStatus, HasStatuses (Statuses, statuses), UVerb, Union, Unique, inject, statusOf, foldMapUnion, matchUnion)
9493

@@ -974,19 +973,3 @@ decodedAs response ct = do
974973
Right val -> return val
975974
where
976975
accept = toList $ contentTypes ct
977-
978-
-------------------------------------------------------------------------------
979-
-- Custom type errors
980-
-------------------------------------------------------------------------------
981-
982-
-- Erroring instance for HasClient' when a combinator is not fully applied
983-
instance (RunClient m, TypeError (PartialApplication HasClient arr)) => HasClient m ((arr :: a -> b) :> sub)
984-
where
985-
type Client m (arr :> sub) = TypeError (PartialApplication HasClient arr)
986-
clientWithRoute _ _ _ = error "unreachable"
987-
hoistClientMonad _ _ _ _ = error "unreachable"
988-
989-
-- Erroring instances for 'HasClient' for unknown API combinators
990-
instance {-# OVERLAPPABLE #-} (RunClient m, TypeError (NoInstanceForSub (HasClient m) ty)) => HasClient m (ty :> sub)
991-
992-
instance {-# OVERLAPPABLE #-} (RunClient m, TypeError (NoInstanceFor (HasClient m api))) => HasClient m api
Lines changed: 41 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,41 @@
1+
{-# LANGUAGE FlexibleInstances #-}
2+
{-# LANGUAGE MultiParamTypeClasses #-}
3+
{-# LANGUAGE PolyKinds #-}
4+
{-# LANGUAGE TypeFamilies #-}
5+
{-# LANGUAGE TypeOperators #-}
6+
{-# LANGUAGE UndecidableInstances #-}
7+
8+
{-# OPTIONS_GHC -fno-warn-orphans #-}
9+
{-# OPTIONS_GHC -fno-warn-missing-methods #-}
10+
11+
-- | This module contains erroring instances for @Servant.Client.Core.HasClient.Internal@.
12+
-- They are separated from the bulk of the code, because they raise "missing methods"
13+
-- warnings. These warnings are expected, but ignoring them would lead to missing
14+
-- relevant warnings in @Servant.Client.Core.HasClient.Internal@. Therefore, we put them
15+
-- in a separate file, and ignore the warnings here.
16+
module Servant.Client.Core.HasClient.TypeErrors ()
17+
where
18+
19+
import Prelude ()
20+
import Prelude.Compat
21+
22+
import GHC.TypeLits
23+
(TypeError)
24+
import Servant.API
25+
((:>))
26+
import Servant.API.TypeErrors
27+
28+
import Servant.Client.Core.HasClient.Internal
29+
import Servant.Client.Core.RunClient
30+
31+
-- Erroring instance for HasClient' when a combinator is not fully applied
32+
instance (RunClient m, TypeError (PartialApplication HasClient arr)) => HasClient m ((arr :: a -> b) :> sub)
33+
where
34+
type Client m (arr :> sub) = TypeError (PartialApplication HasClient arr)
35+
clientWithRoute _ _ _ = error "unreachable"
36+
hoistClientMonad _ _ _ _ = error "unreachable"
37+
38+
-- Erroring instances for 'HasClient' for unknown API combinators
39+
instance {-# OVERLAPPABLE #-} (RunClient m, TypeError (NoInstanceForSub (HasClient m) ty)) => HasClient m (ty :> sub)
40+
41+
instance {-# OVERLAPPABLE #-} (RunClient m, TypeError (NoInstanceFor (HasClient m api))) => HasClient m api

0 commit comments

Comments
 (0)