When was the first time you cried over an anime?
ystael @ ystael @beehaw.org Posts 0Comments 55Joined 2 yr. ago
No miniatures anywhere: the fourth edition of A World At War is $210 from GMT, plus another $67 if you want to replace the mapsheets with mounted map boards. (This is a monster game covering the entire Second World War at the strategic level. It cannot be played by humans in a reasonable period of time.)
If you have ever used an HP RPN calculator (which are clearly the best calculators), there is Droid48, which emulates the HP 48GX.
So, uh, when I saw the post title and the thumbnail ... the first sentence into my mind was "How are you gentlemen?"
I'm old.
It is physically very large. Larger than basically all cats and a lot of dogs. My daughter was 3 1/2 when I got it and it wasn't much smaller than she was then.
I've assembled and disassembled it several times. I think it takes 8-10 hours to get it together and not much less to take it apart. You really have to follow the instructions in reverse to get it broken down, and the pins make my fingers quite sore if I don't take it in stages.
The linked review is correct that the mechanics somewhat overtax the single motor, but I find the design so impressive that it doesn't matter.
This was the last "flagship" Technic set I ever bought. We don't have space in the house for more plastic toys this size, and I don't love the fact that the huge ones tend to be app controlled now. But I think this was a pretty high note to go out on.
J
Nothing much to say about today's. I think I wrote basically the same code you'd write in Python, just with fewer characters, more of which are punctuation. I did learn a little bit more about how to use J's step debugger, and that /
is specifically a right fold, so you can use it on a dyad with arguments of different types as long as the list argument is the left one.
data_file_name =: '15.data' lines =: cutopen fread data_file_name NB. instructions start with the first line not containing a # character start_of_moves =: 0 i.~ '#' e."1 > lines grid =: ,. > start_of_moves {. lines start_row =: 1 i.~ '@' e."1 grid start_col =: '@' i.~ start_row { grid pos =: start_row, start_col grid =: '.' ( start_of_moves }. lines translate_move =: monad define"0 if. y = '>' do. 0 1 elseif. y = '^' do. _1 0 elseif. y = '<' do. 0 _1 elseif. y = 'v' do. 1 0 else. 0 0 end. ) moves =: translate_move move_instructions NB. pos step move updates grid as needed and returns the new position step =: dyad define"1 1 new_pos =. x + y if. '#' = (< new_pos) { grid do. x NB. obstructed by wall elseif. '.' = (< new_pos) { grid do. new_pos NB. free to move else. NB. it's 'O', need to push a stack p =. new_pos NB. pointer to box at end of stack while. 'O' = (< p) { grid do. p =. p + y end. if. '#' = (< p) { grid do. x NB. stack is blocked else. NB. move stack grid =: 'O.' (< p ,: new_pos)} grid new_pos end. end. ) score =: dyad define"0 2 +/ ; ((<"0) 100 * i.#y) +&.> (< @: I. @: = & x)"1 y ) final_pos =: step~/ |. pos , moves NB. / is a right fold result1 =: 'O' score grid translate_cell =: monad define"0 if. y = '#' do. '##' elseif. y = '.' do. '..' elseif. y = 'O' do. '[]' else. '@.' end. ) grid2 =: (,/ @: translate_cell)"1 ,. > start_of_moves {. lines start_row2 =: 1 i.~ '@' e."1 grid2 start_col2 =: '@' i.~ start_row { grid2 pos =: start_row2, start_col2 grid2 =: '.' (< pos)} grid2 NB. erase the @ NB. (grid; box_pos) try_push dir attempts to push the box at box_pos one NB. cell in direction dir. box_pos can be either the left or right cell of NB. the box. it returns (grid; success) where grid is the maybe-changed grid NB. and success is whether the box moved. if any box that would be pushed NB. cannot move, this box cannot move either and the grid does not change. try_push =: dyad define"1 1 'grid pos' =. x if. ']' = (< pos) { grid do. pos =. pos + 0 _1 end. NB. make pos left cell source_cells =. pos ,: pos + 0 1 if. 0 = {: y do. NB. moving up or down target_cells =. (pos + y) ,: (pos + y + 0 1) NB. cells we move into elseif. y -: 0 _1 do. target_cells =. 1 2 $ pos + y NB. moving left else. target_cells =. 1 2 $ pos + y + 0 1 end. NB. moving right NB. Have to check target cells one at a time because pushing a box up or NB. down may vacate the other target cell, or it may not trial_grid =. grid for_tc. target_cells do. NB. if a target cell is blocked by wall, fail if. '#' = (< tc) { trial_grid do. grid; 0 return. elseif. '[]' e.~ (< tc) { trial_grid do. 'trial_grid success' =. (trial_grid; tc) try_push y if. -. success do. grid; 0 return. end. end. end. NB. at this point either target_cells are clear or we have returned failure, NB. so push the box grid =. '[]' (<"1 source_cells +"1 y)} '.' (<"1 source_cells)} trial_grid grid; 1 ) NB. (grid; pos) step2 move executes the move and returns new (grid; pos) step2 =: dyad define"1 1 'grid pos' =. x new_pos =. pos + y if. '#' = (< new_pos) { grid do. grid; pos NB. obstructed by wall elseif. '.' = (< new_pos) { grid do. grid; new_pos NB. free to move else. NB. need to push a box 'new_grid success' =. (grid; new_pos) try_push y if. success do. new_grid; new_pos else. grid; pos end. end. ) 'final_grid final_pos' =: > (step2~ &.>)/ (<"1 |. moves) , <(grid2; pos) result2 =: '[' score final_grid
J
Had to actually render output! What is this "user interface" of which you speak?
J doesn't have meaningful identifiers for system interfaces built into the core language because why would you ever do that. It's all routed through the "foreign conjunction" !:
. There are aliases in the library, like fread
, but if the documentation gives a list of all of them, I haven't found it. We're doing 1980 style system calls by number here. 1 !: 2
is write()
, so x (1 !: 2) 2
writes x
(which must be a list of characters) to stdout
. (6 !: 3) y
is sleep
for y
seconds.
It's inefficient to compute, but I looked for low spots in the mean distance between robots to find the pattern for part 2. The magic numbers (11 and 101) were derived by staring at the entire series for a little bit.
load 'regex' data_file_name =: '14.data' raw =: cutopen fread data_file_name NB. a b sublist y gives elements [a..a+b) of y sublist =: ({~(+i.)/)~"1 _ parse_line =: monad define match =: 'p=(-?[[:digit:]]+),(-?[[:digit:]]+) v=(-?[[:digit:]]+),(-?[[:digit:]]+)' rxmatch y 2 2 $ ". y sublist~ }. match ) initial_state =: parse_line"1 > raw 'positions velocities' =: ({."2 ; {:"2) initial_state steps =: 100 size =: 101 103 step =: (size & |) @: + travel =: step (steps & *) quadrant =: (> & (<. size % 2)) - (< & (<. size % 2)) final_quadrants =: quadrant"1 @: travel"1 quadrant_ids =: 4 2 $ 1 1 _1 1 1 _1 _1 _1 result1 =: */ +/"1 quadrant_ids -:"1/ positions final_quadrants velocities render =: monad define |: 'O' (<"1 y)} size $ '.' ) pair_distances =: monad : 'y (| @: j./ @: -/"1)/ y' loop =: dyad define positions =. positions step"1 (velocities * x) for_i. i. 1000 do. time_number =. x + i * y mean_distance =. (+/ % #) , pair_distances positions if. mean_distance < 50 do. (render positions) (1!:2) 2 (": time_number, mean_distance) (1!:2) 2 (6!:3) 1 end. if. mean_distance < 35 do. break. end. positions =. positions step"1 (velocities * y) end. time_number result2 =: 11 loop 101
J
I think this puzzle is a bit of a missed opportunity. They could have provided inputs with no solution or with a line of solutions, so that the cost optimization becomes meaningful. As it is, you just have to carry out Cramer's rule in extended precision rational arithmetic.
load 'regex' data_file_name =: '13.data' raw =: cutopen fread data_file_name NB. a b sublist y gives elements [a..b) of y sublist =: ({~(+i.)/)~"1 _ parse_button =: monad define match =. 'X\+([[:digit:]]+), Y\+([[:digit:]]+)' rxmatch y ". (}. match) sublist y ) parse_prize =: monad define match =. 'X=([[:digit:]]+), Y=([[:digit:]]+)' rxmatch y ". (}. match) sublist y ) parse_machine =: monad define 3 2 $ (parse_button >0{y), (parse_button >1{y), (parse_prize >2{y) ) NB. x: converts to extended precision, which gives us rational arithmetic machines =: x: (parse_machine"1) _3 ]\ raw NB. A machine is represented by an array 3 2 $ ax ay bx by tx ty, where button NB. A moves the claw by ax ay, button B by bx by, and the target is at tx ty. NB. We are looking for nonnegative integer solutions to ax*a + bx*b = tx, NB. ay*a + by*b = ty; if there is more than one, we want the least by the cost NB. function 3*a + b. solution_rank =: monad define if. 0 ~: -/ . * }: y do. 0 NB. system is nonsingular elseif. */ (=/"1) 2 ]\ ({. % {:) |: y do. 1 NB. one equation is a multiple of the other else. _1 end. ) NB. solve0 yields the cost of solving a machine of solution rank 0 solve0 =: monad define d =. -/ . * }: y a =. (-/ . * 2 1 { y) % d b =. (-/ . * 0 2 { y) % d if. (a >: 0) * (a = <. a) * (b >: 0) * (b = <. b) do. b + 3 * a else. 0 end. ) NB. there are actually no machines of solution rank _1 or 1 in the test set result1 =: +/ solve0"_1 machines machines2 =: machines (+"2) 3 2 $ 0 0 0 0 10000000000000 10000000000000 NB. there are no machines of solution rank _1 or 1 in the modified set either result2 =: +/ solve0"_1 machines2
J
Implementing flood fill or something like that would have been smart, so I didn't do that. Instead I used a sparse-but-still-way-too-big-and-slow block matrix representation, which takes several minutes to compute the region partitions for the real problem. The rest is essentially simple, although counting edges has some picky details. The result is a lot of code though -- way more than has been typical up to now.
data_file_name =: '12.data' grid =: ,. > cutopen fread data_file_name data =: , grid 'rsize csize' =: $ grid size =: # data inbounds =: monad : '(*/ y >: 0 0) * (*/ y < rsize, csize)' coords =: ($ grid) & #: uncoords =: ($ grid) & #. neighbors =: monad : 'uncoords (#~ inbounds"1) (coords y) +"1 (4 2 $ 1 0 0 1 _1 0 0 _1)' components =: 1 ((i.size) ,. i.size)} 1 $. (size, size); (0 1); 0 NB. fuse (m, n) fuses together the components of linear indices m and n onto the NB. lesser of the two fuse =: monad define fused_row =. >./ y { components NB. 4 $. is a version of 1 I. that works on sparse arrays: it gives us the index array, NB. but it's rows of index vectors so we have to transpose to get just the column indices fused_indices =. {. |: 4 $. fused_row components =: 1 (, fused_indices (< @: ,"0/) fused_indices)} components ) NB. fuse_all fuses all adjacent pairs of cells according to the grid contents; this makes NB. a "block diagonal" matrix of 1's where the block index groups are components fuse_cols =: monad define for_r. i. rsize do. for_c. i. <: csize do. n =. uncoords (r, c) pair =. n, n + 1 if. =/ (pair { data) do. fuse pair end. end. end. components ) NB. To speed this up we only execute fusion once on each pair of adjacent contiguous groups, NB. since each row has already had its columns fused. fuse_rows =: monad define for_r. i. <: rsize do. cur_cell =. a: in_group =. 0 for_c. i. csize do. n =. uncoords (r, c) if. cur_cell ~: n { data do. cur_cell =. n { data in_group =. 0 end. pair =. n, n + csize if. =/ (pair { data) do. if. in_group = 1 do. continue. else. fuse pair in_group =. 1 end. else. in_group =. 0 end. end. end. components ) fuse_all =: fuse_rows @: fuse_cols NB. count_edges n counts the number of fenced edges, which is 4 minus the number of neighbor NB. cells in the same component component_neighbors =: monad : '(#~ ((= & (y { data)) @: ({ & data))) neighbors y' count_edges =: monad : '4 - # component_neighbors y' NB. components component_index n gives the least cell index in n's component component_index =: dyad : '<./ {. |: 4 $. y { x' NB. distinct components gives the list of component indices distinct_components =: monad : '~. 0 $. y component_index"_ 0 i.size' NB. components component_cells m gives the cell list of component m component_cells =: dyad : 'I. 0 $. y { x'"_ 0 NB. components area m gives the area of component m area =: (# @: component_cells)"_ 0 NB. components perimeter m gives the perimeter of component m perimeter =: (+/ @: (count_edges"0) @: component_cells)"_ 0 components =: fuse_all components result1 =: +/ components (area * perimeter) distinct_components components NB. cell edges are given coordinates as follows: horizontal edges are numbered according to the NB. cell they are above, so [0..rsize] x [0..csize), and vertical edges are numbered according to NB. the cell they are left of, so [0..rsize) x [0..csize]. Two adjacent (connected) cell edges NB. belong to the same component edge if they have a component cell on the same side. NB. cell_edges m gives the edge coordinates in the schema above of the cell with linear index m, NB. as a boxed list horizontal_edges;vertical_edges. cell_edges =: monad define 'r c' =. coords y neighbors =. component_neighbors y horiz_edges =. (-. ((y - csize), y + csize) e. neighbors) # 2 2 $ r, c, (>: r), c vert_edges =. (-. ((<: y), >: y) e. neighbors) # 2 2 $ r, c, r, >: c horiz_edges ; vert_edges ) NB. cells hconnected r c1 c2 if (r, c1) and (r, c2) are horizontally connected edges hconnected =: dyad define 'r c1 c2' =. y if. 1 < c2 - c1 do. 0 return. end. if. (0 = r) +. rsize = r do. 1 return. end. upper_neighbors =. (uncoords"1) 2 2 $ (<: r), c1, (<: r), c2 lower_neighbors =. (uncoords"1) 2 2 $ r, c1, r, c2 (*/ upper_neighbors e. x) +. (*/ lower_neighbors e. x) ) NB. cells vconnected c r1 r2 if (r1, c) and (r2, c) are vertically connected edges vconnected =: dyad define 'c r1 r2' =. y if. 1 < r2 - r1 do. 0 return. end. if. (0 = c) +. csize = c do. 1 return. end. left_neighbors =. (uncoords"1) 2 2 $ r1, (<: c), r2, <: c right_neighbors =. (uncoords"1) 2 2 $ r1, c, r2, c (*/ left_neighbors e. x) +. (*/ right_neighbors e. x) ) component_edges =: dyad define cells =. x component_cells y 'raw_horiz raw_vert' =. (< @: ;)"1 |: cell_edges"0 cells edge_pairs_of_row =. ((> @: {.) (,"0 1) ((2 & (]\)) @: > @: {:)) horiz_edge_groups =. ({. ;/.. {:) |: raw_horiz new_h_edges_per_row =. (-. @: (cells & hconnected)"1 &.>) (< @: edge_pairs_of_row)"1 horiz_edge_groups total_h_edges =. (# horiz_edge_groups) + +/ ; new_h_edges_per_row vert_edge_groups =. ({: ;/.. {.) |: raw_vert new_v_edges_per_row =. (-. @: (cells & vconnected)"1 &.>) (< @: edge_pairs_of_row)"1 vert_edge_groups total_v_edges =. (# vert_edge_groups) + +/ ; new_v_edges_per_row total_h_edges + total_v_edges ) result2 =: +/ components (area * (component_edges"_ 0)) distinct_components components
J
If one line of code needs five lines of comment, I'm not sure how much of an improvement the "expressive power" is! But I learned how to use J's group-by operator (/.
or /..
) and a trick with evoke gerund (`:0"1) to transform columns of a matrix separately. It might have been simpler to transpose and apply to rows.
data_file_name =: '11.data' data =: ". > cutopen fread data_file_name NB. split splits an even digit positive integer into left digits and right digits split =: ; @: ((10 & #.) &.>) @: (({.~ ; }.~) (-: @: #)) @: (10 & #.^:_1) NB. step consumes a single number and yields the boxed count-matrix of acting on that number step =: monad define if. y = 0 do. < 1 1 elseif. 2 | <. 10 ^. y do. < (split y) ,. 1 1 else. < (y * 2024), 1 end. ) NB. reduce_count_matrix consumes an unboxed count-matrix of shape n 2, left column being NB. the item and right being the count of that item, and reduces it so that each item NB. appears once and the counts are summed; it does not sort the items. Result is unboxed. NB. Read the vocabulary page for /.. to understand the grouped matrix ;/.. builds; the NB. gerund evoke `:0"1 then sums under boxing in the right coordinate of each row. reduce_count_matrix =: > @: (({. ` ((+/&.>) @: {:)) `:0"1) @: ({. ;/.. {:) @: |: initial_count_matrix =: reduce_count_matrix data ,. (# data) $ 1 NB. iterate consumes a count matrix and yields the result of stepping once across that NB. count matrix. There's a lot going on here. On rows (item, count) of the incoming count NB. matrix, (step @: {.) yields the (boxed count matrix) result of step item; NB. (< @: (1&,) @: {:) yields <(1, count); then *"1&.> multiplies those at rank 1 under NB. boxing. Finally raze and reduce. iterate =: reduce_count_matrix @: ; @: (((step @: {.) (*"1&.>) (< @: (1&,) @: {:))"1) count_pebbles =: +/ @: ({:"1) result1 =: count_pebbles iterate^:25 initial_count_matrix result2 =: count_pebbles iterate^:75 initial_count_matrix
Yes. I don't know whether this is a beehaw specific issue (that being my home instance) or a lemmy issue in general, but < and & are HTML escaped in all code blocks I see. Of course, this is substantially more painful for J code than many other languages.
J
Who needs recursion or search algorithms? Over here in line noise array hell, we have built-in sparse matrices! :)
data_file_name =: '10.data' grid =: "."0 ,. > cutopen fread data_file_name data =: , grid 'rsize csize' =: $ grid inbounds =: monad : '(*/ y >: 0 0) * (*/ y < rsize, csize)' coords =: ($ grid) & #: uncoords =: ($ grid) & #. NB. if n is the linear index of a point, neighbors n lists the linear indices NB. of its orthogonally adjacent points neighbors =: monad : 'uncoords (#~ inbounds"1) (coords y) +"1 (4 2 $ 1 0 0 1 _1 0 0 _1)' uphill1 =: dyad : '1 = (y { data) - (x { data)' uphill_neighbors =: monad : 'y ,. (#~ (y & uphill1)) neighbors y' adjacency_of =: monad define edges =. ; (< @: uphill_neighbors"0) i.#y NB. must explicitly specify fill of integer 0, default is float 1 edges} 1 $. ((#y), #y); (0 1); 0 ) adjacency =: adjacency_of data NB. maximum path length is 9 so take 9th power of adjacency matrix leads_to_matrix =: adjacency (+/ . *)^:8 adjacency leads_to =: dyad : '({ & leads_to_matrix) @: < x, y' trailheads =: I. data = 0 summits =: I. data = 9 scores =: trailheads leads_to"0/ summits result1 =: +/, 0 < scores result2 =: +/, scores
J
Mostly-imperative code in J never looks that nice, but at least the matrix management comes out fairly clean.
Part 2 is slow because I didn't cache the lengths of free intervals or the location of the leftmost free interval of a given length, instead just recalculating them every time.
One new-ish construct today is dyadic ]\
. The adverb \
applies its argument verb to sublists of its right argument list, the length of those sublists being specified by the absolute value of the left argument. If it's positive, the sublists overlap; if negative, they tile. The wrinkle is that monadic ]
is actually the identity function -- we actually want the sublists, not to do anything with them, so we apply the adverb \
to ]
. For example, _2 ]\ v
reshapes v
into a matrix of row length 2, without knowing the target length ahead of time like we would need to for $
.
data_file_name =: '9.data' input =: "."0 , > cutopen fread data_file_name compute_intervals =: monad define block_endpoints =. 0 , +/\ y block_intervals =. 2 ]\ block_endpoints result =. (<"2) 0 2 |: _2 ]\ block_intervals if. 2 | #y do. result =. result 1}~ (}: &.>) 1 { result end. result ) 'file_intervals free_intervals' =: compute_intervals input interval =: {. + (i. @: -~/) build_disk_map =: monad define disk_map =. (+/ input) $ 0 for_file_int. y do. disk_map =. file_int_index (interval file_int)} disk_map end. disk_map ) compact =: dyad define p =. <: # y NB. pointer to block we're currently moving for_free_int. x do. for_q. interval free_int do. NB. If p has descended past all compacted space, done if. p <: q do. goto_done. end. NB. Move content of block p to block q; mark block p free y =. (0 , p { y) (p , q)} y NB. Decrement p until we reach another file block p =. <: p while. 0 = p { y do. p =. <: p end. end. end. label_done. y ) disk_map =: build_disk_map file_intervals compacted_map =: free_intervals compact disk_map checksum =: +/ @: (* (i. @: #)) result1 =: checksum compacted_map move_file =: dyad define 'file_intervals free_intervals' =. x file_length =. -~/ y { file_intervals target_free_index =. 1 i.~ ((>: & file_length) @: -~/)"1 free_intervals if. (target_free_index < # free_intervals) do. 'a b' =. target_free_index { free_intervals if. a < {. y { file_intervals do. c =. a + file_length file_intervals =. (a , c) y} file_intervals free_intervals =. (c , b) target_free_index} free_intervals end. end. file_intervals ; free_intervals ) move_compact =: monad define for_i. |. i. # > 0 { y do. y =. y move_file i end. y ) move_compacted_map =: build_disk_map > 0 { move_compact compute_intervals input result2 =: checksum move_compacted_map
J
J really doesn't have hashes! Or anything like hashes! And it's really annoying after a while!
What it does have is automatic internal optimization via hashing of the "index of" operation m i. n
where m
is a fixed list (the object being searched) and n
is the query, which can vary. But as soon as you update m
the hash table is thrown away. And you still have to choose some kind of numeric key, or store a list of boxed pairs where the first coordinate is the key -- effectively this is an old-style Lisp association list, but with extra steps because you have to use boxing to defeat J's automatic array concatenation and reshaping. If you want non-cubical shapes (J calls these "ragged arrays"), or heterogeneous lists, you end up writing u &.>
a lot -- this means "unbox, apply u
then rebox". J arrays are required to be rectangular and homogeneous, but a boxed anything is a single atom just like a number is.
It's just a really bad choice of language if you want data structures other than essentially-cubical arrays. On the other hand, once you beat the list manipulation primitives into producing your 1970s Lisp data structure of choice, the rest of the program is as nice as it usually is.
data_file_name =: '8.data' grid =: ,. > cutopen fread data_file_name 'rsize csize' =: $ grid inbounds =: monad : '(*/ y >: 0 0) * (*/ y < rsize, csize)' antenna_types =: (#~ (~: & '.')) ~. , grid NB. list_antennas gives a list of boxed matrices of shape 2 n_k in cell k, where NB. n_k is the number of antennas of type k and the rows are coordinates of that type list_antennas =: monad define antenna_locs =. (# antenna_types) $ a: for_r. i. rsize do. for_c. i. csize do. cell =. y {~ <(r, c) if. '.' ~: cell do. at =. antenna_types i. cell antenna_locs =. ((<(r, c)) ,&.> at { antenna_locs) at} antenna_locs end. end. end. NB. _2 ]\ l reshapes l into length 2 rows without finding its length ahead of time (_2 & (]\))&.> antenna_locs ) NB. a1 pair_antinodes a2 gives the two antinodes from that pair pair_antinodes =: dyad : '(#~ inbounds"1) ((2 * x) - y) ,: (2 * y) - x' NB. if u is a symmetric dyad expecting rank 1 arguments, u on_pairs is a monad NB. expecting a list of rank 1 arguments, and yields the concatenation of x u y NB. where (x, y) is drawn from the (unordered) pairs of elements of the argument NB. see page_pairs in 5.ijs for a non-point-free version of pair enumeration on_pairs =: adverb define ; @: (< @: u/"2) @: ({~ (; @: (< @: (,~"0 i.)"0) @: i. @: #)) ) NB. antinodes antennas gives a list (may contain duplicates) of all the antinodes from NB. that set of antennas antinodes =: pair_antinodes on_pairs NB. on_antennas concatenates and uniquifies result lists from all antennas on_antennas =: adverb define ~. @: ; @: (u &.>) @: list_antennas ) result1 =: # antinodes on_antennas grid NB. a1 res_antinodes a2 gives the list of antinodes from that pair with resonance res_antinodes =: dyad define step =. (% +./) x - y NB. lazy: max_steps doesn't take location of x into account max_steps =. <. (rsize % 1 >. | 0 { step) <. (csize % 1 >. 1 { step) (#~ inbounds"1) x +"1 step *"1 0 i: max_steps ) result2 =: # res_antinodes on_pairs on_antennas grid
J
Didn't try to make it clever at all, so it's fairly slow (minutes, not seconds). Maybe rewriting foldl_ops
in terms of destructive array update would improve matters, but the biggest problem is that I don't skip unnecessary calculations (because we've already found a match or already reached too big a number). This is concise and follows clearly from the definitions, however.
data_file_name =: '7.data lines =: cutopen fread data_file_name NB. parse_line yields a boxed vector of length 2, target ; operands NB. &. is "under": u &. v is v^:_1 @: u @: v with right rank of v parse_line =: monad : '(". &. >) (>y) ({.~ ; (}.~ >:)) '':'' i.~ >y' NB. m foldl_ops n left folds n by the string of binary operators named by m, NB. as indices into the global operators, the leftmost element of m naming NB. an operator between the leftmost two elements of n. #m must be #n - 1. foldl_ops =: dyad define if. 1 >: # y do. {. y else. (}. x) foldl_ops (((operators @. ({. x))/ 2 {. y) , 2 }. y) end. ) NB. b digit_strings n enumerates i.b^n as right justified digit strings digit_strings =: dyad : '(y # x) #:"1 0 i. x ^ y' feasible =: dyad define operators =: x NB. global 'target operands' =. y +./ target = ((# operators) digit_strings (<: # operands)) foldl_ops"1 operands ) compute =: monad : '+/ ((> @: {.) * (y & feasible))"1 parse_line"0 lines' result1 =: compute +`* concat =: , &.: (10 & #.^:_1) result2 =: compute +`*`concat
J
Today's the first one where I feel like the choice of language is a disadvantage without compensating advantages. Or, at least, I don't know J well enough yet to use its compensating advantages for this kind of task, so what I end up with is Python 2 with obscure syntax and no associative data structures.
Also, I can't post my code, because apparently Lemmy is interpreting some of today's bizarre line noise as hostile and sanitizing it. It looks more or less like the other imperative solutions here, just with more punctuation.
J
This is a problem where J's biases lead one to a very different solution from most of the others. The natural representation of a directed graph in J is an adjacency matrix, and sorting is specified in terms of a permutation to apply rather than in terms of a comparator: x /: y
(respectively x \: y
) determines the permutation that would put y
in ascending (descending) order, then applies that permutation to x
.
data_file_name =: '5.data' lines =: cutopen fread data_file_name NB. manuals start with the first line where the index of a comma is < 5 start_of_manuals =: 1 i.~ 5 > ',' i.~"1 > lines NB. ". can't parse the | so replace it with a space edges =: ". (' ' & (2}))"1 > start_of_manuals {. lines NB. don't unbox and parse yet because they aren't all the same length manuals =: start_of_manuals }. lines max_page =: >./ , edges NB. adjacency matrix of the page partial ordering; e.i. makes identity matrix adjacency =: 1 (< edges)} e. i. >: max_page NB. ordered line is true if line is ordered according to the adjacency matrix ordered =: monad define pages =. ". > y NB. index pairs 0 <: i < j < n; box and raze to avoid array fill page_pairs =. ; (< @: (,~"0 i.)"0) i. # pages */ adjacency {~ <"1 pages {~ page_pairs ) midpoint =: ({~ (<. @: -: @: #)) @: ". @: > result1 =: +/ (ordered"0 * midpoint"0) manuals NB. toposort line yields the pages of line topologically sorted by adjacency NB. this is *not* a general topological sort but works for our restricted case: NB. we know that each individual manual will be totally ordered toposort =: monad define pages =. ". > y NB. for each page, count the pages which come after it, then sort descending pages \: +/"1 adjacency {~ <"1 pages ,"0/ pages ) NB. midpoint2 doesn't parse, but does remove trailing zeroes midpoint2 =: ({~ (<. @: -: @: #)) @: ({.~ (i. & 0)) result2 =: +/ (1 - ordered"0 manuals) * midpoint2"1 toposort"0 manuals
I've been reading your solutions! I have not spent any time with Factor at all, but the solutions you've put up look very nice and clean.
J
Unsurprisingly this is the kind of problem that J is really good at. The dyadic case (table) of the adverb /
is doing all the heavy lifting here: it makes a higher rank tensor by traversing items of the specified rank on each side and combining them according to the remaining frame of each side's shape. The hard part is arranging the arguments so that your resulting matrix has its axes in the correct order.
data_file_name =: '4.data' NB. cutopen yields boxed lines, so unbox them and ravel items to make a letter matrix grid =: ,. > cutopen fread data_file_name NB. pad the grid on every side with #'XMAS' - 1 spaces hpadded_grid =: ((' ' & ,) @: (, & ' '))"1 grid padded_grid =: (3 1 $ ' ') , hpadded_grid , (3 1 $ ' ') NB. traversal vectors directions =: 8 2 $ 1 0 1 1 0 1 _1 1 _1 0 _1 _1 0 _1 1 _1 NB. rpos cpos matches rdir cdir if the string starting at rpos cpos in NB. direction rdir cdir is the string we want matches =: 4 : 0 */ ,'XMAS' -: padded_grid {~ <"1 x +"1 y *"1 0 i. 4 )"1 positions =: (3 + i. 0 { $ grid) ,"0/ (3 + i. 1 { $ grid) result1 =: +/, positions matches/ directions NB. pairs of traversal vectors x_directions =: 4 2 2 $ 1 1 _1 1 1 1 1 _1 _1 _1 _1 1 _1 _1 1 _1 NB. rpos cpos x_matches 2 2 $ rdir1 cdir1 rdir2 cdir2 if there is an 'A' at NB. rpos cpos and the string in each of dir1 and dir2 centered at rpos cpos NB. is the string we want x_matches =: 4 : 0 NB. (2 2 $ rdir1 cdir1 rdir2 cdir2) *"1 0/ (_1 + i.3) yields a matrix NB. 2 3 $ (_1 * dir1) , (0 * dir1) , (1 * dir1) followed by the same for dir2 */ ,'MAS' -:"1 padded_grid {~ <"1 x +"1 y *"1 0/ _1 + i. 3 )"1 2 result2 =: +/, positions x_matches/ x_directions
Anybody else remember Haibane Renmei? or (more depressing, but less sad) Wolf's Rain?