[Haskell-cafe] Question about function on data type

Mike Gunter m at ryangunter.com
Wed Sep 29 14:26:46 EDT 2004


There's the following alternative.

	mike

data TermOp     = TermAnd | TermOr deriving (Show, Eq)
data Term       = Not Term 
                | Op Term TermOp Term
                | Literal Char deriving Show

assoc (Op (Op t1 op1_2 t2) op12_3 t3) | op1_2 == op12_3 = Op t1 op1_2 (Op t2 op1_2 t3)
assoc t                                                 = t
                                                        
(&&&) = (`Op` TermAnd)
(|||) = (`Op` TermOr)
tlA     = Literal 'A'
tlB     = Literal 'B'
tlC     = Literal 'B'
tt1     = Not tlA &&& tlB	-- Should not assoc.
tt2     = tt1 &&& tlC		-- Should assoc.
tt3     = tt1 ||| tlC		-- Should not assoc.
tests   = putStr $ unlines $ map (show . (\t -> (t, assoc t))) [tt1, tt2, tt3]



> Hello!
> My question concerns a general term datatype:
> data Term 
>   = Not Term
>    | Term :&&: Term
>    | Term :||: Term
>    | Literal Char
>
> Is it somehow possible to write a generic function that applies the 
> associativity rules on a "Term" (by using pattern matching) and works with 
> both data constructors or is it necessary to write one for :&&: and :||: ?
>
> Something like:
> assoc :: Term -> Term
> assoc ((t1 `op` t2) `op` t3)  = .... -- this doesn't work


More information about the Haskell-Cafe mailing list