-
-
Notifications
You must be signed in to change notification settings - Fork 412
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Type-level errors for HasLink for invalid combinators
- Loading branch information
Andrea Condoluci
committed
Nov 15, 2021
1 parent
48bc247
commit 42b7d0e
Showing
3 changed files
with
55 additions
and
1 deletion.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,40 @@ | ||
{-# LANGUAGE DataKinds #-} | ||
{-# LANGUAGE PolyKinds #-} | ||
{-# LANGUAGE TypeFamilies #-} | ||
{-# LANGUAGE TypeOperators #-} | ||
{-# LANGUAGE UndecidableInstances #-} | ||
|
||
-- | This module defines the error messages used in type-level errors. | ||
-- Type-level errors can signal non-existing instances, for instance when | ||
-- a combinator is not applied to the correct number of arguments. | ||
|
||
module Servant.API.TypeErrors ( | ||
PartialApplication, | ||
NoInstanceFor, | ||
NoInstanceForSub, | ||
) where | ||
|
||
import Data.Kind | ||
import GHC.TypeLits | ||
|
||
-- | No instance exists for @tycls (expr :> ...)@ because | ||
-- @expr@ is not recognised. | ||
type NoInstanceForSub (tycls :: k) (expr :: k') = | ||
Text "There is no instance for " :<>: ShowType tycls | ||
:<>: Text " (" :<>: ShowType expr :<>: Text " :> ...)" | ||
|
||
-- | No instance exists for @expr@. | ||
type NoInstanceFor (expr :: k) = | ||
Text "There is no instance for " :<>: ShowType expr | ||
|
||
-- | No instance exists for @tycls (expr :> ...)@ because @expr@ is not fully saturated. | ||
type PartialApplication (tycls :: k) (expr :: k') = | ||
NoInstanceForSub tycls expr | ||
:$$: ShowType expr :<>: Text " expects " :<>: ShowType (Arity expr) :<>: Text " more arguments" | ||
|
||
-- The arity of a combinator, i.e. the number of required arguments. | ||
type Arity (ty :: k) = Arity' k | ||
|
||
type family Arity' (ty :: k) :: Nat where | ||
Arity' (_ -> ty) = 1 + Arity' ty | ||
Arity' _ = 0 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters