[commit: ghc] ghc-8.0: users guide: Add documentation for custom compile-time errors (91eddc1)

git at git.haskell.org git at git.haskell.org
Fri Jan 8 11:24:56 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/91eddc13bb2340b32d7642a2d045fc76e150f29d/ghc

>---------------------------------------------------------------

commit 91eddc13bb2340b32d7642a2d045fc76e150f29d
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Wed Jan 6 23:56:44 2016 +0100

    users guide: Add documentation for custom compile-time errors
    
    (cherry picked from commit 568736d757d3e0883b0250e0b948aeed646c20b5)


>---------------------------------------------------------------

91eddc13bb2340b32d7642a2d045fc76e150f29d
 docs/users_guide/glasgow_exts.rst | 66 +++++++++++++++++++++++++++++++++++++--
 1 file changed, 64 insertions(+), 2 deletions(-)

diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst
index 51f84d6..372a033 100644
--- a/docs/users_guide/glasgow_exts.rst
+++ b/docs/users_guide/glasgow_exts.rst
@@ -9599,13 +9599,75 @@ splices.
    supported either.
 
 -  Type splices: only anonymous wildcards are supported in type splices.
-   Named and extra-constraints wildcards are not.
-   ::
+   Named and extra-constraints wildcards are not. ::
 
        {-# LANGUAGE TemplateHaskell #-}
        foo :: $( [t| _ |] ) -> a
        foo x = x
 
+.. _custom-errors:
+
+Custom compile-time errors
+==========================
+
+When designing embedded domain specific languages in Haskell, it is useful to
+have something like ``error`` at the type level. In this way, the EDSL designer
+may show a type error that is specific to the DSL, rather than the standard GHC
+type error.
+
+For example, consider a type class that is not intended to be used with
+functions, but the user accidentally used it at a function type, perhaps
+because they missed an argument to some function. Then, instead of getting the
+standard GHC message about a missing instance, it would be nicer to emit a more
+friendly message specific to the EDSL. Similarly, the reduction of a type-level
+function may get stuck due to an error, at which point it would be nice to
+report an EDSL specific error, rather than a generic error about an ambiguous
+type.
+
+To solve this, GHC provides a single type-level function, ::
+
+    type family TypeError (msg :: ErrorMessage) :: k
+
+along with a small type-level language (via
+``DataKinds`` :ref:`promotion <promotion>`)
+for constructing pretty-printed error messages, ::
+
+    -- ErrorMessage is intended to be used as a kind
+    data ErrorMessage =
+          Text Symbol                        -- Show this text as is
+        | forall t. ShowType t               -- Pretty print a type
+        | ErrorMessage :<>: ErrorMessage     -- Put two chunks of error message next to each other
+        | ErrorMessage :$$: ErrorMessage     -- Put two chunks of error message above each other
+
+in the ``GHC.TypeLits`` :base-ref:`module <GHC-TypeList.html>`.
+
+For instance, we might use this interface to provide a more useful error
+message for applications of ``show`` on unsaturated functions like this, ::
+
+    {-# LANGUAGE DataKinds #-}
+    {-# LANGUAGE TypeOperators #-}
+    {-# LANGUAGE UndecidableInstances #-}
+
+    import GHC.TypeLits
+
+    instance TypeError (Text "Cannot 'Show' functions." :$$:
+                        Text "Perhaps there is a missing argument?")
+             => Show (a -> b) where
+       showsPrec = error "unreachable"
+
+    main = print negate
+
+Which will produce the following compile-time error,
+
+.. code-block:: none
+
+    Test.hs:12:8: error:
+        • Cannot 'Show' functions.
+          Perhaps there is a missing argument?
+        • In the expression: print negate
+          In an equation for ‘main’: main = print negate
+
+
 .. _defer-type-errors:
 
 Deferring type errors to runtime



More information about the ghc-commits mailing list