[Haskell-cafe] Check a lack of a constraint?

Hécate hecate at glitchbra.in
Tue Jul 13 06:46:42 UTC 2021


Oh, very nice approach Viktor. It really seems easier than having a 
custom typeclass for which the blessed types have an instance, if the 
set of verboten types is considerably smaller than the set of allowed types.

Le 12/07/2021 à 22:59, Viktor Dukhovni a écrit :
>
>> 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
>
-- 
Hécate ✨
🐦: @TechnoEmpress
IRC: Hecate
WWW: https://glitchbra.in
RUN: BSD



More information about the Haskell-Cafe mailing list