While working through this year’s Advent of Code Day 2 challenge (I know, I’ve been stuck here for a while now  ), I ran across this issue with deferred length character variables, a.k.a.
), I ran across this issue with deferred length character variables, a.k.a. character(len=:), allocatable when trying to match the color string.
  INTEGER, PARAMETER :: ncolors = 3
  TYPE :: color
    CHARACTER(LEN=:), ALLOCATABLE :: name
    INTEGER :: limit
  END TYPE color
  TYPE(color) :: colors(ncolors)
  INTEGER :: c, i, j, curi, curf, ncubes, game_nrounds, round_ncolors, pos_colon
  INTEGER, ALLOCATABLE :: pos_semicolons(:), pos_commas(:), cur_color(:)
  CHARACTER(LEN=:), ALLOCATABLE :: line, word, color_str
  CHARACTER(LEN=1), ALLOCATABLE :: strarr(:)
:
  colors(1) = color('red', 12)
  colors(2) = color('green', 13)
  colors(3) = color('blue', 14)
:
  ! Read line from input file
:
    ! Parse line
    ALLOCATE(strarr(LEN(line)))
    strarr = [(line(c:c), c = 1, LEN(line))]
    pos_colon = SCAN(line, ':')
    pos_semicolons = [pos_colon, PACK([(c, c = 1, LEN(line))], strarr == ';'), LEN(line)+1]
    game_nrounds = SIZE(pos_semicolons) - 1
    DO i = 1, game_nrounds
      curi = pos_semicolons(i)
      curf = pos_semicolons(i+1)
      pos_commas = [curi, PACK([(c, c = curi+1, curf-1)], strarr(curi+1:curf-1) == ','), curf]
      round_ncolors = SIZE(pos_commas) - 1
      DO j = 1, round_ncolors
        curi = pos_commas(j)
        curf = pos_commas(j+1)
        color_str = line(curi+1:curf-1)
        READ(color_str, *) ncubes, word
        cur_color = PACK([(c, c = 1, ncolors)], colors(:)%name == word)
:
Of course, line is a single line read from the input file. The error message that GFortran 13.1.0 spews out is
02a.f90:101:48:
  101 |         cur_color = PACK([(c, c = 1, ncolors)], colors(:)%name == word)
      |                                                1
Error: Component to the right of a part reference with nonzero rank must not have the ALLOCATABLE attribute at (1)
Any help would be appreciated.