[Haskell-cafe] Check a lack of a constraint?
Viktor Dukhovni
ietf-dane at dukhovni.org
Mon Jul 12 20:59:46 UTC 2021
> On 12 Jul 2021, at 4:24 pm, Viktor Dukhovni <ietf-dane at dukhovni.org> wrote:
>
> However, it is possible to get something along those lines with
> a closed type family and an explicit list of verboten types:
Somewhat cleaner (no complaints from -Wall, and the Filtered type family
now returns a constraint):
{-# LANGUAGE ConstraintKinds
, DataKinds
, FlexibleContexts
, TypeFamilies
, TypeOperators
, UndecidableInstances
#-}
import GHC.TypeLits (ErrorMessage(..), TypeError)
import Data.Kind (Constraint)
type family Filtered a :: Constraint where
Filtered Int = TypeError ('ShowType Int ':<>: 'Text "s not welcome here")
Filtered a = ()
foo :: (Show a, Filtered a) => a -> String
foo = show
--
Viktor.
More information about the Haskell-Cafe
mailing list