开发者

Matching multiple data type constructors at once

Lets say we have this type declaration:

data D a = A a | B a | C a | D a | E a | F a

and want to define a function over it which divides the data constructors in 2 sets. It would be nice to write something like that:

g x | x `is` [A,B,C] = 1
    | x `is` [D,E,F] = 2

instead of matching on each constructor separately.

Is there any way to achi开发者_如何学Ceve this? I looked at uniplate but couldn't find a way to do it.


If you often need to match for the same set of constructors, a helper function could be the simplest solution. For example:

getAbc :: D a -> Maybe a
getAbc (A v) = Just v
getAbc (B v) = Just v
getAbc (C v) = Just v
getAbc _     = Nothing

With such a helper function, the definition of g can be simplified like this:

g x = g_ (getAbc x)
  where
    g_ (Just v) = 1
    g_ Nothing  = 2

Or, using the maybe function:

g = maybe 2 (\v -> 1) . getAbc


Edit: If all constructors have the same type of fields, you could abuse Functor:

{-# LANGUAGE DeriveFunctor #-}

data D a = A a | B a | C a | D a | E a | F a
    deriving (Eq, Functor)

isCons :: (Eq (f Int), Functor f) => f a -> (Int -> f Int) -> Bool
isCons k s = fmap (const 42) k == s 42

is :: (Eq (f Int), Functor f) => f a -> [Int -> f Int] -> Bool
is k l = any (isCons k) l

g :: D a -> Int
g x | x `is` [A,B,C] = 1
    | x `is` [D,E,F] = 2

You could try

{-# LANGUAGE DeriveDataTypeable #-}

import Data.Data

data D a = A a | B a | C a | D a | E a | F a
        deriving (Typeable, Data)

g :: Data a => D a -> Int
g x | y `elem` ["A","B","C"] = 1
    | y `elem` ["D","E","F"] = 2
    where y = showConstr (toConstr x)


I've tried to generalize answer of @KennyTM with:

data D a = A a | B a | C a a | D
    deriving (Show, Eq, Functor)

class AutoBind a where
    bindSome :: forall b . (a -> b) -> b

instance AutoBind Bool where bindSome f = f False
instance Num a => AutoBind a where bindSome f = f 0

class AutoConst a b | a -> b where {- bind until target type -}
    bindAll :: a -> b

instance AutoBind a => AutoConst (a -> b) b where bindAll = bindSome
instance (AutoBind a, AutoConst b c) => AutoConst (a -> b) c where bindAll = bindAll . bindSome

isCons :: (Eq (f a), AutoBind a, AutoConst b (f a), Functor f) => f a -> b -> Bool
isCons x y = fmap (bindSome const) x == bindAll y

But by some reason it doesn't work for constructor C


It's a bit of a hack, but how about this, using Data.Data and a "placeholder" type?

{-# LANGUAGE DeriveDataTypeable #-}

import Data.Data 

data X = X deriving (Show, Data, Typeable)
data D a = A a | B a | C a | D a a | E a a | F a a
    deriving (Show, Data, Typeable)


matchCons :: (Data a) => D a -> [D X] -> Bool
matchCons x ys = any ((== xc) . toConstr) ys
    where xc = toConstr x

g :: (Data a) => D a -> Int
g x | matchCons x [A X, B X, C X] = 1
    | matchCons x [D X X, E X X, F X X] = 2

Note that this avoids the issue of type signature/different constructor arity. There's probably a cleaner way to do something similar, as well.


I wish that Haskell patterns would have a way of specifying the "OR" of two patterns, similar to | in OCaml:

(* ocaml code *)
let g x = match x with
            A v | B v | C v -> 1
          | C v | D v | E v -> 2


I had the same question. My solution would be to use a view, though personally I'd like something that's more canonically semantically equivalent (in some of the code I'm writing, laziness preservation is critical, so any extra unneeded pattern matches could render the technique unusable).

{-# LANGUAGE ViewPatterns #-}

data D a = A a | B a | C a | D a | E a | F a
isABC (A v) = Just v
isABC (B v) = Just v
isABC (C v) = Just v
isABC _ = Nothing

f :: D Int -> Int
f (isABC -> Just v) = v
f (isABC -> Nothing) = 0
0

上一篇:

下一篇:

精彩评论

暂无评论...
验证码 换一张
取 消

最新问答

问答排行榜