Redundant import fixes

This commit is contained in:
Julian K. Arni 2016-08-22 12:24:36 -03:00 committed by Oleg Grenrus
parent e0cd899e06
commit 92b1196830
4 changed files with 54 additions and 7 deletions

View File

@ -37,13 +37,11 @@ import Data.Ord (comparing)
import Data.Proxy (Proxy(Proxy))
import Data.String.Conversions (cs)
import Data.Text (Text, unpack)
import GHC.Exts (Constraint)
import GHC.Generics
import GHC.TypeLits
import Servant.API
import Servant.API.ContentTypes
import Servant.API.TypeLevel
import Servant.Utils.Links
import qualified Data.HashMap.Strict as HM
import qualified Data.Text as T

View File

@ -16,7 +16,6 @@ import Data.Proxy
import Data.String
import Data.Text
import Data.Text.Encoding (decodeUtf8)
import GHC.Exts (Constraint)
import GHC.TypeLits
import qualified Network.HTTP.Types as HTTP
import Prelude hiding (concat)

View File

@ -1,8 +1,11 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
module Servant.API.TypeLevel where
@ -14,6 +17,9 @@ import Servant.API.Header ( Header )
import Servant.API.Verbs ( Verb )
import Servant.API.Sub ( type (:>) )
import Servant.API.Alternative ( type (:<|>) )
#if MIN_VERSION_base(4,9,0)
import GHC.TypeLits (TypeError, ErrorMessage(..))
#endif
-- * API predicates
@ -104,9 +110,24 @@ type family IsSubList a b :: Constraint where
IsSubList '[] b = ()
IsSubList (x ': xs) y = Elem x y `And` IsSubList xs y
type family Elem e es :: Constraint where
Elem x (x ': xs) = ()
Elem y (x ': xs) = Elem y xs
-- | Check that an eleme is an element of a list:
--
-- >>> ok (Proxy :: Proxy (Elem Bool '[Int, Bool]))
-- OK
--
-- >>> ok (Proxy :: Proxy (Elem String '[Int, Bool]))
-- ...
-- No instance for (ElemNotFoundIn [Char] '[Int, Bool])
-- arising from a use of ok
-- ...
type Elem e es = ElemGo e es es
-- 'orig' is used to store original list for better error messages
type family ElemGo e es orig :: Constraint where
ElemGo x (x ': xs) orig = ()
ElemGo y (x ': xs) orig = ElemGo y xs orig
ElemGo x '[] orig = ElemNotFoundIn x orig
-- ** Logic
@ -121,3 +142,33 @@ type family Or (a :: Constraint) (b :: Constraint) :: Constraint where
type family And (a :: Constraint) (b :: Constraint) :: Constraint where
And () () = ()
-- * Custom type errors
#if MIN_VERSION_base(4,9,0)
-- GHC >= 8
type ElemNotFoundIn val list = TypeError
(ShowType val :<>: Text " expected in list " :<>: ShowList list)
-- Utilities
type family ShowListGo ls :: ErrorMessage where
ShowListGo '[] = Text ""
ShowListGo (x ': xs) = ShowType x :<>: Text ", " :<>: ShowListGo xs
type ShowList ls = Text "[" :<>: ShowListGo ls :<>: Text "]"
#else
-- GHC < 8
class ElemNotFoundIn val list
#endif
-- $setup
-- >>> import Data.Proxy
-- >>> data OK = OK deriving (Show)
-- >>> let ok :: ctx => Proxy ctx -> OK; ok _ = OK

View File

@ -10,7 +10,6 @@ import Test.Hspec (Expectation, Spec, describe, it,
import Data.String (fromString)
import Servant.API
import Servant.API.TypeLevel
type TestApi =
-- Capture and query params