Skip to content

Commit e54f2bc

Browse files
authored
Fix build warnings for using * instead of Data.Kind.Type (#1710)
1 parent 459ecef commit e54f2bc

File tree

36 files changed

+133
-76
lines changed

36 files changed

+133
-76
lines changed

servant-auth/servant-auth-docs/src/Servant/Auth/Docs.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@ module Servant.Auth.Docs
3333
) where
3434

3535
import Control.Lens ((%~), (&), (|>))
36+
import Data.Kind (Type)
3637
import Data.List (intercalate)
3738
import Data.Monoid
3839
import Data.Proxy (Proxy (Proxy))
@@ -63,7 +64,7 @@ pretty rs =
6364
)
6465

6566

66-
class AllDocs (x :: [*]) where
67+
class AllDocs (x :: [Type]) where
6768
allDocs :: proxy x
6869
-- intro, req
6970
-> [(String, String)]

servant-auth/servant-auth-server/src/Servant/Auth/Server/Internal/AddSetCookie.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module Servant.Auth.Server.Internal.AddSetCookie where
77

88
import Blaze.ByteString.Builder (toByteString)
99
import qualified Data.ByteString as BS
10+
import Data.Kind (Type)
1011
import qualified Network.HTTP.Types as HTTP
1112
import Network.Wai (mapResponseHeaders)
1213
import Servant
@@ -33,12 +34,12 @@ type family AddSetCookieApiVerb a where
3334
AddSetCookieApiVerb a = Headers '[Header "Set-Cookie" SetCookie] a
3435

3536
#if MIN_VERSION_servant_server(0,18,1)
36-
type family MapAddSetCookieApiVerb (as :: [*]) where
37+
type family MapAddSetCookieApiVerb (as :: [Type]) where
3738
MapAddSetCookieApiVerb '[] = '[]
3839
MapAddSetCookieApiVerb (a ': as) = (AddSetCookieApiVerb a ': MapAddSetCookieApiVerb as)
3940
#endif
4041

41-
type family AddSetCookieApi a :: *
42+
type family AddSetCookieApi a :: Type
4243
type instance AddSetCookieApi (a :> b) = a :> AddSetCookieApi b
4344
type instance AddSetCookieApi (a :<|> b) = AddSetCookieApi a :<|> AddSetCookieApi b
4445
#if MIN_VERSION_servant_server(0,19,0)
@@ -57,7 +58,7 @@ type instance AddSetCookieApi (Stream method stat framing ctyps a)
5758
#endif
5859
type instance AddSetCookieApi (Headers hs a) = AddSetCookieApiVerb (Headers hs a)
5960

60-
data SetCookieList (n :: Nat) :: * where
61+
data SetCookieList (n :: Nat) :: Type where
6162
SetCookieNil :: SetCookieList 'Z
6263
SetCookieCons :: Maybe SetCookie -> SetCookieList n -> SetCookieList ('S n)
6364

servant-auth/servant-auth-server/src/Servant/Auth/Server/Internal/Class.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
module Servant.Auth.Server.Internal.Class where
33

44
import Servant.Auth
5+
import Data.Kind (Type)
56
import Data.Monoid
67
import Servant hiding (BasicAuth)
78

@@ -16,7 +17,7 @@ import Servant.Auth.Server.Internal.JWT (jwtAuthCheck)
1617
-- elements of @ctx@ to be the in the Context and whose authentication check
1718
-- returns an @AuthCheck v@.
1819
class IsAuth a v where
19-
type family AuthArgs a :: [*]
20+
type family AuthArgs a :: [Type]
2021
runAuth :: proxy a -> proxy v -> Unapp (AuthArgs a) (AuthCheck v)
2122

2223
instance FromJWT usr => IsAuth Cookie usr where
@@ -33,7 +34,7 @@ instance FromBasicAuthData usr => IsAuth BasicAuth usr where
3334

3435
-- * Helper
3536

36-
class AreAuths (as :: [*]) (ctxs :: [*]) v where
37+
class AreAuths (as :: [Type]) (ctxs :: [Type]) v where
3738
runAuths :: proxy as -> Context ctxs -> AuthCheck v
3839

3940
instance AreAuths '[] ctxs v where

servant-auth/servant-auth-swagger/src/Servant/Auth/Swagger.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ module Servant.Auth.Swagger
1717
) where
1818

