user1812457
user1812457

Reputation:

Using bagof/3 only for the side effect

Solving a very simple exercise in Prolog: print all numbers from 1 to 100, but instead of the number, print 'Fuzz' if number is a multiple of 3, 'Buzz' if multiple of 5, and 'FizzBuzz' if both.

I ended up doing the following:

fizzbuzz :- forall( between(1, 100, X), fizzbuzz(X) ).
fizzbuzz(X) :- ( write_fb(X) ; write_n(X) ), nl.

write_fb(X) :- bagof(_, fb(X), _).
fb(X) :- X rem 3 =:= 0, write('Fizz').
fb(X) :- X rem 5 =:= 0, write('Buzz').

write_n(X) :- write(X).

but isn't there any predicate or a control structure that would avoid using bagof/3 only for its side effect? (I am always a bit unsure with using predicates only for the side effects).

Upvotes: 1

Views: 481

Answers (11)

repeat
repeat

Reputation: 18726

Instead of bagof/3 you could use if/3, like so:

:- use_module(library(aggregate), [forall/2]).
:- use_module(library(between),  [between/3]).

fizzbuzz :-
   forall(between(1,100,Z),  fizzbuzz(Z)).

fizzbuzz(Z) :-
   forall(if(integer_fb(Z,X), true, Z=X),  write(X)),
   write(' ').

integer_fb(Z, 'Fizz') :- Z rem 3 =:= 0.
integer_fb(Z, 'Buzz') :- Z rem 5 =:= 0.

Sample output using SICStus Prolog 4.4.0:

| ?- fizzbuzz.
1 2 Fizz 4 Buzz Fizz 7 8 Fizz Buzz 11 Fizz 13 14 FizzBuzz 16 17 Fizz 19 Buzz Fizz 22 23 Fizz Buzz 26 Fizz 28 29 FizzBuzz 31 32 Fizz 34 Buzz Fizz 37 38 Fizz Buzz 41 Fizz 43 44 FizzBuzz 46 47 Fizz 49 Buzz Fizz 52 53 Fizz Buzz 56 Fizz 58 59 FizzBuzz 61 62 Fizz 64 Buzz Fizz 67 68 Fizz Buzz 71 Fizz 73 74 FizzBuzz 76 77 Fizz 79 Buzz Fizz 82 83 Fizz Buzz 86 Fizz 88 89 FizzBuzz 91 92 Fizz 94 Buzz Fizz 97 98 Fizz Buzz 

Upvotes: 2

Kintalken
Kintalken

Reputation: 773

The problem:

Print all numbers from 1 to 100, but instead of the number, print 'Fuzz' if number is a multiple of 3, 'Buzz' if multiple of 5, and 'FizzBuzz' if both.

I think the fact that you encountered this peculiarity about bagof is an indication of a "smell" in your program. I find that happens to me a lot with Prolog. Prolog is actually a very minimal kit with not very much provided. I have learned over time that if I encounter a need for something that is NOT in that minimal kit, or my usage seems to betray the intended usage of a builtin feature, then almost always it is because there is a "smell" in my current approach.

More about "smell" here : https://en.wikipedia.org/wiki/Code_smell

I think the "smell" in your current approach becomes apparent when we outline a general sketch of the procedural flow that your program currently entails:

  1. generate
  2. print
  3. transform

The problem is that you are trying to "print" BEFORE you "transform" . You want to "print" AFTER you "transform", like this:

  1. generate
  2. transform
  3. print

With this in mind we can rewrite the problem statement:

The NEW problem:

Solve for all each number:

Generate each number from 1 to 100, but transform each number into an each message, into each message 'Fuzz' if the each number is a multiple of 3, into each message 'Buzz' if the each number is a multiple of 5, into each message 'FizzBuzz' if the each number is both, then print each message.

The following is a program that aims to solve the above stated problem.

The program listing is followed by an example query session.

*/

/* -- prolog setup -- */

