On 8/4/19 7:26 AM, Berend Hasselman wrote:
> Roger,
>
> I have run
>
>       gfortran -c -fsyntax-only -fimplicit-none -Wall -pedantic rqbr.f
>
> in the src folder of quantreg.
>
> There are many warnings about defined but not used labels.
> Also two errors such as "Symbol ‘in’ at (1) has no IMPLICIT type".
> And warnings such as: Warning: "Possible change of value in conversion from 
> REAL(8) to INTEGER(4)  at ..."
>
> No offense intended but this fortran code is awful. I wouldn't want to debug 
> this before an extensive cleanup by
> getting rid of as many numerical labels as possible, indenting and doing 
> something about the warnings "Possible change of value ...".

The unused labels at least can be removed automatically at least for 
fixed form along the lines shown in steps 8 and 9 of

https://bnaras.github.io/SUtools/articles/SUtools.html

which pertain to lines 261--281 of

https://github.com/bnaras/SUtools/blob/master/R/process.R

In fact, here it is, excerpted.

library(stringr)
code_lines  <- readLines(con = "rqbr.f")
cat("Running gfortran to detect warning lines on unused labels\n")
system2(command = "gfortran",
         args = c("-Wunused", "-c", "rqbr.f", "-o", "temp.o"),
         stderr = "gfortran.out")
cat("Scanning gfortran output for warnings on unusued labels\n")
warnings <- readLines("gfortran.out")
line_numbers <- grep('rqbr.f', warnings)
label_warning_line_numbers <- grep(pattern = "^Warning: Label [0-9]+ at", 
warnings)
just_warnings <- sum(grepl('Warning:', warnings))

nW <- length(label_warning_line_numbers)
for (i in seq_len(nW)) {
     offending_line <- 
as.integer(stringr::str_extract(warnings[line_numbers[i]], pattern = 
"([0-9]+)"))
     code_line <- code_lines[offending_line]
     offending_label <- 
stringr::str_extract(warnings[label_warning_line_numbers[i]],
                                             pattern = "([0-9]+)")
     code_lines[offending_line] <- sub(pattern = offending_label,
                                       replacement = str_pad("", width = 
nchar(offending_label)),
                                       x = code_lines[offending_line])
}
writeLines(code_lines, con = "rqbr-new.f")

-Naras

> This is going to be very difficult.
>
> Berend Hasselman
>
>> On 4 Aug 2019, at 08:48, Koenker, Roger W <rkoen...@illinois.edu> wrote:
>>
>> I’d like to solicit some advice on a debugging problem I have in the 
>> quantreg package.
>> Kurt and Brian have reported to me that on Debian machines with gfortran 9
>>
>> library(quantreg)
>> f = summary(rq(foodexp ~ income, data = engel, tau = 1:4/5))
>> plot(f)
>>
>> fails because summary() produces bogus estimates of the coefficient bounds.
>> This example has been around in my R package from the earliest days of R, and
>> before that in various incarnations of S.  The culprit is apparently rqbr.f 
>> which is
>> even more ancient, but must have something that gfortran 9 doesn’t approve 
>> of.
>>
>> I note that in R-devel there have been some other issues with gfortran 9, 
>> but these seem
>> unrelated to my problem.  Not having access to a machine with an R/gfortran9
>> configuration, I can’t  apply my rudimentary debugging methods.  I’ve 
>> considered
>> trying to build gfortran on my mac air and then building R from source, but 
>> before
>> going down this road, I wondered whether others had other suggestions, or
>> advice about  my proposed route.  As far as I can see there are not yet
>> binaries for gfortran 9 for osx.
>>
>> Thanks,
>> Roger
>>
>> Roger Koenker
>> r.koen...@ucl.ac.uk<mailto:r.koen...@ucl.ac.uk>
>> Department of Economics, UCL
>> London  WC1H 0AX.
>>
>>
>>
>>      [[alternative HTML version deleted]]
>>
>> ______________________________________________
>> R-devel@r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
> ______________________________________________
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel

        [[alternative HTML version deleted]]

______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel

Reply via email to