1919
import Control.Lens ((&), (<>~))
20+
import Data.Kind (Type)
2021
import Data.Proxy (Proxy (Proxy))
2122
import Data.Swagger (ApiKeyLocation (..), ApiKeyParams (..),
2223
SecurityRequirement (..), SecurityScheme (..),
@@ -66,7 +67,7 @@ instance HasSecurity JWT where
6667
type_ = SecuritySchemeApiKey (ApiKeyParams "Authorization" ApiKeyHeader)
6768
desc = "JSON Web Token-based API key"
6869

69-
class AllHasSecurity (x :: [*]) where
70+
class AllHasSecurity (x :: [Type]) where
7071
securities :: Proxy x -> [(T.Text,SecurityScheme)]
7172

7273
instance {-# OVERLAPPABLE #-} (HasSecurity x, AllHasSecurity xs) => AllHasSecurity (x ': xs) where

servant-auth/servant-auth/src/Servant/Auth.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
{-# LANGUAGE TypeOperators #-}
66
module Servant.Auth where
77

8+
import Data.Kind (Type)
89
import Data.Proxy (Proxy(..))
910
import Servant.API ((:>))
1011
import Servant.Links (HasLink (..))
@@ -13,15 +14,15 @@ import Servant.Links (HasLink (..))
1314

1415
-- | @Auth [auth1, auth2] val :> api@ represents an API protected *either* by
1516
-- @auth1@ or @auth2@
16-
data Auth (auths :: [*]) val
17+
data Auth (auths :: [Type]) val
1718

1819
-- | A @HasLink@ instance for @Auth@
19-
instance HasLink sub => HasLink (Auth (tag :: [*]) value :> sub) where
20+
instance HasLink sub => HasLink (Auth (tag :: [Type]) value :> sub) where
2021
#if MIN_VERSION_servant(0,14,0)
21-
type MkLink (Auth (tag :: [*]) value :> sub) a = MkLink sub a
22+
type MkLink (Auth (tag :: [Type]) value :> sub) a = MkLink sub a
2223
toLink toA _ = toLink toA (Proxy :: Proxy sub)
2324
#else
24-
type MkLink (Auth (tag :: [*]) value :> sub) = MkLink sub
25+
type MkLink (Auth (tag :: [Type]) value :> sub) = MkLink sub
2526
toLink _ = toLink (Proxy :: Proxy sub)
2627
#endif
2728

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

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,8 @@ import Data.Either
3939
import Data.Constraint (Dict(..))
4040
import Data.Foldable
4141
(toList)
42+
import Data.Kind
43+
(Type)
4244
import Data.List
4345
(foldl')
4446
import Data.Sequence
@@ -128,7 +130,7 @@ clientIn p pm = clientWithRoute pm p defaultRequest
128130
-- combinators that you want to support client-generation, you can ignore this
129131
-- class.
130132
class RunClient m => HasClient m api where
131-
type Client (m :: * -> *) (api :: *) :: *
133+
type Client (m :: Type -> Type) (api :: Type) :: Type
132134
clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api
133135
hoistClientMonad
134136
:: Proxy m
@@ -333,7 +335,7 @@ instance {-# OVERLAPPING #-}
333335
data ClientParseError = ClientParseError MediaType String | ClientStatusMismatch | ClientNoMatchingStatus
334336
deriving (Eq, Show)
335337

336-
class UnrenderResponse (cts :: [*]) (a :: *) where
338+
class UnrenderResponse (cts :: [Type]) (a :: Type) where
337339
unrenderResponse :: Seq.Seq H.Header -> BL.ByteString -> Proxy cts
338340
-> [Either (MediaType, String) a]
339341

@@ -840,7 +842,7 @@ instance HasClient m api => HasClient m (BasicAuth realm usr :> api) where
840842
hoistClientMonad pm (Proxy :: Proxy api) f (cl bauth)
841843

842844
-- | A type that specifies that an API record contains a client implementation.
843-
data AsClientT (m :: * -> *)
845+
data AsClientT (m :: Type -> Type)
844846
instance GenericMode (AsClientT m) where
845847
type AsClientT m :- api = Client m api
846848

@@ -850,7 +852,7 @@ type GClientConstraints api m =
850852
, Client m (ToServantApi api) ~ ToServant api (AsClientT m)
851853
)
852854

853-
class GClient (api :: * -> *) m where
855+
class GClient (api :: Type -> Type) m where
854856
gClientProof :: Dict (GClientConstraints api m)
855857

856858
instance GClientConstraints api m => GClient api m where

servant-foreign/src/Servant/Foreign/Internal.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,8 @@ import Control.Lens
2222
(Getter, makeLenses, makePrisms, (%~), (&), (.~), (<>~))
2323
import Data.Data
2424
(Data)
25+
import Data.Kind
26+
(Type)
2527
import Data.Proxy
2628
import Data.String
2729
import Data.Text
@@ -274,8 +276,8 @@ instance HasForeignType NoTypes NoContent a where
274276
-- | Implementation of the Servant framework types.
275277
--
276278
-- Relevant instances: Everything containing 'HasForeignType'.
277-
class HasForeign lang ftype (api :: *) where
278-
type Foreign ftype api :: *
279+
class HasForeign lang ftype (api :: Type) where
280+
type Foreign ftype api :: Type
279281
foreignFor :: Proxy lang -> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api
280282

281283
instance (HasForeign lang ftype a, HasForeign lang ftype b)

servant-server/src/Servant/Server/Experimental/Auth.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,8 @@ module Servant.Server.Experimental.Auth where
1515

1616
import Control.Monad.Trans
1717
(liftIO)
18+
import Data.Kind
19+
(Type)
1820
import Data.Proxy
1921
(Proxy (Proxy))
2022
import Data.Typeable
@@ -38,7 +40,7 @@ import Servant.Server.Internal
3840
-- quite often this is some `User` datatype.
3941
--
4042
-- NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE
41-
type family AuthServerData a :: *
43+
type family AuthServerData a :: Type
4244

4345
-- | Handlers for AuthProtected resources
4446
--

servant-server/src/Servant/Server/Generic.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,8 @@ module Servant.Server.Generic (
1616
genericServerT
1717
) where
1818

19+
import Data.Kind
20+
(Type)
1921
import Data.Proxy
2022
(Proxy (..))
2123

@@ -37,7 +39,7 @@ genericServe = serve (Proxy :: Proxy (ToServantApi routes)) . genericServer
3739
-- by providing a transformation to bring each handler back in the 'Handler'
3840
-- monad.
3941
genericServeT
40-
:: forall (routes :: * -> *) (m :: * -> *).
42+
:: forall (routes :: Type -> Type) (m :: Type -> Type).
4143
( GenericServant routes (AsServerT m)
4244
, GenericServant routes AsApi
4345
, HasServer (ToServantApi routes) '[]
@@ -55,7 +57,7 @@ genericServeT f server = serve p $ hoistServer p f (genericServerT server)
5557
-- used by auth-related combinators in servant, e.g to hold auth checks) and the given
5658
-- transformation to map all the handlers back to the 'Handler' monad.
5759
genericServeTWithContext
58-
:: forall (routes :: * -> *) (m :: * -> *) (ctx :: [*]).
60+
:: forall (routes :: Type -> Type) (m :: Type -> Type) (ctx :: [Type]).
5961
( GenericServant routes (AsServerT m)
6062
, GenericServant routes AsApi
6163
, HasServer (ToServantApi routes) ctx

servant-server/src/Servant/Server/Internal.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,8 @@ import qualified Data.ByteString.Lazy as BL
4747
import Data.Constraint (Constraint, Dict(..))
4848
import Data.Either
4949
(partitionEithers)
50+
import Data.Kind
51+
(Type)
5052
import Data.Maybe
5153
(fromMaybe, isNothing, mapMaybe, maybeToList)
5254
import Data.String
@@ -97,8 +99,6 @@ import Servant.API.TypeErrors
9799
import Web.HttpApiData
98100
(FromHttpApiData, parseHeader, parseQueryParam, parseUrlPiece,
99101
parseUrlPieces)
100-
import Data.Kind
101-
(Type)
102102

103103
import Servant.Server.Internal.BasicAuth
104104
import Servant.Server.Internal.Context
@@ -121,7 +121,7 @@ class HasServer api context where
121121
--
122122
-- Note that the result kind is @*@, so it is /not/ a monad transformer, unlike
123123
-- what the @T@ in the name might suggest.
124-
type ServerT api (m :: * -> *) :: *
124+
type ServerT api (m :: Type -> Type) :: Type
125125

126126
route ::
127127
Proxy api
@@ -900,7 +900,7 @@ instance TypeError (PartialApplication
900900
#endif
901901
HasServer arr) => HasServer ((arr :: a -> b) :> sub) context
902902
where
903-
type ServerT (arr :> sub) _ = TypeError (PartialApplication (HasServer :: * -> [*] -> Constraint) arr)
903+
type ServerT (arr :> sub) _ = TypeError (PartialApplication (HasServer :: Type -> [Type] -> Constraint) arr)
904904
route = error "unreachable"
905905
hoistServerWithContext _ _ _ _ = error "unreachable"
906906

@@ -973,7 +973,7 @@ instance (AtLeastOneFragment api, FragmentUnique (Fragment a1 :> api), HasServer
973973
-- >>> import Servant
974974

975975
-- | A type that specifies that an API record contains a server implementation.
976-
data AsServerT (m :: * -> *)
976+
data AsServerT (m :: Type -> Type)
977977
instance GenericMode (AsServerT m) where
978978
type AsServerT m :- api = ServerT api m
979979

@@ -999,7 +999,7 @@ type GServerConstraints api m =
999999
-- Users shouldn't have to worry about this class, as the only possible instance
10001000
-- is provided in this module for all record APIs.
10011001

1002-
class GServer (api :: * -> *) (m :: * -> *) where
1002+
class GServer (api :: Type -> Type) (m :: Type -> Type) where
10031003
gServerProof :: Dict (GServerConstraints api m)
10041004

10051005
instance

0 commit comments

Comments
 (0)