Hi David,

I don't think this is well-typed. GHC seems to infer `Proposition a -> Bool -> Bool` (by majority vote?) but obviously then complains about the cases `id` and `not`.

I believe that there is a way to do this with dependent types, but not sure whether this is possible in Haskell.

Best,

Vilem

On 2018-02-15, at 13:51, David Fox <dsf@seereason.com> wrote:

You actually can pattern match on constructor only:

magic = \case
    Var {} -> id
    Not  {}-> not
    And {} -> (&&)
    Or {} -> (||)
    If {} -> (==>)
    Iff {} -> (==)

On Sun, Feb 11, 2018 at 6:30 PM, Vilem-Benjamin Liepelt <vl81@kent.ac.uk> wrote:
Hi,

I am looking for a solution to get rid of this silly boilerplate:

eval :: Ord var => Map var Bool -> Proposition var -> Bool
eval ctx prop = evalP $ fmap (ctx Map.!) prop
  where
    evalP = \case
        Var b -> b
        Not q -> not $ evalP q
        And p q -> evalP p && evalP q
        Or p q -> evalP p || evalP q
        If p q -> evalP p ==> evalP q
        Iff p q -> evalP p == evalP q

What I would like to do in essence is to replace the data constructors like so:

-- Not valid Haskell!! Can't pattern match on constructor only...
magic = \case
    Var -> id
    Not -> not
    And -> (&&)
    Or -> (||)
    If -> (==>)
    Iff -> (==)

compile = transformAST magic $ fmap (\case 'P' -> False; 'Q' -> True)

>>> compile (Iff (Not (And (Var 'P') (Var 'Q'))) (Or (Not (Var 'P')) (Not (Var 'Q'))))
            ((==) (not ((&&) (id True) (id False))) ((||) (not (id True)) (not (id False))))

Note how the compiled expression exactly mirrors the AST, so there should be some meta programming technique for this.

Does anyone have an idea how I can achieve this?


I am happy to take any other comments relating to my code...

Best,

Vilem

_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.