Exclude quantified constraints code for GHCJS
QuantifiedConstraints isn't available for GHC 8.4 (where our GHCJS version is still stuck). We may need to take a drastic decision for GHCJS at some point.
This commit is contained in:
parent
5ead291f8d
commit
861cd4f997
2 changed files with 20 additions and 1 deletions
|
@ -1,16 +1,21 @@
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
{-# LANGUAGE ConstraintKinds #-}
|
{-# LANGUAGE ConstraintKinds #-}
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE InstanceSigs #-}
|
{-# LANGUAGE InstanceSigs #-}
|
||||||
{-# LANGUAGE KindSignatures #-}
|
{-# LANGUAGE KindSignatures #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE QuantifiedConstraints #-}
|
|
||||||
{-# LANGUAGE RankNTypes #-}
|
{-# LANGUAGE RankNTypes #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
|
||||||
|
#if __GLASGOW_HASKELL__ >= 806
|
||||||
|
{-# LANGUAGE QuantifiedConstraints #-}
|
||||||
|
#endif
|
||||||
|
|
||||||
module Servant.Client.Generic (
|
module Servant.Client.Generic (
|
||||||
AsClientT,
|
AsClientT,
|
||||||
genericClient,
|
genericClient,
|
||||||
|
@ -58,6 +63,8 @@ genericClientHoist nt
|
||||||
m = Proxy :: Proxy m
|
m = Proxy :: Proxy m
|
||||||
api = Proxy :: Proxy (ToServantApi routes)
|
api = Proxy :: Proxy (ToServantApi routes)
|
||||||
|
|
||||||
|
#if __GLASGOW_HASKELL__ >= 806
|
||||||
|
|
||||||
type GClientConstraints api m =
|
type GClientConstraints api m =
|
||||||
( GenericServant api (AsClientT m)
|
( GenericServant api (AsClientT m)
|
||||||
, Client m (ToServantApi api) ~ ToServant api (AsClientT m)
|
, Client m (ToServantApi api) ~ ToServant api (AsClientT m)
|
||||||
|
@ -95,3 +102,5 @@ instance
|
||||||
fromServant @api @(AsClientT mb) $
|
fromServant @api @(AsClientT mb) $
|
||||||
hoistClientMonad @m @(ToServantApi api) @ma @mb Proxy Proxy nat $
|
hoistClientMonad @m @(ToServantApi api) @ma @mb Proxy Proxy nat $
|
||||||
toServant @api @(AsClientT ma) clientA
|
toServant @api @(AsClientT ma) clientA
|
||||||
|
|
||||||
|
#endif
|
||||||
|
|
|
@ -1,6 +1,7 @@
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
{-# LANGUAGE AllowAmbiguousTypes #-}
|
{-# LANGUAGE AllowAmbiguousTypes #-}
|
||||||
{-# LANGUAGE ConstraintKinds #-}
|
{-# LANGUAGE ConstraintKinds #-}
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
{-# LANGUAGE DefaultSignatures #-}
|
{-# LANGUAGE DefaultSignatures #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
@ -15,6 +16,11 @@
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
|
||||||
|
#if __GLASGOW_HASKELL__ >= 806
|
||||||
|
{-# LANGUAGE QuantifiedConstraints #-}
|
||||||
|
#endif
|
||||||
|
|
||||||
-- | @since 0.14.1
|
-- | @since 0.14.1
|
||||||
module Servant.Server.Generic (
|
module Servant.Server.Generic (
|
||||||
AsServerT,
|
AsServerT,
|
||||||
|
@ -113,6 +119,8 @@ genericServerT
|
||||||
-> ToServant routes (AsServerT m)
|
-> ToServant routes (AsServerT m)
|
||||||
genericServerT = toServant
|
genericServerT = toServant
|
||||||
|
|
||||||
|
#if __GLASGOW_HASKELL__ >= 806
|
||||||
|
|
||||||
-- | Set of constraints required to convert to / from vanilla server types.
|
-- | Set of constraints required to convert to / from vanilla server types.
|
||||||
type GServerConstraints api m =
|
type GServerConstraints api m =
|
||||||
( ToServant api (AsServerT m) ~ ServerT (ToServantApi api) m
|
( ToServant api (AsServerT m) ~ ServerT (ToServantApi api) m
|
||||||
|
@ -173,3 +181,5 @@ instance
|
||||||
toServant server
|
toServant server
|
||||||
servantSrvN :: ServerT (ToServantApi api) n =
|
servantSrvN :: ServerT (ToServantApi api) n =
|
||||||
hoistServerWithContext (Proxy @(ToServantApi api)) pctx nat servantSrvM
|
hoistServerWithContext (Proxy @(ToServantApi api)) pctx nat servantSrvM
|
||||||
|
|
||||||
|
#endif
|
||||||
|
|
Loading…
Reference in a new issue