RabbitFarm

2020-11-15

Perl Weekly Challenge 086

Part 1

You are given an array of integers @N and an integer $A. Write a script to find find if there exists a pair of elements in the array whose difference is $A. Print 1 if exists otherwise 0.

Solution


:- use_module(library(optparse)).
/*
    You are given an array of integers @N and an integer $A.
    Write a script to find find if there exists a pair of elements 
    in the array whose difference is $A.
    Print 1 if exists otherwise 0.
*/
opts_spec(
    [
        [opt(numbers), 
        default([10, 8, 12, 15, 5]),
        longflags([numbers])],

        [opt(a), 
        default(7),
        longflags([a])]
    ]).

ch_1(L, N):-
    member(A, L),
    member(B, L),
    A =\= B,
    D is A - B,
    N = D,
    writeln(1).
    
ch_1(_, _):-  
    writeln(0).
    
main:-
    opts_spec(OptsSpec),
    opt_arguments(OptsSpec, [numbers(L), a(A)], _AdditionalArguments),
    ch_1(L, A),
    halt.

Sample Run


$ swipl -s ch-1.p -g main --numbers="[10, 30, 20, 50, 40]" --a=15
0
$ swipl -s ch-1.p -g main --numbers="[10, 8, 12, 15, 5]" --a=7
1

Notes

My approach here is very similar to what I did last week. Please do check that out if you’re interested in a slightly longer discussion of the use of optparse to handle the command line arguments.

Part 2

You are given Sudoku puzzle (9x9). Write a script to complete the puzzle

Solution


:- use_module(library(clpfd)).
 
sudoku(Puzzle, Solution) :-
        Solution = Puzzle,
        Puzzle = [S11, S12, S13, S14, S15, S16, S17, S18, S19,
                  S21, S22, S23, S24, S25, S26, S27, S28, S29,
                  S31, S32, S33, S34, S35, S36, S37, S38, S39,
                  S41, S42, S43, S44, S45, S46, S47, S48, S49,
                  S51, S52, S53, S54, S55, S56, S57, S58, S59,
                  S61, S62, S63, S64, S65, S66, S67, S68, S69,
                  S71, S72, S73, S74, S75, S76, S77, S78, S79,
                  S81, S82, S83, S84, S85, S86, S87, S88, S89,
                  S91, S92, S93, S94, S95, S96, S97, S98, S99],
 
        ins(Puzzle, 1..9),
 
        Row1 = [S11, S12, S13, S14, S15, S16, S17, S18, S19],
        Row2 = [S21, S22, S23, S24, S25, S26, S27, S28, S29],
        Row3 = [S31, S32, S33, S34, S35, S36, S37, S38, S39],
        Row4 = [S41, S42, S43, S44, S45, S46, S47, S48, S49],
        Row5 = [S51, S52, S53, S54, S55, S56, S57, S58, S59],
        Row6 = [S61, S62, S63, S64, S65, S66, S67, S68, S69],
        Row7 = [S71, S72, S73, S74, S75, S76, S77, S78, S79],
        Row8 = [S81, S82, S83, S84, S85, S86, S87, S88, S89],
        Row9 = [S91, S92, S93, S94, S95, S96, S97, S98, S99],
 
        Column1 = [S11, S21, S31, S41, S51, S61, S71, S81, S91],
        Column2 = [S12, S22, S32, S42, S52, S62, S72, S82, S92],
        Column3 = [S13, S23, S33, S43, S53, S63, S73, S83, S93],
        Column4 = [S14, S24, S34, S44, S54, S64, S74, S84, S94],
        Column5 = [S15, S25, S35, S45, S55, S65, S75, S85, S95],
        Column6 = [S16, S26, S36, S46, S56, S66, S76, S86, S96],
        Column7 = [S17, S27, S37, S47, S57, S67, S77, S87, S97],
        Column8 = [S18, S28, S38, S48, S58, S68, S78, S88, S98],
        Column9 = [S19, S29, S39, S49, S59, S69, S79, S89, S99],
 
        SubBox1 = [S11, S12, S13, S21, S22, S23, S31, S32, S33],
        SubBox2 = [S41, S42, S43, S51, S52, S53, S61, S62, S63],
        SubBox3 = [S71, S72, S73, S81, S82, S83, S91, S92, S93],
        SubBox4 = [S14, S15, S16, S24, S25, S26, S34, S35, S36],
        SubBox5 = [S44, S45, S46, S54, S55, S56, S64, S65, S66],
        SubBox6 = [S74, S75, S76, S84, S85, S86, S94, S95, S96],
        SubBox7 = [S17, S18, S19, S27, S28, S29, S37, S38, S39],
        SubBox8 = [S47, S48, S49, S57, S58, S59, S67, S68, S69],
        SubBox9 = [S77, S78, S79, S87, S88, S89, S97, S98, S99],
 
        valid([Row1, Row2, Row3, Row4, Row5, Row6, Row7, Row8, Row9,
               Column1, Column2, Column3, Column4, Column5, Column6, Column7, Column8, Column9,
               SubBox1, SubBox2, SubBox3, SubBox4, SubBox5, SubBox6, SubBox7, SubBox8, SubBox9]).
 
valid([]).
valid([H|T]) :-
    all_different(H),
    valid(T).

Sample Run


$ swipl -s prolog/ch-2.p
Welcome to SWI-Prolog (threaded, 64 bits, version 8.2.2)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.
Please run ?- license. for legal details.

For online help and background, visit https://www.swi-prolog.org
For built-in help, use ?- help(Topic). or ?- apropos(Word).

?- sudoku([_,_,_,2,6,_,7,_,1,6,8,_,_,7,_,_,9,_,1,9,_,_,_,4,5,_,_,8,2,_,1,_,_,_,4,_,_,_,4,6,_,2,9,_,_,_,5,_,_,_,3,_,2,8,_,_,9,3,_,_,_,7,4,_,4,_,_,5,_,_,3,6,7,_,3,_,1,8,_,_,_],Solution).
Solution = [4, 3, 5, 2, 6, 9, 7, 8, 1|...].

?- halt.

Notes

How many Prolog programmers saw this part of the challenge and thought “finally my training has paid off!” For the unfamiliar, Sudoku is a natural fit for a language like Prolog and quite a few variations are possible. My approach here is to make some use of clpfd but favored a more verbose style so that what is happening should be fairly clear. The clpfd manual includes a much more terse example.

posted at: 23:49 by: Adam Russell | path: /prolog | permanent link to this entry