Re: [Rd] gfortran 9 quantreg bug

2019-08-04 Thread Balasubramanian Narasimhan


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  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
>> 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


Re: [Rd] From .Fortran to .Call?

2020-12-22 Thread Balasubramanian Narasimhan
To deal with such Fortran issues in several packages I deal with, I 
wrote the SUtools package (https://github.com/bnaras/SUtools) that you 
can try.  The current version generates the registration assuming 
implicit Fortran naming conventions though. (I've been meaning to 
upgrade it to use the gfortran -fc-prototypes-external flag which should 
be easy; I might just finish that during these holidays.)


There's a vignette as well: 
https://bnaras.github.io/SUtools/articles/SUtools.html


-Naras


On 12/19/20 9:53 AM, Ivan Krylov wrote:

On Sat, 19 Dec 2020 17:04:59 +
"Koenker, Roger W"  wrote:


There are comments in various places, including R-extensions §5.4
suggesting that .Fortran is (nearly) deprecated and hinting that use
of .Call is more efficient and now preferred for packages.

My understanding of §5.4 and 5.5 is that explicit routine registration
is what's important for efficiency, and your package already does that
(i.e. calls R_registerRoutines()). The only two things left to add
would be types (REALSXP/INTSXP/...) and styles (R_ARG_IN,
R_ARG_OUT/...) of the arguments of each subroutine.

Switching to .Call makes sense if you want to change the interface of
your native subroutines to accept arbitrary heavily structured SEXPs
(and switching to .External could be useful if you wanted to play with
evaluation of the arguments).



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


Re: [Rd] From .Fortran to .Call?

2020-12-23 Thread Balasubramanian Narasimhan
I think it should be pretty easy to fix up SUtools to use the .Call 
instead of .Fortran following along the lines of


https://github.com/wrathematics/Romp

I too deal with a lot of f77 and so I will most likely finish it before 
the new year, if not earlier. (Would welcome testers besides myself.)


Incidentally, any idea of what the performance hit is, quantitatively? I 
confess I never paid attention to it myself as most Fortran code I use 
seems pretty fast, i.e. glmnet.


-Naras


On 12/23/20 3:57 AM, Koenker, Roger W wrote:

Thanks to all and best wishes for a better 2021.

Unfortunately I remain somewhat confused:

o  Bill reveals an elegant way to get from my rudimentary  registration 
setup to
one that would explicitly type the C interface functions,

o Ivan seems to suggest that there would be no performance gain from 
doing this.

o  Naras’s pcLasso package does use the explicit C typing, but then 
uses .Fortran
not .Call.

o  Avi uses .Call and cites the Romp package 
https://github.com/wrathematics/Romp
where it is asserted that "there is a (nearly) deprecated interface 
.Fortran() which you
should not use due to its large performance overhead.”

As the proverbial naive R (ab)user I’m left wondering:

o  if I updated my quantreg_init.c file in accordance with Bill’s 
suggestion could I
then simply change my .Fortran calls to .Call?

o  and if so, do I need to include ALL the fortran subroutines in my 
src directory
or only the ones called from R?

o  and in either case could I really expect to see a significant 
performance gain?

Finally, perhaps I should stipulate that my fortran is strictly f77, so no 
modern features
are in play, indeed most of the code is originally written in ratfor, Brian 
Kernighan’s
dialect from ancient times at Bell Labs.

Again,  thanks to all for any advice,
Roger



On Dec 23, 2020, at 1:11 AM, Avraham Adler  wrote:

Hello, Ivan.

I used .Call instead of .Fortran in the Delaporte package [1]. What
helped me out a lot was Drew Schmidt's Romp examples and descriptions
[2]. If you are more comfortable with the older Fortran interface,
Tomasz Kalinowski has a package which uses Fortran 2018 more
efficiently [3]. I haven't tried this last in practice, however.

Hope that helps,

Avi

[1] 
https://urldefense.com/v3/__https://CRAN.R-project.org/package=Delaporte__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPITBN5NK8$
[2] 
https://urldefense.com/v3/__https://github.com/wrathematics/Romp__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPISF5aCYs$
[3] 
https://urldefense.com/v3/__https://github.com/t-kalinowski/RFI__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPIbwXmXqY$

Tomasz Kalinowski



On Tue, Dec 22, 2020 at 7:24 PM Balasubramanian Narasimhan
 wrote:

To deal with such Fortran issues in several packages I deal with, I
wrote the SUtools package 
(https://urldefense.com/v3/__https://github.com/bnaras/SUtools__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPIJ5BbDwA$
 ) that you
can try.  The current version generates the registration assuming
implicit Fortran naming conventions though. (I've been meaning to
upgrade it to use the gfortran -fc-prototypes-external flag which should
be easy; I might just finish that during these holidays.)

There's a vignette as well:
https://urldefense.com/v3/__https://bnaras.github.io/SUtools/articles/SUtools.html__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPITq9-Quc$

-Naras


On 12/19/20 9:53 AM, Ivan Krylov wrote:

On Sat, 19 Dec 2020 17:04:59 +
"Koenker, Roger W"  wrote:


There are comments in various places, including R-extensions §5.4
suggesting that .Fortran is (nearly) deprecated and hinting that use
of .Call is more efficient and now preferred for packages.

My understanding of §5.4 and 5.5 is that explicit routine registration
is what's important for efficiency, and your package already does that
(i.e. calls R_registerRoutines()). The only two things left to add
would be types (REALSXP/INTSXP/...) and styles (R_ARG_IN,
R_ARG_OUT/...) of the arguments of each subroutine.

Switching to .Call makes sense if you want to change the interface of
your native subroutines to accept arbitrary heavily structured SEXPs
(and switching to .External could be useful if you wanted to play with
evaluation of the arguments).


__
R-devel@r-project.org mailing list
https://urldefense.com/v3/__https://stat.ethz.ch/mailman/listinfo/r-devel__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPIr_nqkqg$


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


Re: [Rd] From .Fortran to .Call?

2020-12-23 Thread Balasubramanian Narasimhan
Also, just came to know about dotcall64::.C64() (on CRAN) which allows 
for Fortran to be called using .Call().


-Naras

On 12/23/20 8:34 AM, Balasubramanian Narasimhan wrote:
I think it should be pretty easy to fix up SUtools to use the .Call 
instead of .Fortran following along the lines of


https://github.com/wrathematics/Romp

I too deal with a lot of f77 and so I will most likely finish it 
before the new year, if not earlier. (Would welcome testers besides 
myself.)


Incidentally, any idea of what the performance hit is, quantitatively? 
I confess I never paid attention to it myself as most Fortran code I 
use seems pretty fast, i.e. glmnet.


-Naras


On 12/23/20 3:57 AM, Koenker, Roger W wrote:

Thanks to all and best wishes for a better 2021.

Unfortunately I remain somewhat confused:

o  Bill reveals an elegant way to get from my rudimentary 
registration setup to

one that would explicitly type the C interface functions,

o Ivan seems to suggest that there would be no performance gain 
from doing this.


o  Naras’s pcLasso package does use the explicit C typing, but 
then uses .Fortran

not .Call.

o  Avi uses .Call and cites the Romp package 
https://github.com/wrathematics/Romp
where it is asserted that "there is a (nearly) deprecated 
interface .Fortran() which you

should not use due to its large performance overhead.”

As the proverbial naive R (ab)user I’m left wondering:

o  if I updated my quantreg_init.c file in accordance with Bill’s 
suggestion could I

then simply change my .Fortran calls to .Call?

o  and if so, do I need to include ALL the fortran subroutines in 
my src directory

or only the ones called from R?

o  and in either case could I really expect to see a significant 
performance gain?


Finally, perhaps I should stipulate that my fortran is strictly f77, 
so no modern features
are in play, indeed most of the code is originally written in ratfor, 
Brian Kernighan’s

dialect from ancient times at Bell Labs.

Again,  thanks to all for any advice,
Roger


On Dec 23, 2020, at 1:11 AM, Avraham Adler  
wrote:


Hello, Ivan.

I used .Call instead of .Fortran in the Delaporte package [1]. What
helped me out a lot was Drew Schmidt's Romp examples and descriptions
[2]. If you are more comfortable with the older Fortran interface,
Tomasz Kalinowski has a package which uses Fortran 2018 more
efficiently [3]. I haven't tried this last in practice, however.

Hope that helps,

Avi

[1] 
https://urldefense.com/v3/__https://CRAN.R-project.org/package=Delaporte__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPITBN5NK8$
[2] 
https://urldefense.com/v3/__https://github.com/wrathematics/Romp__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPISF5aCYs$
[3] 
https://urldefense.com/v3/__https://github.com/t-kalinowski/RFI__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPIbwXmXqY$


Tomasz Kalinowski



On Tue, Dec 22, 2020 at 7:24 PM Balasubramanian Narasimhan
 wrote:

To deal with such Fortran issues in several packages I deal with, I
wrote the SUtools package 
(https://urldefense.com/v3/__https://github.com/bnaras/SUtools__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPIJ5BbDwA$ 
) that you

can try.  The current version generates the registration assuming
implicit Fortran naming conventions though. (I've been meaning to
upgrade it to use the gfortran -fc-prototypes-external flag which 
should

be easy; I might just finish that during these holidays.)

There's a vignette as well:
https://urldefense.com/v3/__https://bnaras.github.io/SUtools/articles/SUtools.html__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPITq9-Quc$ 



-Naras


On 12/19/20 9:53 AM, Ivan Krylov wrote:

On Sat, 19 Dec 2020 17:04:59 +
"Koenker, Roger W"  wrote:


There are comments in various places, including R-extensions §5.4
suggesting that .Fortran is (nearly) deprecated and hinting that use
of .Call is more efficient and now preferred for packages.
My understanding of §5.4 and 5.5 is that explicit routine 
registration
is what's important for efficiency, and your package already does 
that

(i.e. calls R_registerRoutines()). The only two things left to add
would be types (REALSXP/INTSXP/...) and styles (R_ARG_IN,
R_ARG_OUT/...) of the arguments of each subroutine.

Switching to .Call makes sense if you want to change the interface of
your native subroutines to accept arbitrary heavily structured SEXPs
(and switching to .External could be useful if you wanted to play 
with

evaluation of the arguments).


__
R-devel@r-project.org mailing list
https://urldefense.com/v3/__https://stat.ethz.ch/mailman/listinfo/r-devel__;!!DZ3fjg!s1-ihrZ9DPUtXpxdIpJPA1VedpZFt12Ahmn4CycOmile_uSahFZnJPn_5KPIr_nqkqg$ 



__
R-devel@r-project.org mailing list

Re: [Rd] Possible x11 window manager window aggregation under one icon?

2021-03-22 Thread Balasubramanian Narasimhan

Confession: haven't done this in decades.

Isn't the usual way to use 'xwininfo' to figure out the information 
about any X window and set a specific resource in the .X11defaults or 
equivalent?  Also doing the same with windows that aggregate could yield 
a common resource, perhaps?


-Naras

On 3/20/21 9:51 AM, Dirk Eddelbuettel wrote:

[ I hope the Subject: is arcane enough to reduce readership to a handful :) ]

