|
| 1 | +{-# LANGUAGE DataKinds #-} |
| 2 | +{-# LANGUAGE PolyKinds #-} |
| 3 | +{-# LANGUAGE TypeFamilies #-} |
| 4 | +{-# LANGUAGE TypeOperators #-} |
| 5 | +{-# LANGUAGE UndecidableInstances #-} |
| 6 | + |
| 7 | +-- | This module defines the error messages used in type-level errors. |
| 8 | +-- Type-level errors can signal non-existing instances, for instance when |
| 9 | +-- a combinator is not applied to the correct number of arguments. |
| 10 | + |
| 11 | +module Servant.API.TypeErrors ( |
| 12 | + PartialApplication, |
| 13 | + NoInstanceFor, |
| 14 | + NoInstanceForSub, |
| 15 | +) where |
| 16 | + |
| 17 | +import Data.Kind |
| 18 | +import GHC.TypeLits |
| 19 | + |
| 20 | +-- | No instance exists for @tycls (expr :> ...)@ because |
| 21 | +-- @expr@ is not recognised. |
| 22 | +type NoInstanceForSub (tycls :: k) (expr :: k') = |
| 23 | + Text "There is no instance for " :<>: ShowType tycls |
| 24 | + :<>: Text " (" :<>: ShowType expr :<>: Text " :> ...)" |
| 25 | + |
| 26 | +-- | No instance exists for @expr@. |
| 27 | +type NoInstanceFor (expr :: k) = |
| 28 | + Text "There is no instance for " :<>: ShowType expr |
| 29 | + |
| 30 | +-- | No instance exists for @tycls (expr :> ...)@ because @expr@ is not fully saturated. |
| 31 | +type PartialApplication (tycls :: k) (expr :: k') = |
| 32 | + NoInstanceForSub tycls expr |
| 33 | + :$$: ShowType expr :<>: Text " expects " :<>: ShowType (Arity expr) :<>: Text " more arguments" |
| 34 | + |
| 35 | +-- The arity of a combinator, i.e. the number of required arguments. |
| 36 | +type Arity (ty :: k) = Arity' k |
| 37 | + |
| 38 | +type family Arity' (ty :: k) :: Nat where |
| 39 | + Arity' (_ -> ty) = 1 + Arity' ty |
| 40 | + Arity' _ = 0 |
0 commit comments