Difference between revisions of "Haskell Quiz/Constraint Processing/Solution Jethr0"

From HaskellWiki
Jump to navigation Jump to search
m (infixing "List")
(sharpen cat)
 
(One intermediate revision by one other user not shown)
Line 1: Line 1:
[[Category:Code]]
+
[[Category:Haskell Quiz solutions|Constraint Processing]]
   
 
Basically there's nothing to be done in haskell for this quiz.
 
Basically there's nothing to be done in haskell for this quiz.
Line 37: Line 37:
   
 
<haskell>
 
<haskell>
data List a = List a (List a) | Empty deriving (Show)
+
data List a = a ::: (List a) | Empty deriving (Show)
   
 
foldrL :: (a->b->b) -> b -> List a -> b
 
foldrL :: (a->b->b) -> b -> List a -> b
 
foldrL _ start Empty = start
 
foldrL _ start Empty = start
foldrL f start (List x xs) = f x (foldrL f start xs)
+
foldrL f start (x ::: xs) = f x (foldrL f start xs)
   
 
appendL :: List a -> List a -> List a
 
appendL :: List a -> List a -> List a
appendL xs ys = foldrL List ys xs
+
appendL xs ys = foldrL (:::) ys xs
   
 
concatL :: List (List a) -> List a
 
concatL :: List (List a) -> List a
Line 50: Line 50:
   
 
instance Functor List where
 
instance Functor List where
fmap f = foldrL (\a b -> f a `List` b) Empty
+
fmap f = foldrL (\a b -> f a ::: b) Empty
   
 
instance Monad List where
 
instance Monad List where
return x = x `List` Empty
+
return x = x ::: Empty
 
l >>= f = concatL . fmap f $ l
 
l >>= f = concatL . fmap f $ l
   
Line 62: Line 62:
 
range :: (Integral a) => a -> a -> List a
 
range :: (Integral a) => a -> a -> List a
 
range from to | from > to = Empty
 
range from to | from > to = Empty
| from == to = to `List` Empty
+
| from == to = to ::: Empty
| otherwise = from `List` range (from+1) to
+
| otherwise = from ::: range (from+1) to
   
 
constr' = do a <- range 0 4
 
constr' = do a <- range 0 4

Latest revision as of 10:45, 13 January 2007


Basically there's nothing to be done in haskell for this quiz.

As the List Monad already provides non-deterministic evaluation with "guard" as a description of constraints, you really just have to write the problem in the List Monad and be done with it.

Of course one could write all kinds of wrapping hackery, but I think from the standpoint of usability and conciseness the built-in behaviour of haskell is already pretty optimal.


constr = do a <- [0..4]
            b <- [0..4]
            c <- [0..4]
            guard (a < b)
            guard (a + b == c)
            return ("a:",a,"b:",b,"c:",c)

{- 
> constr
[("a:",0,"b:",1,"c:",1)
,("a:",0,"b:",2,"c:",2)
,("a:",0,"b:",3,"c:",3)
,("a:",0,"b:",4,"c:",4)
,("a:",1,"b:",2,"c:",3)
,("a:",1,"b:",3,"c:",4)]
-}


Obviously, solving a problem with built-in functionality always feels a little like cheating, because it's "pure chance" that the solution to the problem is already built-in.

So, for the sake of argument and because I was bored here's the same solution under the premise that haskell's List Monad didn't already exist.

Unfortunately I "had" to reimplement a fair bit of the Prelude, but that's what happens if you start creating unrealistic scenarios :). Of course, the "do" notation is also kind of a built-in, but representing it with bind (>>=) only made is less nice to look at.

data List a = a ::: (List a) | Empty deriving (Show)

foldrL :: (a->b->b) -> b -> List a -> b
foldrL _ start Empty       = start
foldrL f start (x ::: xs) = f x (foldrL f start xs)

appendL :: List a -> List a -> List a
appendL xs ys = foldrL (:::) ys xs

concatL :: List (List a) -> List a
concatL = foldrL appendL Empty

instance Functor List where
    fmap f = foldrL (\a b -> f a ::: b) Empty

instance Monad List where
    return x = x ::: Empty
    l >>= f  = concatL . fmap f $ l

instance MonadPlus List where
    mzero = Empty
    mplus = appendL

range :: (Integral a) => a -> a -> List a
range from to | from > to  = Empty
              | from == to = to ::: Empty
              | otherwise  = from ::: range (from+1) to

constr' = do a <- range 0 4
             b <- range 0 4
             c <- range 0 4
             guard (a < b)
             guard (a + b == c)
             return (a,b,c)