Conflict between defined assignment and intrinsic assignment (with nagfor)?












4














Intrinsic polymorphic assignment is a recent feature of some Fortran compilers (e.g. ifort 18, nagfor 6.2) that is not available in older versions (e.g. ifort 17, gfortran 6.3). A well-known solution that works with these older versions is to use a defined assignment as in the example below (taken and adapted from the book of Chivers and Sleightholme):



module deftypes  
type, abstract :: shape_t
integer :: x = 0, y = 0
end type shape_t

type, extends(shape_t) :: circle_t
integer :: radius = 0
end type circle_t

interface assignment(=)
module procedure generic_shape_assign
end interface

contains
subroutine generic_shape_assign ( lhs, rhs )
class(shape_t), intent(in ) :: rhs
class(shape_t), allocatable, intent(out) :: lhs
print*,' --> in generic_shape_assign'
allocate(lhs, source = rhs)
end subroutine generic_shape_assign
end module deftypes

program check_assign
use deftypes
implicit none
class(shape_t), allocatable :: myshape
type (circle_t) :: mycirc1, mycirc2

mycirc1 = circle_t ( 1, 2, 3 )

print*,'A polymorphic assignment: myshape = mycirc1'
myshape = mycirc1

print*,'An intrinsic assignment: mycirc2 = mycirc1'
mycirc2 = mycirc1
end program check_assign


This example, compiles and works well with ifort 15.0.3 and gfortran 6.3.0. But with nagfor 6.2 I get the following error during the compilation (for the line mycirc2=mycirc1):



Error: check_assign.f90, line 41: Incorrect data type CIRCLE_T (expected SHAPE_T) for argument LHS (no. 1) of GENERIC_SHAPE_ASSIGN  


It's not clear to me why this compiler is trying to use the defined assignment in the instruction mycirc2 = mycirc1 while these two variables are not allocatable polymorphic ones.



Of course, if I delete the defined assignment it works with nagfor but not with the other old compilers. Any idea where this error came from and how to get around it?










