• 0 Posts
  • 5 Comments
Joined 2 years ago
cake
Cake day: June 11th, 2023

help-circle
  • 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
    


  • 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