Writing a polymorphic function in Haskell

Dear All, I am having problems writing a polymorphic function. I have a type that has two constructors: data Arg = IndArg {evi::Evi, t1::Treatment, t2::Treatment, out::Outcome, dir::Direction} | MetaArg {target::EviType} deriving (Show) I have a function checks for conflict: checkConflict :: Arg -> Arg -> Bool checkConflict a b = if t1 a == t1 b && t2 a == t2 b && dir a /= dir b then True else False However, I can't make this work with both types of Argument - if I pass it MetaArg, it raises an error. In another language, I would write something like: checkConflict(ArgA,ArgB):

Apologies - sent too soon - code edited below Dear All,
I am having problems writing a polymorphic function.
I have a type that has two constructors:
data Arg = IndArg {evi::Evi, t1::Treatment, t2::Treatment, out::Outcome, dir::Direction} | MetaArg {target::EviType} deriving (Show)
I have a function checks for conflict:
checkConflict :: Arg -> Arg -> Bool checkConflict a b = if t1 a == t1 b && t2 a == t2 b && dir a /= dir b then True else False
However, I can't make this work with both types of Argument - if I pass it MetaArg, it raises an error.
In another language, I would write something like:
checkConflict(ArgA,ArgB):
if type(ArgA) == IndArg: <do this> elif type(ArgA) == MetaArg: <do other> Any thoughts would be welcomed. BW, Matt

Not tested but maybe adding an Eq instance to your datatype would help? So
try changing 'deriving (Show)' to 'deriving (Show, Eq)'.
On Fri, Sep 22, 2017 at 2:55 PM, Matt Williams wrote: Apologies - sent too soon - code edited below Dear All, I am having problems writing a polymorphic function. I have a type that has two constructors: data Arg = IndArg {evi::Evi, t1::Treatment, t2::Treatment, out::Outcome,
dir::Direction}
| MetaArg {target::EviType}
deriving (Show) I have a function checks for conflict: checkConflict :: Arg -> Arg -> Bool
checkConflict a b = if t1 a == t1 b && t2 a == t2 b && dir a /= dir b
then True
else False However, I can't make this work with both types of Argument - if I pass
it MetaArg, it raises an error. In another language, I would write something like: checkConflict(ArgA,ArgB): if type(ArgA) == IndArg:
<do this>
elif type(ArgA) == MetaArg:
<do other> Any thoughts would be welcomed. BW,
Matt _______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

It is a mistake to use record syntax with data types with multiple
constructors. It creates a partial function that dies when you try to
use it on a constructor that does not have that field. It is a flaw
in the language that many people would like to see removed because it
allows programs to compile that will fail at run time, possibly
unexpectedly.
Arg can have a constructor that does not have an evi. Also what
happens if you compare an IndArg to a MetaArg? Or a MetaArg to
another MetaArg?
You should remove all of these record names, and then write
checkConflict as follows (warning untested):
checkConflict :: Arg -> Arg -> Bool
checkConflict (IndArg _ at1 at2 _ adir) (IndArg _ bt1 bt2 _ bdir) =
at1 == bt1 && at2 == bt2 && adir /= bdir
-- checkConflict (IndArg ...) (MetaArg) = ???
-- checkConflict a@(MetaArg ...) b@(IndArg ...) = checkConflict b a
-- checkConflict (MetaArg _) (MetaArg _) = ???
checkConflict _ _ -> False -- perhaps a catchall?
However, you may keep the records as long as you are absolutely sure
you are using them only in places where you have the appropriate
constructor.
On Fri, Sep 22, 2017 at 3:53 PM, Matt Williams
Dear All,
I am having problems writing a polymorphic function.
I have a type that has two constructors:
data Arg = IndArg {evi::Evi, t1::Treatment, t2::Treatment, out::Outcome, dir::Direction} | MetaArg {target::EviType} deriving (Show)
I have a function checks for conflict:
checkConflict :: Arg -> Arg -> Bool checkConflict a b = if t1 a == t1 b && t2 a == t2 b && dir a /= dir b then True else False
However, I can't make this work with both types of Argument - if I pass it MetaArg, it raises an error.
In another language, I would write something like:
checkConflict(ArgA,ArgB):
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Dear All,
Thanks so much for your help. It was largely a syntactic issue around
pattern matching - but I also learnt about the @ operator for
patter-matching.
The correct code is posted below in case it helps anyone else. The only
other think would be to rewrite eviCheck as an inline function using where,
but I am happy with this for now.
Thanks for your speedy help.
BW,
Matt
checkConflict3 :: Arg -> Arg -> Bool
checkConflict3 (IndArg _ at1 at2 _ adir) (IndArg _ bt1 bt2 _ bdir) =
if at1 == bt1 && at2 == bt2 && adir /= bdir then True
else if at1 == bt2 && at2 == bt1 && revDir (adir) /= bdir then True
else False
checkConflict3 (IndArg e _ _ _ _) (MetaArg a) = eviCheck e a
checkConflict3 a@(MetaArg a) b@(IndArg e _ _ _ _) = eviCheck b a
checkConflict3 (MetaArg _) (MetaArg _) = False
checkConflict3 _ _ = False --A final catchall
eviCheck:: Evi -> EviType -> Bool
eviCheck (SimpEvi _ _ _ _ type1) type2 = if type1 == type2 then True
else False
On 22 September 2017 at 21:16, David McBride
It is a mistake to use record syntax with data types with multiple constructors. It creates a partial function that dies when you try to use it on a constructor that does not have that field. It is a flaw in the language that many people would like to see removed because it allows programs to compile that will fail at run time, possibly unexpectedly.
Arg can have a constructor that does not have an evi. Also what happens if you compare an IndArg to a MetaArg? Or a MetaArg to another MetaArg?
You should remove all of these record names, and then write checkConflict as follows (warning untested):
checkConflict :: Arg -> Arg -> Bool checkConflict (IndArg _ at1 at2 _ adir) (IndArg _ bt1 bt2 _ bdir) = at1 == bt1 && at2 == bt2 && adir /= bdir -- checkConflict (IndArg ...) (MetaArg) = ??? -- checkConflict a@(MetaArg ...) b@(IndArg ...) = checkConflict b a -- checkConflict (MetaArg _) (MetaArg _) = ??? checkConflict _ _ -> False -- perhaps a catchall?
However, you may keep the records as long as you are absolutely sure you are using them only in places where you have the appropriate constructor.
Dear All,
I am having problems writing a polymorphic function.
I have a type that has two constructors:
data Arg = IndArg {evi::Evi, t1::Treatment, t2::Treatment, out::Outcome, dir::Direction} | MetaArg {target::EviType} deriving (Show)
I have a function checks for conflict:
checkConflict :: Arg -> Arg -> Bool checkConflict a b = if t1 a == t1 b && t2 a == t2 b && dir a /= dir b
On Fri, Sep 22, 2017 at 3:53 PM, Matt Williams
wrote: then True else False
However, I can't make this work with both types of Argument - if I pass it MetaArg, it raises an error.
In another language, I would write something like:
checkConflict(ArgA,ArgB):
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (3)
-
aditya siram
-
David McBride
-
Matt Williams