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

2007-02-21 Thread Henk-Jan van Tuyl


On 2007-02-21, Joe Thornber <[EMAIL PROTECTED]> wrote:


> On 2007-02-10, Peter Berry <[EMAIL PROTECTED]> 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-21 Thread Ricardo Herrmann

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 <[EMAIL PROTECTED]> wrote:


> On 2/10/07, Peter Berry <[EMAIL PROTECTED]> 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"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-21 Thread Joe Thornber

On 2/10/07, Peter Berry <[EMAIL PROTECTED]> 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


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

2007-02-20 Thread Gene A

On 2/10/07, Peter Berry <[EMAIL PROTECTED]> wrote:


Sigh, I seem to have done a reply to sender. Reposting to the list.

On 06/02/07, [EMAIL PROTECTED] <[EMAIL PROTECTED]> 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-06 Thread Nicolas Frisby

You were very close! Try

 mapM putStrLn pImpliesQAndQImpliesRLoopShow >> return ()

Note the M on in mapM. That should do it for you.

On 2/6/07, Philippe de Rochambeau <[EMAIL PROTECTED]> wrote:

Hello,

the following code


---
import Stdm -- From "Discrete Mathematics Using a Computer", by
Cordelia Hall and John O'Donnell.

pImpliesQAndR :: [Bool] -> Bool
pImpliesQAndR (p:q:r:[]) = p ==> ( q /\ r )

pImpliesQAndQImpliesR :: [Bool] -> Bool
pImpliesQAndQImpliesR (p:q:r:[]) = ( p ==> q ) /\ ( q ==> r )

pImpliesQAndRLoop = [ ( (p, q, r), pImpliesQAndR [p, q, r] ) | p <-
[True, False], q <- [True, False], r <- [True,False] ]
pImpliesQAndQImpliesRLoop = [ ( (p, q, r), pImpliesQAndQImpliesR [p,
q, r] ) | p <- [True, False], q <- [True, False], r <- [True,False] ]

pImpliesQAndRLoopShow = [ "pImpliesQAndR"  ++ show x ++ " = " ++ show
xs | (x,xs) <- pImpliesQAndRLoop ]
pImpliesQAndQImpliesRLoopShow = [ "pImpliesQAndQImpliesR" ++ show x +
+ " = " ++ show xs | (x,xs) <- pImpliesQAndQImpliesRLoop ]

---

returns


