RabbitFarm

2021-07-11

The Weekly Challenge 120 (Prolog Solutions)

The examples used here are from the weekly challenge problem statement and demonstrate the working solution.

Part 1

You are given a positive integer $N less than or equal to 255. Write a script to swap the odd positioned bits with the even positioned bits and print the decimal equivalent of the new binary representation.

Solution


:-initialization(main).

pad(Bits, Padded):-
    length(Bits, L),
    PadLength is 8 - L, 
    length(Padding, PadLength),  
    maplist(=(0), Padding),
    append(Padding, Bits, Padded).  

bits(N, Bits):-
    bits(N, [], Bits).
bits(0, Bits, Bits).    
bits(N, Bit_Accum, Bits):-    
    B is N /\ 1,
    N0 is N >> 1,
    bits(N0, [B|Bit_Accum], Bits).

swap([], []). 
swap([H0, H1|T], [H1, H0|ST]):-
    swap(T, ST).

decimal(Bits, Decimal):-
    decimal(Bits, 0, Decimal).
decimal([], Decimal, Decimal).
decimal([H|T], DecimalAccum, Decimal):-
    length([H|T], B), 
    D is (H * 2 ** (B - 1)) + DecimalAccum,
    decimal(T, D, Decimal).  

main:-
    bits(18, B),
    pad(B, Padded),  
    swap(Padded, Swapped), 
    decimal(Swapped, Decimal), 
    write(Decimal), nl,
    halt.

Sample Run


$ gprolog --consult-file prolog/ch-1.p
GNU Prolog 1.4.5 (32 bits)
Compiled Dec  3 2020, 00:37:14 with gcc
By Daniel Diaz
Copyright (C) 1999-2020 Daniel Diaz
compiling /home/adamcrussell/Projects/perlweeklychallenge-club/challenge-120/adam-russell/prolog/ch-1.p for byte code...
/home/adamcrussell/Projects/perlweeklychallenge-club/challenge-120/adam-russell/prolog/ch-1.p compiled, 36 lines read - 3978 bytes written, 98 ms
33.0

Notes

Working with bitwise operators in Prolog is something I have done a bit before. This code most notably borrows from a solution to Challenge 079. Here that set_bit/2 predicate is repurposed as bits/2 which returns a list of bits for any given number.

The list of bits must be padded (pad/2), the bits swapped (swap/2), and then the decimal value of the swapped bits calculated (decimal/2).

Part 2

You are given time $T in the format hh:mm. Write a script to find the smaller angle formed by the hands of an analog clock at a given time.

Solution


:-initialization(main).

clock_angle(Time, Angle):-
    append(H, [58|M], Time),  
    number_codes(Hour, H),
    number_codes(Minutes, M),
    A is abs(0.5 * (60 * Hour - 11 * Minutes)), 
    ((A > 180, Angle is 360 - A); Angle = A). 

main:-
    clock_angle("03:10", Angle),
    write(Angle), nl,  
    halt. 

Sample Run


$ gprolog --consult-file prolog/ch-2.p
GNU Prolog 1.4.5 (32 bits)
Compiled Dec  3 2020, 00:37:14 with gcc
By Daniel Diaz
Copyright (C) 1999-2020 Daniel Diaz
compiling /home/adamcrussell/Projects/perlweeklychallenge-club/challenge-120/adam-russell/prolog/ch-2.p for byte code...
/home/adamcrussell/Projects/perlweeklychallenge-club/challenge-120/adam-russell/prolog/ch-2.p compiled, 13 lines read - 2384 bytes written, 40 ms
35.0

Notes

clock_angle/2 starts out by splitting the hh:mm formatted time into the hour and minute parts, by way of append. 58 is the character code for the ':'. Once this is done, and that is perhaps the most prological part of the code, the formula for the angle is applied.

References

Challenge 120

posted at: 14:37 by: Adam Russell | path: /prolog | permanent link to this entry