
Pattern matching 'works' simply because all it does is what it
describes: it scrutinizes or 'matches' a value of a specific type
against a set constructors of that type.
The classic way to circumvent this is to put the datatype behind a
module, where only the type is exported, but none of the constructors
are exported:
-- Note the difference between the export 'Foo(..)' and just 'Foo' -
-- one exposes the type and all its constructors, the other exposes only
-- the type.
module HiddenType ( Foo, mySpecialEquality ) where
data Foo = Bar ... -- no 'deriving Eq'
-- a special, super secret equality function, so clients can't create
-- their own or try to.
mySpecialEquality :: Foo -> Foo -> Bool
mySpecialEquality = ...
module Main where
import Foo
-- this is invalid, as 'Bar' is not exported and thus not in scope, no
pattern matching allowed.
f :: Foo -> ...
f Bar = ...
More generally this kind of idiom is found when you deal with what you
call 'smart constructors' - functions which, like a constructor,
create a value of a specific data type. But instead of doing it via
the constructor itself, you make the type opaque, and export functions
that construct values in the sensible or correct way:
module Even (Even, makeFoo) where
-- the underlying Int should only be even
data Even = Even Int deriving (Eq, Show)
-- safe, smart constructor for the Even datatype
makeEven :: Int -> Maybe Even
makeEven x = if not (x `mod` 2 == 0) then Nothing else Just x
Hope it helps.
On Mon, Jul 18, 2011 at 7:44 PM, Tom Murphy
Hi list! When I define an algebraic datatype without an instance for Eq, I'm obviously unable to use the (==) function on it. I can pattern-match with a series of function definitions (f [] = False; f x = True) on the expression, though. Why is that? I understand that in the second case I'm not literally using the (==) function, but it seems like there would be instances where you'd intentionally not want to be able to test for equality, and pattern-matching with multiple function definitions circumvents that.
Thanks for your time, Tom
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Regards, Austin