Running the default window manager in the Linux distribution I am running,
multiple 'windows' of the same program are usually aggregated under one icon.
I typically have numerous (gnome) terminals, several top-level emacs windows,
likely more than brower window (even with tabs) and so on. They all aggregate
under the top-level icon

R plots however all have one each. Needless to say I may also have more than
one plot device open...  Would anyone know how we can force these to
aggregate under just one?  I had some digital fingerprints on the .desktop
file that ships with simply because someone first sent it to me as a patch
for the Debian package. But I know nuttin' about the XDG desktop
specification and all that. I had one idea regarding window titles, but those
are different for the terminals and emacs windows too.  Anybody have an idea?

Dirk



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


Re: [Rd] subset argument in nls() and possibly other functions

2021-07-14 Thread Balasubramanian Narasimhan
For the example provided below, the subsetting happens in evaluating the 
call to stats::model.formula in line 583 of nls.R 
(https://github.com/wch/r-source/blob/e91be22f6f37644e5a0ba74a3dfe504a3a29e9f7/src/library/stats/R/nls.R#L583) 
returning an appropriate (subsetted) data frame.


-Naras

On 7/13/21 4:21 PM, J C Nash wrote:

In mentoring and participating in a Google Summer of Code project "Improvements to 
nls()",
I've not found examples of use of the "subset" argument in the call to nls(). 
Moreover,
in searching through the source code for the various functions related to 
nls(), I can't
seem to find where subset is used, but a simple example, included below, 
indicates it works.
Three approaches all seem to give the same results.

Can someone point to documentation or code so we can make sure we get our 
revised programs
to work properly? The aim is to make them more maintainable and provide 
maintainer documentation,
along with some improved functionality. We seem, for example, to already be 
able to offer
analytic derivatives where they are feasible, and should be able to add 
Marquardt-Levenberg
stabilization as an option.

Note that this "subset" does not seem to be the "subset()" function of R.

John Nash

# CroucherSubset.R -- https://walkingrandomly.com/?p=5254

xdata = c(-2,-1.64,-1.33,-0.7,0,0.45,1.2,1.64,2.32,2.9)
ydata = 
c(0.699369,0.700462,0.695354,1.03905,1.97389,2.41143,1.91091,0.919576,-0.730975,-1.42001)
Cform <- ydata ~ p1*cos(p2*xdata) + p2*sin(p1*xdata)
Cstart<-list(p1=1,p2=0.2)
Cdata<-data.frame(xdata, ydata)
Csubset<-1:8 # just first 8 points

# Original problem - no subset
fit0 = nls(ydata ~ p1*cos(p2*xdata) + p2*sin(p1*xdata), data=Cdata, 
start=list(p1=1,p2=.2))
summary(fit0)

# via subset argument
fit1 = nls(ydata ~ p1*cos(p2*xdata) + p2*sin(p1*xdata), data=Cdata, 
start=list(p1=1,p2=.2), subset=Csubset)
summary(fit1)

# via explicit subsetting
Csdata <- Cdata[Csubset, ]
Csdata
fit2 = nls(ydata ~ p1*cos(p2*xdata) + p2*sin(p1*xdata), data=Csdata, 
start=list(p1=1,p2=.2))
summary(fit2)

# via weights -- seems to give correct observation count if zeros not recognized
wts <- c(rep(1,8), rep(0,2))
fit3 = nls(ydata ~ p1*cos(p2*xdata) + p2*sin(p1*xdata), data=Cdata, 
weights=wts, start=list(p1=1,p2=.2))
summary(fit3)

__
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


[Rd] FLIBS in MacOS M1 binary at odds with documentation for optional libraries/tools

2021-11-01 Thread Balasubramanian Narasimhan
The Mac OS M1 pre-built binary arrives with a 
/Library/Frameworks/R.framework/Resources/etc/Makevars containing

FLIBS =  
-L/Volumes/Builds/opt/R/arm64/gfortran/lib/gcc/aarch64-apple-darwin20.2.0/11.0.0
 -L/Volumes/Builds/opt/R/arm64/gfortran/lib/gcc 
-L/Volumes/Builds/opt/R/arm64/gfortran/lib -lgfortran -lemutls_w -lm

This is inconsistent with what is at said at the top of 
https://mac.r-project.org/libs-arm64/: that all binaries live in 
/opt/R/arm64, not /Volumes/Builds/opt/R/arm64.

So no one would be able to build a source package containing Fortran 
without either modifying Makevars or creating symbolic links.

-Naras


[[alternative HTML version deleted]]

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


Re: [Rd] FLIBS in MacOS M1 binary at odds with documentation for optional libraries/tools

2021-11-02 Thread Balasubramanian Narasimhan
Thanks, Simon.  I only had sporadic access to a M1 laptop but now 
actually have one. Will try to do my part.


Best,

-Naras

On 11/1/21 8:22 PM, Simon Urbanek wrote:

Naras,

thanks. It seems that the FLIBS check resolves symlinks, unfortunately (all 
others are fine).

I would like to remind people that reports are a lot more useful *before* the 
release - that's why we publish RCs.

Thanks,
Simon



On Nov 2, 2021, at 3:03 PM, Balasubramanian Narasimhan  
wrote:

The Mac OS M1 pre-built binary arrives with a
/Library/Frameworks/R.framework/Resources/etc/Makevars containing

FLIBS =  
-L/Volumes/Builds/opt/R/arm64/gfortran/lib/gcc/aarch64-apple-darwin20.2.0/11.0.0
 -L/Volumes/Builds/opt/R/arm64/gfortran/lib/gcc 
-L/Volumes/Builds/opt/R/arm64/gfortran/lib -lgfortran -lemutls_w -lm

This is inconsistent with what is at said at the top of
https://mac.r-project.org/libs-arm64/: that all binaries live in
/opt/R/arm64, not /Volumes/Builds/opt/R/arm64.

So no one would be able to build a source package containing Fortran
without either modifying Makevars or creating symbolic links.

-Naras


[[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


Re: [Rd] f951.exe: sorry, unimplemented: 64-bit mode not compiled

2012-05-08 Thread Balasubramanian Narasimhan
The original post below refers to an issue that arose with glmnet. It 
has since been fixed but the underlying problem (I believe) is a bug in 
gcc/gfortran 2.6.3 toolchain.  Here is a reproducible example, test.f90.


program dblbug
  real :: x, y
  x=2
  y=exp(dble(x))
end program dblbug

Compile with gfortran -fdefault-real-8 -o test test.f90.

The program will crash on Windows but not on i386 or x86_64 linux (same 
version of toolchain) but I think that says nothing.


Note: The glmnet code was originally written for single precision and 
hence the flag -fdefault-real-8. The fix was to just to remove the "dble."


-Naras



On 5/4/12 6:58 PM, Simon Urbanek wrote:

On May 4, 2012, at 8:48 PM, Spencer Graves wrote:


Hello:


  Under my Windows 7 system, "R CMD check DiercxkSpline_1.1-5.tar.gz" fails 
because:


f951.exe: sorry, unimplemented: 64-bit mode not compiled in


This typically means that you're using the wrong (old) compiler. The new MinGW 
compilers support both -m32 and -m64. You have to set the PATH to the new 
compilers (in the gcc-4.6.3 subdirectory of Rtools) *before* any old compilers 
in Rtools.

Cheers,
Simon



make: *** [bispev.o] Error 1
gfortran -m64 -O2  -mtune=core2 -c bispev.f -o bispev.o
f951.exe: sorry, unimplemented: 64-bit mode not compiled in

make: *** [bispev.o] Error 1
ERROR: compilation failed for package 'DierckxSpline'


  A similar problem was reported for package "glmnet" 
(http://stackoverflow.com/questions/10291189/compiling-glmnet-failed-in-windows) plus one with R 
2.14.2 
(http://r.789695.n4.nabble.com/Problems-when-building-a-package-for-Windows-64-td4464488.html).  
However, I get this with R 2.15.0 and the latest R tools (reinstalled earlier today).  On R-Forge, 
DierckxSpline has "Build status:  Current", which suggests that R-Forge does NOT have 
this problem.  I read through the two replies to these two earlier questions without seeing how to 
fix my problem.





  Thanks in advance for any suggestions.


  Spencer Graves

__
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


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


[Rd] Matrix 1.6.2+ versus Matrix 1.6.2-

2023-11-22 Thread Balasubramanian Narasimhan
Package Rmosek compiles fine using Matrix versions 1.6.2- but not with 
anything beyond Matrix 1.6.2.  (FYI, Rmosek provides R interfaces to the 
excellent MOSEK solver; academic licenses are free.)

Here is the error message:

rmsk_obj_matrices.cc:50:9: error: use of undeclared identifier 
'Matrix_isclass_Csparse'
    50 | if (Matrix_isclass_Csparse(val)) {
   | ^
rmsk_obj_matrices.cc:171:9: error: use of undeclared identifier 
'Matrix_isclass_triplet'
   171 | if (Matrix_isclass_triplet(val)) {
   | ^
rmsk_obj_matrices.cc:225:24: error: use of undeclared identifier 
'M_chm_triplet_to_SEXP'
   225 |   matrixhandle.protect(M_chm_triplet_to_SEXP(tmp, 0, 0, 0, NULL, 
R_NilValue));

These API entry points are no longer in the recent headers. My quick 
examination shows that the first two seem like mostly R API stuff and so 
can be copied over to Rmosek easily but the last one looks more involved 
in my cursory examination.

I was going to let the author of Rmosek know, but I do not see any 
mention of these API entries going away in the NEWS for Matrix.

Would be good to point the author to a suggested approach or even 
provide the beginnings of a fix. Any thoughts, particularly by Matrix 
authors (Martin, Mikael)?

Thanks in advance.

-Naras


[[alternative HTML version deleted]]

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


Re: [Rd] Matrix 1.6.2+ versus Matrix 1.6.2-

2023-11-22 Thread Balasubramanian Narasimhan

Thanks Mikael.

[I too wondered if this topic was appropriate for the list and in the 
end thought it might be. We can probably take this offline after this 
exchange and summarize if appropriate.]


The actual source of the package is here: 
https://download.mosek.com/R/10.1/src/contrib/Rmosek_10.1.14.tar.gz


and requires a download of the optimizer first using an academic 
license: https://www.mosek.com/products/academic-licenses/


The optimizer typically installs under ~/mosek.

Then one installs Rmosek from CRAN as usual and follows the instructions 
it emits as it is loaded. The installation needs to know the Mosek bin 
directory: on a mac it is "~/mosek/10.1/tools/platform/osx64x86/bin". 
That begins the source installation process.


-Naras


On 11/22/23 1:14 PM, Mikael Jagan wrote:

Naras,

Thanks.  I'm a bit confused, because Rmosek does not declare Matrix as a
dependency:

    > tools::package_dependencies("Rmosek", which = "all")[[1L]]
    [1] "pkgbuild"

nor does it contain code needing compilation:

    > packageDescription("Rmosek", fields="NeedsCompilation")
    [1] "no"

Can you explain the nature of the dependency and how I can reproduce your
output?  Is an _external_ library somehow linking Matrix ... ?

Note that the 3 removed entry points were unused by all reverse LinkingTo
on CRAN and BioC at the time that Matrix 1.6-2 was released.  We can
suggest replacements (probably off list; I don't know that R-devel is the
right forum) but only if we are able to see the code being compiled ...

Mikael

> Package Rmosek compiles fine using Matrix versions 1.6.2- but not with
> anything beyond Matrix 1.6.2.  (FYI, Rmosek provides R interfaces to 
the

> excellent MOSEK solver; academic licenses are free.)
>
> Here is the error message:
>
> rmsk_obj_matrices.cc:50:9: error: use of undeclared identifier 
'Matrix_isclass_Csparse'

> 50 | if (Matrix_isclass_Csparse(val)) {
>    | ^
> rmsk_obj_matrices.cc:171:9: error: use of undeclared identifier 
'Matrix_isclass_triplet'

>    171 | if (Matrix_isclass_triplet(val)) {
>    | ^
> rmsk_obj_matrices.cc:225:24: error: use of undeclared identifier 
'M_chm_triplet_to_SEXP'
>    225 | matrixhandle.protect(M_chm_triplet_to_SEXP(tmp, 0, 0, 
0, NULL, R_NilValue));

>
> These API entry points are no longer in the recent headers. My quick
> examination shows that the first two seem like mostly R API stuff 
and so
> can be copied over to Rmosek easily but the last one looks more 
involved

> in my cursory examination.
>
> I was going to let the author of Rmosek know, but I do not see any
> mention of these API entries going away in the NEWS for Matrix.
>
> Would be good to point the author to a suggested approach or even
> provide the beginnings of a fix. Any thoughts, particularly by Matrix
> authors (Martin, Mikael)?
>
> Thanks in advance.
>
> -Naras


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