---
["pImpliesQAndR(True,True,True) = True","pImpliesQAndR
(True,True,False) = False","pImpliesQAndR(True,False,True) =
False","pImpliesQAndR(True,False,False) = False","pImpliesQAndR
(False,True,True) = True","pImpliesQAndR(False,True,False) =
True","pImpliesQAndR(False,False,True) = True","pImpliesQAndR
(False,False,False) = True"]

---

when I type


---
pImpliesQAndRLoopShow

---

I still can't figure out how to write a function that loops through
the string items in the list returned by pImpliesQAndRLoopShow and
pImpliesQAndQImpliesRLoopShow, and print them separated by carriage
returns, thus

pImpliesQAndR(True,True,True) = True
pImpliesQAndR(True,True,False) = False


I have tried


---
map (putStrLn) pImpliesQAndRLoopShow

---

but that results in the following error message:


---
:1:0:
 No instance for (Show (IO ()))
   arising from use of `print' at :1:0-33
 Possible fix: add an instance declaration for (Show (IO ()))
 In the expression: print it
 In a 'do' expression: print it
*Main>

---

Any help would be appreciated.

Cheers,

phiroc






On 6 févr. 07, at 10:32, Ketil Malde wrote:

> [EMAIL PROTECTED] wrote:
>> Ketil,
>>
>> thanks for you help.
>>
>> Here's the code:
>>
>> and2 :: Bool -> Bool -> Bool
>> and2 a b = a && b
>>
>>
>> loop = [ and2 x y  | x <- [True,False], y <- [True,False] ]
>>
>>
>> Now, how do I have Haskell print
>>
>> printStrLn("True and True = ") + 
>> printStrLn("True and False = ") + 
>>
> Well, if you keep x and y in the table as well, either as a triple
> (x, y, and2 x y) or a nested tuple ((x,y), and2 x y) (which would
> let you use the lookup function), you can define a function that
> converts such a tuple to the approprate string.  Keep in mind
> that Bool has a Show instance, so that e.g. show True => "True",
> and use ++ to join two strings.
>
> Then, you can 'map' this function on the table to get a list of
> strings
> corresponding to table rows, and use 'concat' or 'unlines'.  When you
> have a result you're happy with, you feed it to putStrLn.
>
> -k
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-06 Thread Yitzchak Gale

Philippe de Rochambeau wrote:

I have tried
map (putStrLn) pImpliesQAndRLoopShow
but that results in the following error message:


Try

mapM_ putStrLn pImpliesQAndRLoopShow

or

putStrLn $ unlines pImpliesQAndRLoopShow

Regards,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-06 Thread Philippe de Rochambeau

Hello,

the following code

 
---
import Stdm -- From "Discrete Mathematics Using a Computer", by  
Cordelia Hall and John O'Donnell.


pImpliesQAndR :: [Bool] -> Bool
pImpliesQAndR (p:q:r:[]) = p ==> ( q /\ r )

pImpliesQAndQImpliesR :: [Bool] -> Bool
pImpliesQAndQImpliesR (p:q:r:[]) = ( p ==> q ) /\ ( q ==> r )

pImpliesQAndRLoop = [ ( (p, q, r), pImpliesQAndR [p, q, r] ) | p <-  
[True, False], q <- [True, False], r <- [True,False] ]
pImpliesQAndQImpliesRLoop = [ ( (p, q, r), pImpliesQAndQImpliesR [p,  
q, r] ) | p <- [True, False], q <- [True, False], r <- [True,False] ]


pImpliesQAndRLoopShow = [ "pImpliesQAndR"  ++ show x ++ " = " ++ show  
xs | (x,xs) <- pImpliesQAndRLoop ]
pImpliesQAndQImpliesRLoopShow = [ "pImpliesQAndQImpliesR" ++ show x + 
+ " = " ++ show xs | (x,xs) <- pImpliesQAndQImpliesRLoop ]
 
---


returns

 
---
["pImpliesQAndR(True,True,True) = True","pImpliesQAndR 
(True,True,False) = False","pImpliesQAndR(True,False,True) =  
False","pImpliesQAndR(True,False,False) = False","pImpliesQAndR 
(False,True,True) = True","pImpliesQAndR(False,True,False) =  
True","pImpliesQAndR(False,False,True) = True","pImpliesQAndR 
(False,False,False) = True"]
 
---


when I type

 
---

pImpliesQAndRLoopShow
 
---


I still can't figure out how to write a function that loops through  
the string items in the list returned by pImpliesQAndRLoopShow and  
pImpliesQAndQImpliesRLoopShow, and print them separated by carriage  
returns, thus


pImpliesQAndR(True,True,True) = True
pImpliesQAndR(True,True,False) = False


I have tried

 
---

map (putStrLn) pImpliesQAndRLoopShow
 
---


but that results in the following error message:

 
---

:1:0:
No instance for (Show (IO ()))
  arising from use of `print' at :1:0-33
Possible fix: add an instance declaration for (Show (IO ()))
In the expression: print it
In a 'do' expression: print it
*Main>
 
---


Any help would be appreciated.

Cheers,

phiroc






On 6 févr. 07, at 10:32, Ketil Malde wrote:


[EMAIL PROTECTED] wrote:

Ketil,

thanks for you help.

Here's the code:

and2 :: Bool -> Bool -> Bool
and2 a b = a && b


loop = [ and2 x y  | x <- [True,False], y <- [True,False] ]


Now, how do I have Haskell print

printStrLn("True and True = ") + 
printStrLn("True and False = ") + 


Well, if you keep x and y in the table as well, either as a triple
(x, y, and2 x y) or a nested tuple ((x,y), and2 x y) (which would
let you use the lookup function), you can define a function that
converts such a tuple to the approprate string.  Keep in mind
that Bool has a Show instance, so that e.g. show True => "True",
and use ++ to join two strings.

Then, you can 'map' this function on the table to get a list of  
strings

corresponding to table rows, and use 'concat' or 'unlines'.  When you
have a result you're happy with, you feed it to putStrLn.

-k



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-06 Thread Martin DeMello

On 2/6/07, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:

Hello,

how would you convert Boolean triples to strings, in the IO function?

printStrings :: (Bool,Bool,Bool) -> IO ()


Take a look at 'show':

Prelude> show True
"True"

martin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-06 Thread phiroc
Hello,

how would you convert Boolean triples to strings, in the IO function?

printStrings :: (Bool,Bool,Bool) -> IO ()


phiroc


Quoting Lennart Augustsson <[EMAIL PROTECTED]>:

> It would be better to produce a triple (as was suggested)
>
> loop = [(x, y, x&&y) | x <- [True, False], y <- [True, False]]
>
> The you can map a function that prints over that.  Or even better
> map a function that generates the strings, and the use one big
> putStr at the end.  Always try to separate IO from computation.
>
>   -- Lennart
>
> On Feb 6, 2007, at 10:18 , [EMAIL PROTECTED] wrote:
>
> > Ketil,
> >
> > thanks for you help.
> >
> > Here's the code:
> >
> > and2 :: Bool -> Bool -> Bool
> > and2 a b = a && b
> >
> >
> > loop = [ and2 x y  | x <- [True,False], y <- [True,False] ]
> >
> >
> > Now, how do I have Haskell print
> >
> > printStrLn("True and True = ") + 
> > printStrLn("True and False = ") + 
> > ...
> >
> > Thanks.
> >
> > phiroc
> >
> >
> >
> >
> > Quoting Ketil Malde <[EMAIL PROTECTED]>:
> >
> >> [EMAIL PROTECTED] wrote:
> >>> 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
> >>>
> >> What is the type of the resulting table?
> >>> I have tried creating a second function called "loop", which
> >>> repeatedly
> >> calls
> >>> "and", but it did not work, because, for some reason unknown to
> >>> me, "do"
> >> does
> >>> not like repeated function calls
> >>>
> >>> loop = do
> >>>   and True True
> >>>   and True False
> >>>
> >> I'm not sure I understand what you expected here.  The 'do' syntax
> >> is for monadic code.
> >>> Is there a better way to repeatedly call "and"?
> >>>
> >> If you want your table in list for, I'd suggest using a list
> >> comprehension.
> >>
> >> Here's how you'd calculate squares of numbers, for instance:
> >>
> >>squares = [ x^2 | x <- [1..5] ]
> >>> Furthermore, is there a way in Haskell to loop through the
> >>> Boolean values
> >> (True
> >>> and False)
> >>>
> >> Since there are only two values, you can just feed a list
> >> comprehension
> >> with [True,False].
> >>> Last but not least, in the "loop" function above, assuming that
> >>> there is a
> >> way
> >>> to repeatedly call the "and" function, how could you intersperse
> >> "printStr"s
> >>> between the "and" calls?
> >>>
> >> I would't - keep the the calculation and the output separate instead.
> >>
> >> -k
> >>
> >
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-06 Thread Dougal Stanton
Quoth [EMAIL PROTECTED], nevermore,
> 
> loop = do
>   and True True
>   and True False
>   and False True
>   and False False

For this construct to work you'd have to have 'and' as a monadic
function - let's say, for argument's sake, in IO. And because there are
no results being carried around we can surmise that the type signature
is:

> and :: Bool -> Bool -> IO ()

This will help you do the putStr statements too, although I think it can
be done better. For example, you want to create a truth table, and you
want to print the values of this table. These should really be done
separately, so you don't mix IO with pure computation.

You might want to write a function of the type:

> and :: Bool -> Bool -> (Bool, Bool, Bool)

instead, where the two arguments passed in are stored alongside the
result.

> 
> Is there a better way to repeatedly call "and"?
> 
> Furthermore, is there a way in Haskell to loop through the Boolean values 
> (True
> and False) and call "and" each time?
> 

These can be answered in one sweep with list comprehensions. An
expression of the form

[ f x y | x <- xs, y <- ys ]

will form a list where every value is 'f x y' for all values of x and y
in the two source lists xs and ys. I hope this is of some help. I've
been purposefully vague in case this is a homework question. If not, let
us know and I'm sure people will be more than happy to provide fuller
answers.

Cheers,

D.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-06 Thread Ketil Malde

[EMAIL PROTECTED] wrote:

Ketil,

thanks for you help.

Here's the code:

and2 :: Bool -> Bool -> Bool
and2 a b = a && b


loop = [ and2 x y  | x <- [True,False], y <- [True,False] ]


Now, how do I have Haskell print

printStrLn("True and True = ") + 
printStrLn("True and False = ") + 
  

Well, if you keep x and y in the table as well, either as a triple
(x, y, and2 x y) or a nested tuple ((x,y), and2 x y) (which would
let you use the lookup function), you can define a function that
converts such a tuple to the approprate string.  Keep in mind
that Bool has a Show instance, so that e.g. show True => "True",
and use ++ to join two strings.

Then, you can 'map' this function on the table to get a list of strings
corresponding to table rows, and use 'concat' or 'unlines'.  When you
have a result you're happy with, you feed it to putStrLn.

-k
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-06 Thread Lennart Augustsson

It would be better to produce a triple (as was suggested)

loop = [(x, y, x&&y) | x <- [True, False], y <- [True, False]]

The you can map a function that prints over that.  Or even better
map a function that generates the strings, and the use one big
putStr at the end.  Always try to separate IO from computation.

-- Lennart

On Feb 6, 2007, at 10:18 , [EMAIL PROTECTED] wrote:


Ketil,

thanks for you help.

Here's the code:

and2 :: Bool -> Bool -> Bool
and2 a b = a && b


loop = [ and2 x y  | x <- [True,False], y <- [True,False] ]


Now, how do I have Haskell print

printStrLn("True and True = ") + 
printStrLn("True and False = ") + 
...

Thanks.

phiroc




Quoting Ketil Malde <[EMAIL PROTECTED]>:


[EMAIL PROTECTED] wrote:
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


What is the type of the resulting table?
I have tried creating a second function called "loop", which  
repeatedly

calls
"and", but it did not work, because, for some reason unknown to  
me, "do"

does

not like repeated function calls

loop = do
and True True
and True False


I'm not sure I understand what you expected here.  The 'do' syntax
is for monadic code.

Is there a better way to repeatedly call "and"?

If you want your table in list for, I'd suggest using a list  
comprehension.


Here's how you'd calculate squares of numbers, for instance:

   squares = [ x^2 | x <- [1..5] ]
Furthermore, is there a way in Haskell to loop through the  
Boolean values

(True

and False)

Since there are only two values, you can just feed a list  
comprehension

with [True,False].
Last but not least, in the "loop" function above, assuming that  
there is a

way

to repeatedly call the "and" function, how could you intersperse

"printStr"s

between the "and" calls?


I would't - keep the the calculation and the output separate instead.

-k




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-06 Thread phiroc
Ketil,

thanks for you help.

Here's the code:

and2 :: Bool -> Bool -> Bool
and2 a b = a && b


loop = [ and2 x y  | x <- [True,False], y <- [True,False] ]


Now, how do I have Haskell print

printStrLn("True and True = ") + 
printStrLn("True and False = ") + 
...

Thanks.

phiroc




Quoting Ketil Malde <[EMAIL PROTECTED]>:

> [EMAIL PROTECTED] wrote:
> > 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
> >
> What is the type of the resulting table?
> > I have tried creating a second function called "loop", which repeatedly
> calls
> > "and", but it did not work, because, for some reason unknown to me, "do"
> does
> > not like repeated function calls
> >
> > loop = do
> > and True True
> > and True False
> >
> I'm not sure I understand what you expected here.  The 'do' syntax
> is for monadic code.
> > Is there a better way to repeatedly call "and"?
> >
> If you want your table in list for, I'd suggest using a list comprehension.
>
> Here's how you'd calculate squares of numbers, for instance:
>
>squares = [ x^2 | x <- [1..5] ]
> > Furthermore, is there a way in Haskell to loop through the Boolean values
> (True
> > and False)
> >
> Since there are only two values, you can just feed a list comprehension
> with [True,False].
> > Last but not least, in the "loop" function above, assuming that there is a
> way
> > to repeatedly call the "and" function, how could you intersperse
> "printStr"s
> > between the "and" calls?
> >
> I would't - keep the the calculation and the output separate instead.
>
> -k
>


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-02-06 Thread Ketil Malde

[EMAIL PROTECTED] wrote:

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
  

What is the type of the resulting table?

I have tried creating a second function called "loop", which repeatedly calls
"and", but it did not work, because, for some reason unknown to me, "do" does
not like repeated function calls

loop = do
and True True
and True False
  

I'm not sure I understand what you expected here.  The 'do' syntax
is for monadic code.

Is there a better way to repeatedly call "and"?
  

If you want your table in list for, I'd suggest using a list comprehension.

Here's how you'd calculate squares of numbers, for instance:

  squares = [ x^2 | x <- [1..5] ]

Furthermore, is there a way in Haskell to loop through the Boolean values (True
and False)
  

Since there are only two values, you can just feed a list comprehension
with [True,False].

Last but not least, in the "loop" function above, assuming that there is a way
to repeatedly call the "and" function, how could you intersperse "printStr"s
between the "and" calls?
  

I would't - keep the the calculation and the output separate instead.

-k
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe