-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy path05.pl
59 lines (52 loc) · 1.83 KB
/
05.pl
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
:- use_module(library(dcg/basics)).
:- use_module(library(clpfd)).
solve_(File,F,Answer) :-
phrase_from_file(file(F,Ss,Cs0),File),
flatten([Ss,Cs0],Cs),
retractall(c(_,_,_,_)),maplist(assertz,Cs),
findall(S,c(S,_,none,seed),[H|T]),
foldl([A,B,C]>>fdset_union(A,B,C),T,H,Seeds),
map(`seed`,Seeds,Final),
fdset_min(Final,Answer).
solve(File,Part1,Part2) :-
solve_(File,seeds,Part1),
solve_(File,seedz,Part2).
seeds([]) --> [].
seeds([c(S,0,none,seed)|Xs]) -->
blanks,number(X),{range_to_fdset(X..X,S)},seeds(Xs).
seedz([]) --> [].
seedz([c(S,0,none,seed)|Xs]) -->
blanks,number(X),blanks,number(L),
{E is X+L-1, range_to_fdset(X..E,S)},seedz(Xs).
rngs(_,_,[]) --> [].
rngs(Fr,To,[c(S,O,Fr,To)|Xs]) -->
number(D),blanks,number(X),blanks,number(L),
{E is X+L-1,range_to_fdset(X..E,S), O is D-X},
"\n",rngs(Fr,To,Xs).
rngs(Fr,To,[c(S,O,Fr,To)]) -->
number(D),blanks,number(X),blanks,number(L),
{E is X+L-1,range_to_fdset(X..E,S), O is D-X}.
cat([]) --> [].
cat(Rs) --> string(Fr),"-to-",string(To)," map:\n",rngs(Fr,To,Rs).
cats([Rs|Xs]) --> cat(Rs),"\n\n",!,cats(Xs).
cats([Rs]) --> cat(Rs).
file(F,Seeds,Cats) --> "seeds:",call(F,Seeds),"\n\n",cats(Cats).
offset(S0,O,S) :- X in_set S0, Y #= X+O, fd_set(Y,S).
map_(_,[],AccS,AccD,AccS,AccD) :- !.
map_(Src,[S-O|T],AccS0,AccD0,SrcU,DstU) :-
fdset_union(S,AccS0,AccS),
fdset_intersection(Src,S,Int),
(empty_fdset(Int) ->
AccD=AccD0;offset(Int,O,Off),fdset_union(AccD0,Off,AccD)),
!,map_(Src,T,AccS,AccD,SrcU,DstU).
map_(Src,Dests,NewSrc) :-
empty_fdset(E),
map_(Src,Dests,E,E,SrcU,DstU),
fdset_subtract(Src,SrcU,Diff),
fdset_union(Diff,DstU,NewSrc).
map(`location`,Src,Src) :- !.
map(Fr,Src,End) :-
once(c(_,_,Fr,To)),
findall(S-O,c(S,O,Fr,To),Dests),
map_(Src,Dests,NewSrc),!,
map(To,NewSrc,End).