Fwd: [Haskell-cafe] Newbie: generating a truth table

Sigh, I seem to have done a reply to sender. Reposting to the list.
On 06/02/07, phiroc@free.fr
Hello,
I would like to create a Haskell function that generates a truth table, for all Boolean values, say, using the following "and" function :
and :: Bool -> Bool -> Bool and a b = a && b
A fairly old thread, but I had an interesting idea:
combos :: (Enum a, Enum b) => a -> b -> (a -> b -> c) -> [(a, b, c)] combos min1 min2 op = [(x, y, x `op` y) | x <- [min1..], y <- [min2..]]
Then: *Main> combos False (&&) [(False,False,False),(False,True,False),(True,False,False),(True,True,True)] In the case of Bool and a few others, you can use a slightly nicer one:
bCombos :: (Enum a, Bounded a, Enum b, Bounded b) => (a -> b -> c) -> [(a, b, c)] bCombos op = [(x, y, x `op` y) | x <- [minBound..maxBound], y <- [minBound..maxBound]]
And:
*Main> bCombos (&&)
[(False,False,False),(False,True,False),(True,False,False),(True,True,True)]
The secret of these is of course in the Enum and Bounded type classes, which
define, respectively,
* enumFrom and enumFromTo (which have syntactic sugar in [foo..] and [foo..bar]
respectively), and
* minBound and maxBound.
You can do the same with any instance of these classes.
--
Peter Berry

On 2/10/07, Peter Berry
Sigh, I seem to have done a reply to sender. Reposting to the list.
On 06/02/07, phiroc@free.fr
wrote: Hello,
I would like to create a Haskell function that generates a truth table, for all Boolean values, say, using the following "and" function :
and :: Bool -> Bool -> Bool and a b = a && b
This is solution that I used with list comprehension.. combining some of the other ideas on the thread such as a tuple to see the original values and then the result. Prelude> putStrLn $ concatMap (flip (++)"\n") $ map show $ [(x,y,(&&) x y) |x <- [True,False],y <- [True,False]] (True,True,True) (True,False,False) (False,True,False) (False,False,False) gene

On 2/10/07, Peter Berry
wrote: Prelude> putStrLn $ concatMap (flip (++)"\n") $ map show $ [(x,y,(&&) x y) |x <- [True,False],y <- [True,False]]
This can be simplified slightly to: Prelude > putStrLn . unlines . map show $ [(x, y, x && y) | x <- [True, False], y <- [True, False]] - Joe

One possible way to generate the values would be using a generic function
for permutation with repetition, such as:
permuteRep :: [a] -> [b] -> [[(a,b)]]
permuteRep [] _ = []
permuteRep (a:[]) bs = [ [ (a,b) ] | b <- bs ]
permuteRep (a:as) bs = concat [ [ (a,b):p | p <- permuteRep as bs ] | b <-
bs ]
and then use:
lines = permuteRep ["x","y","z"] [False,True]
In case the variable names can be discarded (or, in this case, not generated
... lazy evaluation rox ;-), then:
map (map snd) lines
This avoids having to provide a "domain" for each variable in the list
comprehension, which could be problematic when dealing with many variables
On 2/21/07, Joe Thornber
On 2/10/07, Peter Berry
wrote: Prelude> putStrLn $ concatMap (flip (++)"\n") $ map show $ [(x,y,(&&) x y) |x <- [True,False],y <- [True,False]] This can be simplified slightly to:
Prelude > putStrLn . unlines . map show $ [(x, y, x && y) | x <- [True, False], y <- [True, False]]
- Joe _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ricardo Guimarães Herrmann "Those who do not understand Lisp are doomed to reinvent it, poorly" "Curried food and curried functions are both acquired tastes" "If you think good architecture is expensive, try bad architecture"

On 2007-02-21, Joe Thornber
On 2007-02-10, Peter Berry
wrote: Prelude> putStrLn $ concatMap (flip (++)"\n") $ map show $ [(x,y,(&&) x y) |x <- [True,False],y <- [True,False]] This can be simplified slightly to:
Prelude > putStrLn . unlines . map show $ [(x, y, x && y) | x <- [True, False], y <- [True, False]]
This can be further simplified to: putStrLn $ unlines [show (x, y, x && y) | x <- [True, False], y <- [True, False]] -- Met vriendelijke groet, Henk-Jan van Tuyl -- http://Van.Tuyl.eu/ -- Using Opera's revolutionary e-mail client: https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433
participants (5)
-
Gene A
-
Henk-Jan van Tuyl
-
Joe Thornber
-
Peter Berry
-
Ricardo Herrmann