share|improve this question





























    4














    Intrinsic polymorphic assignment is a recent feature of some Fortran compilers (e.g. ifort 18, nagfor 6.2) that is not available in older versions (e.g. ifort 17, gfortran 6.3). A well-known solution that works with these older versions is to use a defined assignment as in the example below (taken and adapted from the book of Chivers and Sleightholme):



    module deftypes  
    type, abstract :: shape_t
    integer :: x = 0, y = 0
    end type shape_t

    type, extends(shape_t) :: circle_t
    integer :: radius = 0
    end type circle_t

    interface assignment(=)
    module procedure generic_shape_assign
    end interface

    contains
    subroutine generic_shape_assign ( lhs, rhs )
    class(shape_t), intent(in ) :: rhs
    class(shape_t), allocatable, intent(out) :: lhs
    print*,' --> in generic_shape_assign'
    allocate(lhs, source = rhs)
    end subroutine generic_shape_assign
    end module deftypes

    program check_assign
    use deftypes
    implicit none
    class(shape_t), allocatable :: myshape
    type (circle_t) :: mycirc1, mycirc2

    mycirc1 = circle_t ( 1, 2, 3 )

    print*,'A polymorphic assignment: myshape = mycirc1'
    myshape = mycirc1

    print*,'An intrinsic assignment: mycirc2 = mycirc1'
    mycirc2 = mycirc1
    end program check_assign


    This example, compiles and works well with ifort 15.0.3 and gfortran 6.3.0. But with nagfor 6.2 I get the following error during the compilation (for the line mycirc2=mycirc1):



    Error: check_assign.f90, line 41: Incorrect data type CIRCLE_T (expected SHAPE_T) for argument LHS (no. 1) of GENERIC_SHAPE_ASSIGN  


    It's not clear to me why this compiler is trying to use the defined assignment in the instruction mycirc2 = mycirc1 while these two variables are not allocatable polymorphic ones.



    Of course, if I delete the defined assignment it works with nagfor but not with the other old compilers. Any idea where this error came from and how to get around it?










    share|improve this question



























      4












      4








      4







      Intrinsic polymorphic assignment is a recent feature of some Fortran compilers (e.g. ifort 18, nagfor 6.2) that is not available in older versions (e.g. ifort 17, gfortran 6.3). A well-known solution that works with these older versions is to use a defined assignment as in the example below (taken and adapted from the book of Chivers and Sleightholme):



      module deftypes  
      type, abstract :: shape_t
      integer :: x = 0, y = 0
      end type shape_t

      type, extends(shape_t) :: circle_t
      integer :: radius = 0
      end type circle_t

      interface assignment(=)
      module procedure generic_shape_assign
      end interface

      contains
      subroutine generic_shape_assign ( lhs, rhs )
      class(shape_t), intent(in ) :: rhs
      class(shape_t), allocatable, intent(out) :: lhs
      print*,' --> in generic_shape_assign'
      allocate(lhs, source = rhs)
      end subroutine generic_shape_assign
      end module deftypes

      program check_assign
      use deftypes
      implicit none
      class(shape_t), allocatable :: myshape
      type (circle_t) :: mycirc1, mycirc2

      mycirc1 = circle_t ( 1, 2, 3 )

      print*,'A polymorphic assignment: myshape = mycirc1'
      myshape = mycirc1

      print*,'An intrinsic assignment: mycirc2 = mycirc1'
      mycirc2 = mycirc1
      end program check_assign


      This example, compiles and works well with ifort 15.0.3 and gfortran 6.3.0. But with nagfor 6.2 I get the following error during the compilation (for the line mycirc2=mycirc1):



      Error: check_assign.f90, line 41: Incorrect data type CIRCLE_T (expected SHAPE_T) for argument LHS (no. 1) of GENERIC_SHAPE_ASSIGN  


      It's not clear to me why this compiler is trying to use the defined assignment in the instruction mycirc2 = mycirc1 while these two variables are not allocatable polymorphic ones.



      Of course, if I delete the defined assignment it works with nagfor but not with the other old compilers. Any idea where this error came from and how to get around it?










      share|improve this question















      Intrinsic polymorphic assignment is a recent feature of some Fortran compilers (e.g. ifort 18, nagfor 6.2) that is not available in older versions (e.g. ifort 17, gfortran 6.3). A well-known solution that works with these older versions is to use a defined assignment as in the example below (taken and adapted from the book of Chivers and Sleightholme):



      module deftypes  
      type, abstract :: shape_t
      integer :: x = 0, y = 0
      end type shape_t

      type, extends(shape_t) :: circle_t
      integer :: radius = 0
      end type circle_t

      interface assignment(=)
      module procedure generic_shape_assign
      end interface

      contains
      subroutine generic_shape_assign ( lhs, rhs )
      class(shape_t), intent(in ) :: rhs
      class(shape_t), allocatable, intent(out) :: lhs
      print*,' --> in generic_shape_assign'
      allocate(lhs, source = rhs)
      end subroutine generic_shape_assign
      end module deftypes

      program check_assign
      use deftypes
      implicit none
      class(shape_t), allocatable :: myshape
      type (circle_t) :: mycirc1, mycirc2

      mycirc1 = circle_t ( 1, 2, 3 )

      print*,'A polymorphic assignment: myshape = mycirc1'
      myshape = mycirc1

      print*,'An intrinsic assignment: mycirc2 = mycirc1'
      mycirc2 = mycirc1
      end program check_assign


      This example, compiles and works well with ifort 15.0.3 and gfortran 6.3.0. But with nagfor 6.2 I get the following error during the compilation (for the line mycirc2=mycirc1):



      Error: check_assign.f90, line 41: Incorrect data type CIRCLE_T (expected SHAPE_T) for argument LHS (no. 1) of GENERIC_SHAPE_ASSIGN  


      It's not clear to me why this compiler is trying to use the defined assignment in the instruction mycirc2 = mycirc1 while these two variables are not allocatable polymorphic ones.



      Of course, if I delete the defined assignment it works with nagfor but not with the other old compilers. Any idea where this error came from and how to get around it?







      fortran polymorphism gfortran intel-fortran nag-fortran






      share|improve this question















      share|improve this question













      share|improve this question




      share|improve this question








      edited Nov 22 at 12:46









      francescalus

      16.9k73256




      16.9k73256










      asked Nov 20 at 9:50









      R. Hassani

      506




      506
























          1 Answer
          1






          active

          oldest

          votes


















          3














          I believe that the compiler is correct to reject this program. However, if you have a support contract with NAG I strongly advise asking them over taking my comments as definitive.



          I will show my reasoning.



          It is clear that the reference to the specific procedure generic_shape_assign like



          type(circle_t) mycirc1, mycirc2
          call generic_shape_assign(mycirc2, mycirc1)


          is not valid. It fails because the actual argument mycirc2, corresponding to the allocatable polymorphic dummy argument lhs:




          • is not allocatable;

          • is not of the same declared type as the corresponding dummy argument;

          • is not polymorphic.


          The error message you quote covers rejection of the program for violating this second.



          So, that means that generic_shape_assign is not a valid specific procedure (for this reference) with generic specification assignment(=), right? And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?



          This is where things get murky (at least to me).



          I think that the specific subroutine generic_shape_assign is chosen for the defined assignment and the compiler is therefore correct to reject your program because you aren't calling this specific subroutine correctly.



          Let's look further, using Fortran 2008 7.2.1.4 where there's definition of when an assignment statement is a defined assignment statement.



          To decide whether the subroutine generic_shape_assign defines the defined assignment statement mycirc2=mycirc1 we look at the given points:





          1. generic_shape_assign is a subroutine with two dummy arguments (lhs and rhs here);

          2. the interface block gives generic_shape_assign the generic spec assignment(=);


          3. lhs (of type shape_t) is type compatible with mycirc2 (of dynamic type circle_t); rhs similarly;

          4. there are no type parameters for dummy or actual arguments;

          5. the ranks (being scalar) of the dummy and actual arguments match.


          We meet all of the requirements for this being a defined assignment: there is no requirement which states that defined assignment requires the chosen subroutine to be callable!



          In summary:




          It's not clear to me why this compiler is trying to use the defined assignment in the instruction mycirc2 = mycirc1 while these two variables are not allocatable polymorphic ones.




          Because whether defined assignment is used is unrelated to whether the left- and right-hand sides are polymorphic or allocatable.



          Finally, I think the diagnostic message from the compiler could be improved whether my reasoning is correct or incorrect.






          share|improve this answer





















          • "And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?" Yes that's what I think. I just checked with the recent compilers ifort 18 and gfortran 8.1 (even if the defined assignment is here superfluous since polymorphic assignment is allowed with these compilers as with nag one) and I don't get any error messages and the results are correct. Yes, I will ask the nag support in the next few days as soon as I have purchased this compiler (I only used the trial version) and I will report their answer here.Thanks francescalus.
            – R. Hassani
            Nov 24 at 9:00












          • I would be very interested to hear an answer from a compiler developer. Experts also gather on the comp.lang.fortran newsgroup.
            – francescalus
            Nov 24 at 10:43










          • And I should add, if I'm correct and the program is invalid, it isn't invalid in such a way as the compiler is required to detect/diagnose.
            – francescalus
            Nov 24 at 14:09










          • Sorry for this very long period of time. As promised I asked the Nag's support and they completely confirm your analysis. They "agree that the compiler message could be improved and believe that the wording in the Standard will be improved to better guide compiler writers and users." Thank you again francescalus for your help.
            – R. Hassani
            Dec 18 at 11:52










          • Thanks for the update. It's good to know that this answer isn't wrong.
            – francescalus
            Dec 18 at 12:07











          Your Answer






          StackExchange.ifUsing("editor", function () {
          StackExchange.using("externalEditor", function () {
          StackExchange.using("snippets", function () {
          StackExchange.snippets.init();
          });
          });
          }, "code-snippets");

          StackExchange.ready(function() {
          var channelOptions = {
          tags: "".split(" "),
          id: "1"
          };
          initTagRenderer("".split(" "), "".split(" "), channelOptions);

          StackExchange.using("externalEditor", function() {
          // Have to fire editor after snippets, if snippets enabled
          if (StackExchange.settings.snippets.snippetsEnabled) {
          StackExchange.using("snippets", function() {
          createEditor();
          });
          }
          else {
          createEditor();
          }
          });

          function createEditor() {
          StackExchange.prepareEditor({
          heartbeatType: 'answer',
          autoActivateHeartbeat: false,
          convertImagesToLinks: true,
          noModals: true,
          showLowRepImageUploadWarning: true,
          reputationToPostImages: 10,
          bindNavPrevention: true,
          postfix: "",
          imageUploader: {
          brandingHtml: "Powered by u003ca class="icon-imgur-white" href="https://imgur.com/"u003eu003c/au003e",
          contentPolicyHtml: "User contributions licensed under u003ca href="https://creativecommons.org/licenses/by-sa/3.0/"u003ecc by-sa 3.0 with attribution requiredu003c/au003e u003ca href="https://stackoverflow.com/legal/content-policy"u003e(content policy)u003c/au003e",
          allowUrls: true
          },
          onDemand: true,
          discardSelector: ".discard-answer"
          ,immediatelyShowMarkdownHelp:true
          });


          }
          });














          draft saved

          draft discarded


















          StackExchange.ready(
          function () {
          StackExchange.openid.initPostLogin('.new-post-login', 'https%3a%2f%2fstackoverflow.com%2fquestions%2f53390274%2fconflict-between-defined-assignment-and-intrinsic-assignment-with-nagfor%23new-answer', 'question_page');
          }
          );

          Post as a guest















          Required, but never shown

























          1 Answer
          1






          active

          oldest

          votes








          1 Answer
          1






          active

          oldest

          votes









          active

          oldest

          votes






          active

          oldest

          votes









          3














          I believe that the compiler is correct to reject this program. However, if you have a support contract with NAG I strongly advise asking them over taking my comments as definitive.



          I will show my reasoning.



          It is clear that the reference to the specific procedure generic_shape_assign like



          type(circle_t) mycirc1, mycirc2
          call generic_shape_assign(mycirc2, mycirc1)


          is not valid. It fails because the actual argument mycirc2, corresponding to the allocatable polymorphic dummy argument lhs:




          • is not allocatable;

          • is not of the same declared type as the corresponding dummy argument;

          • is not polymorphic.


          The error message you quote covers rejection of the program for violating this second.



          So, that means that generic_shape_assign is not a valid specific procedure (for this reference) with generic specification assignment(=), right? And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?



          This is where things get murky (at least to me).



          I think that the specific subroutine generic_shape_assign is chosen for the defined assignment and the compiler is therefore correct to reject your program because you aren't calling this specific subroutine correctly.



          Let's look further, using Fortran 2008 7.2.1.4 where there's definition of when an assignment statement is a defined assignment statement.



          To decide whether the subroutine generic_shape_assign defines the defined assignment statement mycirc2=mycirc1 we look at the given points:





          1. generic_shape_assign is a subroutine with two dummy arguments (lhs and rhs here);

          2. the interface block gives generic_shape_assign the generic spec assignment(=);


          3. lhs (of type shape_t) is type compatible with mycirc2 (of dynamic type circle_t); rhs similarly;

          4. there are no type parameters for dummy or actual arguments;

          5. the ranks (being scalar) of the dummy and actual arguments match.


          We meet all of the requirements for this being a defined assignment: there is no requirement which states that defined assignment requires the chosen subroutine to be callable!



          In summary:




          It's not clear to me why this compiler is trying to use the defined assignment in the instruction mycirc2 = mycirc1 while these two variables are not allocatable polymorphic ones.




          Because whether defined assignment is used is unrelated to whether the left- and right-hand sides are polymorphic or allocatable.



          Finally, I think the diagnostic message from the compiler could be improved whether my reasoning is correct or incorrect.






          share|improve this answer





















          • "And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?" Yes that's what I think. I just checked with the recent compilers ifort 18 and gfortran 8.1 (even if the defined assignment is here superfluous since polymorphic assignment is allowed with these compilers as with nag one) and I don't get any error messages and the results are correct. Yes, I will ask the nag support in the next few days as soon as I have purchased this compiler (I only used the trial version) and I will report their answer here.Thanks francescalus.
            – R. Hassani
            Nov 24 at 9:00












          • I would be very interested to hear an answer from a compiler developer. Experts also gather on the comp.lang.fortran newsgroup.
            – francescalus
            Nov 24 at 10:43










          • And I should add, if I'm correct and the program is invalid, it isn't invalid in such a way as the compiler is required to detect/diagnose.
            – francescalus
            Nov 24 at 14:09










          • Sorry for this very long period of time. As promised I asked the Nag's support and they completely confirm your analysis. They "agree that the compiler message could be improved and believe that the wording in the Standard will be improved to better guide compiler writers and users." Thank you again francescalus for your help.
            – R. Hassani
            Dec 18 at 11:52










          • Thanks for the update. It's good to know that this answer isn't wrong.
            – francescalus
            Dec 18 at 12:07
















          3














          I believe that the compiler is correct to reject this program. However, if you have a support contract with NAG I strongly advise asking them over taking my comments as definitive.



          I will show my reasoning.



          It is clear that the reference to the specific procedure generic_shape_assign like



          type(circle_t) mycirc1, mycirc2
          call generic_shape_assign(mycirc2, mycirc1)


          is not valid. It fails because the actual argument mycirc2, corresponding to the allocatable polymorphic dummy argument lhs:




          • is not allocatable;

          • is not of the same declared type as the corresponding dummy argument;

          • is not polymorphic.


          The error message you quote covers rejection of the program for violating this second.



          So, that means that generic_shape_assign is not a valid specific procedure (for this reference) with generic specification assignment(=), right? And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?



          This is where things get murky (at least to me).



          I think that the specific subroutine generic_shape_assign is chosen for the defined assignment and the compiler is therefore correct to reject your program because you aren't calling this specific subroutine correctly.



          Let's look further, using Fortran 2008 7.2.1.4 where there's definition of when an assignment statement is a defined assignment statement.



          To decide whether the subroutine generic_shape_assign defines the defined assignment statement mycirc2=mycirc1 we look at the given points:





          1. generic_shape_assign is a subroutine with two dummy arguments (lhs and rhs here);

          2. the interface block gives generic_shape_assign the generic spec assignment(=);


          3. lhs (of type shape_t) is type compatible with mycirc2 (of dynamic type circle_t); rhs similarly;

          4. there are no type parameters for dummy or actual arguments;

          5. the ranks (being scalar) of the dummy and actual arguments match.


          We meet all of the requirements for this being a defined assignment: there is no requirement which states that defined assignment requires the chosen subroutine to be callable!



          In summary:




          It's not clear to me why this compiler is trying to use the defined assignment in the instruction mycirc2 = mycirc1 while these two variables are not allocatable polymorphic ones.




          Because whether defined assignment is used is unrelated to whether the left- and right-hand sides are polymorphic or allocatable.



          Finally, I think the diagnostic message from the compiler could be improved whether my reasoning is correct or incorrect.






          share|improve this answer





















          • "And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?" Yes that's what I think. I just checked with the recent compilers ifort 18 and gfortran 8.1 (even if the defined assignment is here superfluous since polymorphic assignment is allowed with these compilers as with nag one) and I don't get any error messages and the results are correct. Yes, I will ask the nag support in the next few days as soon as I have purchased this compiler (I only used the trial version) and I will report their answer here.Thanks francescalus.
            – R. Hassani
            Nov 24 at 9:00












          • I would be very interested to hear an answer from a compiler developer. Experts also gather on the comp.lang.fortran newsgroup.
            – francescalus
            Nov 24 at 10:43










          • And I should add, if I'm correct and the program is invalid, it isn't invalid in such a way as the compiler is required to detect/diagnose.
            – francescalus
            Nov 24 at 14:09










          • Sorry for this very long period of time. As promised I asked the Nag's support and they completely confirm your analysis. They "agree that the compiler message could be improved and believe that the wording in the Standard will be improved to better guide compiler writers and users." Thank you again francescalus for your help.
            – R. Hassani
            Dec 18 at 11:52










          • Thanks for the update. It's good to know that this answer isn't wrong.
            – francescalus
            Dec 18 at 12:07














          3












          3








          3






          I believe that the compiler is correct to reject this program. However, if you have a support contract with NAG I strongly advise asking them over taking my comments as definitive.



          I will show my reasoning.



          It is clear that the reference to the specific procedure generic_shape_assign like



          type(circle_t) mycirc1, mycirc2
          call generic_shape_assign(mycirc2, mycirc1)


          is not valid. It fails because the actual argument mycirc2, corresponding to the allocatable polymorphic dummy argument lhs:




          • is not allocatable;

          • is not of the same declared type as the corresponding dummy argument;

          • is not polymorphic.


          The error message you quote covers rejection of the program for violating this second.



          So, that means that generic_shape_assign is not a valid specific procedure (for this reference) with generic specification assignment(=), right? And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?



          This is where things get murky (at least to me).



          I think that the specific subroutine generic_shape_assign is chosen for the defined assignment and the compiler is therefore correct to reject your program because you aren't calling this specific subroutine correctly.



          Let's look further, using Fortran 2008 7.2.1.4 where there's definition of when an assignment statement is a defined assignment statement.



          To decide whether the subroutine generic_shape_assign defines the defined assignment statement mycirc2=mycirc1 we look at the given points:





          1. generic_shape_assign is a subroutine with two dummy arguments (lhs and rhs here);

          2. the interface block gives generic_shape_assign the generic spec assignment(=);


          3. lhs (of type shape_t) is type compatible with mycirc2 (of dynamic type circle_t); rhs similarly;

          4. there are no type parameters for dummy or actual arguments;

          5. the ranks (being scalar) of the dummy and actual arguments match.


          We meet all of the requirements for this being a defined assignment: there is no requirement which states that defined assignment requires the chosen subroutine to be callable!



          In summary:




          It's not clear to me why this compiler is trying to use the defined assignment in the instruction mycirc2 = mycirc1 while these two variables are not allocatable polymorphic ones.




          Because whether defined assignment is used is unrelated to whether the left- and right-hand sides are polymorphic or allocatable.



          Finally, I think the diagnostic message from the compiler could be improved whether my reasoning is correct or incorrect.






          share|improve this answer












          I believe that the compiler is correct to reject this program. However, if you have a support contract with NAG I strongly advise asking them over taking my comments as definitive.



          I will show my reasoning.



          It is clear that the reference to the specific procedure generic_shape_assign like



          type(circle_t) mycirc1, mycirc2
          call generic_shape_assign(mycirc2, mycirc1)


          is not valid. It fails because the actual argument mycirc2, corresponding to the allocatable polymorphic dummy argument lhs:




          • is not allocatable;

          • is not of the same declared type as the corresponding dummy argument;

          • is not polymorphic.


          The error message you quote covers rejection of the program for violating this second.



          So, that means that generic_shape_assign is not a valid specific procedure (for this reference) with generic specification assignment(=), right? And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?



          This is where things get murky (at least to me).



          I think that the specific subroutine generic_shape_assign is chosen for the defined assignment and the compiler is therefore correct to reject your program because you aren't calling this specific subroutine correctly.



          Let's look further, using Fortran 2008 7.2.1.4 where there's definition of when an assignment statement is a defined assignment statement.



          To decide whether the subroutine generic_shape_assign defines the defined assignment statement mycirc2=mycirc1 we look at the given points:





          1. generic_shape_assign is a subroutine with two dummy arguments (lhs and rhs here);

          2. the interface block gives generic_shape_assign the generic spec assignment(=);


          3. lhs (of type shape_t) is type compatible with mycirc2 (of dynamic type circle_t); rhs similarly;

          4. there are no type parameters for dummy or actual arguments;

          5. the ranks (being scalar) of the dummy and actual arguments match.


          We meet all of the requirements for this being a defined assignment: there is no requirement which states that defined assignment requires the chosen subroutine to be callable!



          In summary:




          It's not clear to me why this compiler is trying to use the defined assignment in the instruction mycirc2 = mycirc1 while these two variables are not allocatable polymorphic ones.




          Because whether defined assignment is used is unrelated to whether the left- and right-hand sides are polymorphic or allocatable.



          Finally, I think the diagnostic message from the compiler could be improved whether my reasoning is correct or incorrect.







          share|improve this answer












          share|improve this answer



          share|improve this answer










          answered Nov 22 at 12:31









          francescalus

          16.9k73256




          16.9k73256












          • "And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?" Yes that's what I think. I just checked with the recent compilers ifort 18 and gfortran 8.1 (even if the defined assignment is here superfluous since polymorphic assignment is allowed with these compilers as with nag one) and I don't get any error messages and the results are correct. Yes, I will ask the nag support in the next few days as soon as I have purchased this compiler (I only used the trial version) and I will report their answer here.Thanks francescalus.
            – R. Hassani
            Nov 24 at 9:00












          • I would be very interested to hear an answer from a compiler developer. Experts also gather on the comp.lang.fortran newsgroup.
            – francescalus
            Nov 24 at 10:43










          • And I should add, if I'm correct and the program is invalid, it isn't invalid in such a way as the compiler is required to detect/diagnose.
            – francescalus
            Nov 24 at 14:09










          • Sorry for this very long period of time. As promised I asked the Nag's support and they completely confirm your analysis. They "agree that the compiler message could be improved and believe that the wording in the Standard will be improved to better guide compiler writers and users." Thank you again francescalus for your help.
            – R. Hassani
            Dec 18 at 11:52










          • Thanks for the update. It's good to know that this answer isn't wrong.
            – francescalus
            Dec 18 at 12:07


















          • "And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?" Yes that's what I think. I just checked with the recent compilers ifort 18 and gfortran 8.1 (even if the defined assignment is here superfluous since polymorphic assignment is allowed with these compilers as with nag one) and I don't get any error messages and the results are correct. Yes, I will ask the nag support in the next few days as soon as I have purchased this compiler (I only used the trial version) and I will report their answer here.Thanks francescalus.
            – R. Hassani
            Nov 24 at 9:00












          • I would be very interested to hear an answer from a compiler developer. Experts also gather on the comp.lang.fortran newsgroup.
            – francescalus
            Nov 24 at 10:43










          • And I should add, if I'm correct and the program is invalid, it isn't invalid in such a way as the compiler is required to detect/diagnose.
            – francescalus
            Nov 24 at 14:09










          • Sorry for this very long period of time. As promised I asked the Nag's support and they completely confirm your analysis. They "agree that the compiler message could be improved and believe that the wording in the Standard will be improved to better guide compiler writers and users." Thank you again francescalus for your help.
            – R. Hassani
            Dec 18 at 11:52










          • Thanks for the update. It's good to know that this answer isn't wrong.
            – francescalus
            Dec 18 at 12:07
















          "And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?" Yes that's what I think. I just checked with the recent compilers ifort 18 and gfortran 8.1 (even if the defined assignment is here superfluous since polymorphic assignment is allowed with these compilers as with nag one) and I don't get any error messages and the results are correct. Yes, I will ask the nag support in the next few days as soon as I have purchased this compiler (I only used the trial version) and I will report their answer here.Thanks francescalus.
          – R. Hassani
          Nov 24 at 9:00






          "And thus no defined assignment is chosen and the compiler should fall back to intrinsic assignment?" Yes that's what I think. I just checked with the recent compilers ifort 18 and gfortran 8.1 (even if the defined assignment is here superfluous since polymorphic assignment is allowed with these compilers as with nag one) and I don't get any error messages and the results are correct. Yes, I will ask the nag support in the next few days as soon as I have purchased this compiler (I only used the trial version) and I will report their answer here.Thanks francescalus.
          – R. Hassani
          Nov 24 at 9:00














          I would be very interested to hear an answer from a compiler developer. Experts also gather on the comp.lang.fortran newsgroup.
          – francescalus
          Nov 24 at 10:43




          I would be very interested to hear an answer from a compiler developer. Experts also gather on the comp.lang.fortran newsgroup.
          – francescalus
          Nov 24 at 10:43












          And I should add, if I'm correct and the program is invalid, it isn't invalid in such a way as the compiler is required to detect/diagnose.
          – francescalus
          Nov 24 at 14:09




          And I should add, if I'm correct and the program is invalid, it isn't invalid in such a way as the compiler is required to detect/diagnose.
          – francescalus
          Nov 24 at 14:09












          Sorry for this very long period of time. As promised I asked the Nag's support and they completely confirm your analysis. They "agree that the compiler message could be improved and believe that the wording in the Standard will be improved to better guide compiler writers and users." Thank you again francescalus for your help.
          – R. Hassani
          Dec 18 at 11:52




          Sorry for this very long period of time. As promised I asked the Nag's support and they completely confirm your analysis. They "agree that the compiler message could be improved and believe that the wording in the Standard will be improved to better guide compiler writers and users." Thank you again francescalus for your help.
          – R. Hassani
          Dec 18 at 11:52












          Thanks for the update. It's good to know that this answer isn't wrong.
          – francescalus
          Dec 18 at 12:07




          Thanks for the update. It's good to know that this answer isn't wrong.
          – francescalus
          Dec 18 at 12:07


















          draft saved

          draft discarded




















































          Thanks for contributing an answer to Stack Overflow!


          • Please be sure to answer the question. Provide details and share your research!

          But avoid



          • Asking for help, clarification, or responding to other answers.

          • Making statements based on opinion; back them up with references or personal experience.


          To learn more, see our tips on writing great answers.





          Some of your past answers have not been well-received, and you're in danger of being blocked from answering.


          Please pay close attention to the following guidance:


          • Please be sure to answer the question. Provide details and share your research!

          But avoid



          • Asking for help, clarification, or responding to other answers.

          • Making statements based on opinion; back them up with references or personal experience.


          To learn more, see our tips on writing great answers.




          draft saved


          draft discarded














          StackExchange.ready(
          function () {
          StackExchange.openid.initPostLogin('.new-post-login', 'https%3a%2f%2fstackoverflow.com%2fquestions%2f53390274%2fconflict-between-defined-assignment-and-intrinsic-assignment-with-nagfor%23new-answer', 'question_page');
          }
          );

          Post as a guest















          Required, but never shown





















































          Required, but never shown














          Required, but never shown












          Required, but never shown







          Required, but never shown

































          Required, but never shown














          Required, but never shown












          Required, but never shown







          Required, but never shown







          Popular posts from this blog

          Create new schema in PostgreSQL using DBeaver

          Deepest pit of an array with Javascript: test on Codility

          Costa Masnaga