
Very interesting trick, thanks, it feels closer to what I've imagined! Meanwhile I've played with quasi-quoters and TH a bit for the sake of experiment. As a result I got this: https://github.com/abbradar/isit/blob/master/src/Language/Haskell/IsIt.hs It allows one to do very nice-looking checks, like: λ filter [is|Left (Just 4)|] [Right "test", Left (Just 4), Left Nothing] [Left (Just 4)] λ let x = 4 λ filter [is|Left (Just x)|] [Right "test", Left (Just 4), Left Nothing] [Left (Just 4)] λ :t [is|Just _|] [is|Just _|] :: Maybe t -> Bool I doubt anyone including me would actually use this though -- it depends on haskell-src-{exts,meta} which you probably don't want as yet more dependencies for your project to do such a trivial task. On 07/13/2015 05:06 PM, Erik Hesselink wrote:
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 -- Nikolay.