[Haskell-cafe] Best way to return Bool based on a successful pattern match?

Erik Hesselink hesselink at gmail.com
Mon Jul 13 14:06:40 UTC 2015


You can write a generic 'is constructor' function using GHC Generics,
if you want:

{-# LANGUAGE
    DeriveGeneric
  , FlexibleContexts
  , FlexibleInstances
  , FunctionalDependencies
  , MultiParamTypeClasses
  , UndecidableInstances
  #-}

import GHC.Generics
import Generics.Deriving.ConNames

class SameType a b | b -> a where
  saturate :: b -> a

instance SameType a a where
  saturate = id

instance SameType a b => SameType a (c -> b) where
  saturate f = saturate (f undefined)

is :: (ConNames (Rep a), Generic a, SameType a b) => b -> a -> Bool
is ctor val = conNameOf val == conNameOf (saturate ctor)

Now you can do things like:

data Foo = A | B Int
  deriving (Show, Generic)

*Main> is A A
True
*Main> is A (B 1)
False
*Main> is B A
False
*Main> is B (B 2)
True

Erik

On Mon, Jul 13, 2015 at 3:40 PM, Nikolay Amiantov <ab at fmap.me> wrote:
> A nice idea! It can be helpful in some cases, although usually I have
> more complex patterns, for example "get all DataDefinitions from a list
> of TopLevelDefinitions parsed from a .hs file" or "filter all KeyPresses
> directed to a particular window from an Event stream".
>
> On 07/13/2015 04:24 PM, Adam Bergmark wrote:
>> Perhaps this is of interest to
>> you, http://hackage.haskell.org/package/generic-maybe
>>
>> HTH,
>> Adam
>
> --
> Nikolay.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list