:-  ( op(10'1150,'yfx','forall')    )   .

:-  ( op(10'1150,'fy','if') )   .
:-  ( op(10'1140,'yfx','then') )    .
:-  ( op(10'1140,'yfx','else') )    .

(if IF then THEN else ELSE) :- (IF *-> THEN ; ELSE) .
(if IF then THEN) :- (IF *-> THEN ; (throw(false(IF)))) .

term_expansion((if IF then THEN else ELSE),((IF :- THEN *-> (true) ; ELSE)))    .
term_expansion((if IF then THEN),((IF :- THEN *-> (true) ; (throw(false(IF))))))    .

/* -- program -- */

if
(
  program(_)
)
then
(
  (
    if
    (
      generate(NUMBER)
    )
    then
    (
      true
    )
  )
  forall
  (
    if
    (
      transform(NUMBER,MESSAGE)
    )
    then
    (
      if
      (
        accept(NUMBER,MESSAGE)
      )
      then
      (
        if
        (
          echo(NUMBER)
        )
        then
        (
          echo(MESSAGE)
        )
      )
      else
      (
        true
      )
    )
  )
)
.

if
(
  generate(NUMBER)
)
then
(
  between(1,100,NUMBER)
)
.

if
(
  transform(NUMBER,MESSAGE)
)
then
(
  if
  (
    multiple_of_3(NUMBER)
  )
  then
  (
    if
    (
      multiple_of_5(NUMBER)
    )
    then
    (
      MESSAGE='FizzBuzz'
    )
    else
    (
      MESSAGE='Fuzz'
    )
  )
  else
  (
    if
    (
      multiple_of_5(NUMBER)
    )
    then
    (
      MESSAGE='Buzz'
    )
    else
    (
      % this contingency is undefined in the problem statement %
      true
    )
  )
)
.

if
(
  multiple_of_3(NUMBER)
)
then
(
  NUMBER rem 10'3 =:= 10'0
)
else
(
  false
)
.

if
(
  multiple_of_5(NUMBER)
)
then
(
  NUMBER rem 10'5 =:= 10'0
)
else
(
  false
)
.

if
(
  accept(NUMBER,MESSAGE)
)
then
(
  if
  (
    true
  )
  then
  (
    true
  )
  else
  (
    false
  )
)
else
(
  false
)
.

if
(
  echo(MESSAGE)
)
then
(
  if
  (
    writeq(MESSAGE)
  )
  then
  (
    nl
  )
)
.

/*

example query
=============

?-
program(_)
.

3
'Fuzz'
5
'Buzz'
6
'Fuzz'
9
'Fuzz'
12
'Fuzz'
15
'FizzBuzz'
18
'Fuzz'

[ ... and so on as expected ... ]

90
'FizzBuzz'
93
'Fuzz'
95
'Buzz'
96
'Fuzz'
99
'Fuzz'
100
'Buzz'
true.

?- 

However, the program as currently presented does not quite produce the intended output as presented above.

In the program above there is a marker:

  % this contingency is undefined in the problem statement %

Issue needs to be resolved before the program is 100% satisfactory.

Tested using swi-prolog and yap.

Upvotes: 0

mat
mat

Reputation: 40768

Complementing the existing answers, I would like to show a more relational solution that I hope illustrates some unique benefits of applying a declarative programming paradigm such as logic programming to this question.

First, let us recapitulate the task:

print all numbers from 1 to 100, but instead of the number, print...

  • 'Fuzz' if number is a multiple of 3
  • 'Buzz' if multiple of 5
  • and 'FizzBuzz' if both.

The tacit assumption, I presume, is that the numbers are limited to integers.

For simplicity, let us first restrict ourselves to a single integer, and let us describe the relation between such integer and the required output.

The three cases mentioned above can be quite directly translated to Prolog, using your Prolog ystem's CLP(FD) constraints for declarative integer arithmetic:

integer_output(N, 'Fuzz')     :- N #= 3*_.
integer_output(N, 'Buzz')     :- N #= 5*_.
integer_output(N, 'FizzBuzz') :- N #= 3*_, N #= 5*_.

That's not all though, because this yields for example:

?- integer_output(4, N).
false.

Hence, we need one more case, which we can for example formulate as:

integer_output(N, N)          :- N mod 3 #\= 0, N mod 5 #\= 0.

This simply states that in the event that none of the other cases applies, we output the number as is. The resulting relation is very general. For example, we can use it for concrete integers:

?- integer_output(1, O).
O = 1.

?- integer_output(3, O).
O = 'Fuzz' ;
false.

And we can also use it to write unit tests, for example:

?- integer_output(5, 'Buzz').
true .

Here, the intended output is already specified, and we can use the same relation to ask whether the output will be as required. That's a quite nice property of relations, and would not be so easy if we only wrote the output on the system terminal instead of making it explicit as a predicate argument as we did above.

But there's even more! We can also use the same relation in the other direction, where we ask for example: "Which integers result in the output Buzz?" Here it is:

?- integer_output(I, 'Buzz').
5*_680#=I.

That's a massive generalization of the earlier test case, and can serve as an additional assurance that we have covered all cases. In fact, we can even generalize this further, resulting in the most general query which asks how answers look like in general:

?- integer_output(I, O).
O = 'Fuzz',
3*_742#=I ;
O = 'Buzz',
5*_742#=I ;
O = 'FizzBuzz',
5*_1014#=I,
3*_1038#=I.

Let us reason more about the output. Obviously, we expect that the output is uniquely determined for each possible integer, right? Let us ask Prolog whether this is so, by asking for counterexamples of this property:

?- dif(O1, O2),
   integer_output(I, O1),
   integer_output(I, O2).
O1 = 'Fuzz',
O2 = 'Buzz',
5*_1046#=I,
3*_1070#=I ;
O1 = 'Fuzz',
O2 = 'FizzBuzz',
5*_1318#=I,
3*_1342#=I,
3*_1366#=I .

Now that doesn't look good : From the above, we already suspect that there may be cases of the same integer I yielding two different, equally justifiable, outputs O1 and O2.

And in fact, here's a concrete integer where this problem arises:

?- integer_output(15, O).
O = 'Fuzz' ;
O = 'Buzz' ;
O = 'FizzBuzz' ;
false.

So, it turns out, that the output is not uniquely determined! Let us follow our natural instinct and ask right away:

WHOSE FAULT IS THIS?

CLP(FD) CONSTRAINTS TO BLAME?

In fact, it turns out that using a declarative formulation has simply exposed an ambiguity in the task formulation. Prematurely committing to one of the solutions does not expose this problem.

What was probably meant was a task description that induces the following relation between an integer and the output:

integer_output(N, 'Fuzz')     :- N #= 3*_, N mod 5 #\= 0.
integer_output(N, 'Buzz')     :- N #= 5*_, N mod 3 #\= 0.
integer_output(N, 'FizzBuzz') :- N #= 3*_, N #= 5*_.
integer_output(N, N)          :- N mod 3 #\= 0, N mod 5 #\= 0.

This yields:

?- integer_output(15, O).
O = 'FizzBuzz' ;
false.

The other test cases still work as expected.

Now, using this relation as a building block, it is easy to lift it to lists of integers, using the meta-predicate maplist/3:

fizz_buzz(Ls) :-
        numlist(1, 100, Ls0),
        maplist(integer_output, Ls0, Ls).

Sample query and answer:

?- fizz_buzz(Ls).
Ls = [1, 2, 'Fuzz', 4, 'Buzz', 'Fuzz', 7, 8, 'Fuzz'|...] ;
false.

Note that we are not writing anything ourselves: We are using the Prolog toplevel to do the writing for us, and reason about arguments.

The advantage is clear: We can again write test cases for such a predicate. For example, we expect the following to hold, and it does:

?- Ls = [1,2|_], fizz_buzz(Ls).
Ls = [1, 2, 'Fuzz', 4, 'Buzz', 'Fuzz', 7, 8, 'Fuzz'|...] .

So far, everything is completely pure and usable in all directions. I leave formatting such solutions as you want as an easy exercise.

If your Prolog system does not provide numlist/3, you can use bagof/3 to obtain the list of integers from 1 to 100 like this:

?- bagof(L, (L in 1..100,indomain(L)), Ls).
Ls = [1, 2, 3, 4, 5, 6, 7, 8, 9|...].

Thus, bagof/3 can be useful for this task, but I cannot recommend to use it for side-effects.

Upvotes: 3

Kintalken
Kintalken

Reputation: 773

/*

problem statement

solve for all each number   :

generate each number from 1 to 100 , but transform each number into an each message , into each message 'Fuzz' if the each number is a multiple of 3 , into each message 'Buzz' if the each number is a multiple of 5 , into each message 'FizzBuzz' if the each number is both , then print each message .

*/

/*

program

*/

    :- use_module(library(clpfd)) .

    :- op(10'1,'yfx','forall') .
    :- op(10'1,'fy','once') .

    (
        program
    )
    :-
    (
        (
            between(1,100,NUMBER)
        )
        forall
        (
            once
            (
                (
                    MESSAGE='FizzBuzz'
                    ,
                    NUMBER rem 10'3 #= 10'0
                    ,
                    NUMBER rem 10'5 #= 10'0
                )
                |
                (
                    MESSAGE='Buzz'
                    ,
                    NUMBER rem 10'5 #= 10'0
                )
                |
                (
                    MESSAGE='Fuzz'
                    ,
                    NUMBER rem 10'3 #= 10'0
                )
                |
                (
                    MESSAGE=_
                )
            )
            ,
            once
            (
                (
                    nonvar(MESSAGE)
                    ,
                    writeq(NUMBER)
                    ,
                    nl
                    ,
                    writeq(MESSAGE)
                    ,
                    nl
                )
                |
                (
                    true
                )
            )
        )
    )
    .

/*

testing

Tested in swi prolog . */

    ?- program .

    3
    'Fuzz'
    5
    'Buzz'
    6
    'Fuzz'
    9
    'Fuzz'
    10
    'Buzz'
    12
    'Fuzz'
    15
    'FizzBuzz'

    { .e.t.c. | ... as expected ... |  .e.t.c. }

    99
    'Fuzz'
    100
    'Buzz'
    true.

    ?- 

*/

Upvotes: -1

user7473772
user7473772

Reputation:

I take the idea of @Kintalken and I just do minimal change in your original code to arrive at this solution:

fizzbuzz :-
    forall( between(1, 100, X),
        (   fizzbuzz(X, Output),
            format("~w~n", [Output])
        )).

fizzbuzz(X, Output) :-
    (   bagof(Y, fb(X, Y), Ys)
    ->  atomic_list_concat(Ys, Output)
    ;   X = Output
    ).

fb(X, 'Fizz') :- X rem 3 =:= 0.
fb(X, 'Buzz') :- X rem 5 =:= 0.

The only change from the code in your question is that first I collect solutions then I print in one place only and not as side effect of predicate that is collected with bagof so you no more have to have side effect inside bagof.

Also as you see now printing is in the second argument of forall so that it is clear where side effects are happening and not hiding elsewhere and there is exactly one place for all side effect of this program not scattered between clauses of different predicates.

Another thing is that instead of conjunction I use -> not because it is any different but because it conveys intention to use bagof to collect solution or do something else if there are no solutions. When I read your question and answers and comments to answers this was part of the discussion?

I do not know how to indent exactly the contents of forall. The way I have indented looks maybe ok but maybe not ok at all. between and fizzbuzz and format are now aligned but only fizzbuzz and format should have been aligned, but between aligned by accident so this is not on purpose, maybe it is confusing, but I don't like to have something like this

forall(
    between(1, 100, X),
    (   fizzbuzz(X, Output),
        format("~w~n", [Output])
    ))

because then forall( looks so lonely all alone by itself on a whole line without anything to help it feel less lonely with its sad little opening paren.

Upvotes: 1

user1812457
user1812457

Reputation:

Why abuse bagof/3 for the side effect and just stop there? We can also abuse circular lists:

fizzbuzz :-
        Fizz = [fail,fail,write('Fizz')|Fizz],
        Buzz = [fail,fail,fail,fail,write('Buzz')|Buzz],
        fb(1, 100, Fizz, Buzz).

fb(N, N, _, _) :- !.
fb(N, Last, [F|Fs], [B|Bs]) :-
        (       bagof(_, ( F ; B ), _)
        ->      true
        ;       write(N)
        ),
        nl,
        succ(N, N1),
        fb(N1, Last, Fs, Bs).

Upvotes: 0

Nicholas Carey
Nicholas Carey

Reputation: 74355

Me...I'd do something like:

fizzbuzz( X , Y ) :-
  X =< Y ,
  R3 is X % 3 ,
  R5 is X % 5 ,
  map( R3 , R5 , X , V ) ,
  write(V) ,
  nl ,
  X1 is X+1 ,
  fizzbuzz( X1 , Y )
  .

map( 0 , 0 , _ , fizzbuzz ) :- ! .
map( 0 , _ , _ , fizz     ) :- ! .
map( _ , 0 , _ , buzz     ) :- ! .
map( _ , _ , X , X        ) :- ! .

Upvotes: 0

Anniepoo
Anniepoo

Reputation: 2162

My esteemed collegues have answered, but you want 'between'.

You don't need to collect the solutions. In that your intuition is correct. I suspect you started with something like

fizzbuzz :-  between(1, 100, N),
             fb(N).


fb(N) :-  N rem 5 =:= 0,  
          N rem 3 =:= 0,
          write(fizzbuzz).

fb(N) :-  N rem 5 =:= 0,    
          write(buzz).

fb(N) :-  N rem 3 =:= 0,
          write(fizz).

fb(N) :-  write(N).

the problem with this is that fb isn't 'steadfast' - you don't expect it to offer you multiple solutions, but it does - for example, fb(15) unifies with every fb rule.

The solution is to force it to be steadfast, using a cut:

fizzbuzz :-  between(1, 100, N),
             fb(N).


fb(N) :-  N rem 5 =:= 0,  
          N rem 3 =:= 0,
          !,
          write(fizzbuzz).

fb(N) :-  N rem 5 =:= 0,
          !,    
          write(buzz).

fb(N) :-  N rem 3 =:= 0,
          !,
          write(fizz).

fb(N) :-  write(N).

Upvotes: 0

CapelliC
CapelliC

Reputation: 60034

aggregate(count, fb(X), C) allows to count solutions, but is based on bagof, thus builds the list just to count the elements. Then I wrote a reusable 'building block', predating call_nth/2, from this @false answer

:- meta_predicate count_solutions(0, ?).

count_solutions(Goal, C) :-
    State = count(0, _), % note the extra argument which remains a variable
    (   Goal,
        arg(1, State, C1),
        C2 is C1 + 1,
        nb_setarg(1, State, C2),
        fail
    ;   arg(1, State, C)
    ).

the 'applicative' code become

:- use_module(uty, [count_solutions/2]).

fizzbuzz :- forall( between(1, 100, X), fizzbuzz(X) ).
fizzbuzz(X) :-
    ( count_solutions(fb(X), 0) -> write(X) ; true ), nl.

fb(X) :- X rem 3 =:= 0, write('Fizz').
fb(X) :- X rem 5 =:= 0, write('Buzz').

Upvotes: 1

thanos
thanos

Reputation: 5858

Well, you are already using it; forall/2:

write_fb(X) :-
    forall(fb(X), true).

Alternatively, you can change your representation of the problem:

write_fb(X) :-
  (X rem 3 =:= 0 -> write('Fizz') ; true),
  (X rem 5 =:= 0 -> write('Buzz') ; true).

Of course, in this case, using bagof/3 and friends is fine since the generated list is very small.

Upvotes: 0

joel76
joel76

Reputation: 5645

You can use sort of pattern matching :

fizzbuzz :-
    forall( between(1, 100, X), fizzbuzz(X) ).
fizzbuzz(X) :-
    0 is X rem 15,
    format('~w FizzBuzz~n', [X]).

fizzbuzz(X) :-
    0 is X rem 5,
    format('~w Buzz~n', [X]).

fizzbuzz(X) :-
    0 is X mod 3,
    format('~w Fizz~n', [X]).

fizzbuzz(X) :-
    write(X), nl.

Upvotes: 1

Related Questions