Silverfrost Forums

Welcome to our forums

Error 169 - different types cannot be comapred with .EQ.

19 Sep 2011 12:25 #8997

I am getting an error when compiling the following expression:

IF (UX.EQ.'US'.OR.UX.EQ.'ME'.OR.UX.EQ.'us'.OR.UX.EQ.'Me'. *OR.UX.EQ.'me') GOTO 110

'error 169 - Different types cannot be compared with .EQ. (REAL(KIND=1) and CHARACTER(LEN=2))'

Any suggestions?

Thanks,

Jim

19 Sep 2011 6:56 #8998

UX is REAL whilst 'US' is CHARACTER and you are not allowed to compare the two for equality.

Perhaps you need to declare UX as CHARACTER and assign a value to it.

Use IMPLICIT NONE to ensure that all variables are explicitly declared.

19 Sep 2011 1:40 #9002

If you programmed Fortran several decades ago, you stored character information in arrays of REAL or INTEGER type. This got progressively more frowned on after the introduction of CHARACTER type, to the point that it is now illegal. If your intention is clear from the code fragment, then you are locked into an obsolete method. Otherwise, you have forgotten to declare the variables as being of CHARACTER type.

E

19 Sep 2011 8:19 #9004

Because the error indicates that UX is real(kind=1) which is the default real kind and UX starts with U it is almost certain you have not declared UX to be a character variable (as others say above).

You should use IMPLICIT NONE.

Fix this. Then you might want to consider writing the code like this.

if (any(UX == (/'US','ME','us','me','Us','Me'/))) GOTO 110

This includes the possibility 'Us' which was missing from your code.

Your way should work too.

27 Sep 2011 9:58 #9027

Hi David

I never knew that one can if an array as in your example! Anyway, I tried it as shown below - parsing an array in (/ ... /). This is real cool ans saves a lot of time when connecting nodes. You can image how many lines I wasted doing it the 'old' way.

It always pays off keeping an eye in the forum 😄

    call add_bc(srg,14,201,(/-2,-1,11,-7/))
    call add_bc(srg,17,  0,(/-17,-16,-31,-18/))
    subroutine add_bc(srg,pos,mat,ivrt)
        implicit none
        integer,dimension(:) :: ivrt
        type(srg_type) :: srg
        integer :: pos,mat
        integer :: n,i,k
        n = size(ivrt)
        srg%nvbc(pos) = n
        srg%itype(pos) = mat
        if (pos == 1) then
            k = 1
        else
            k = sum(srg%nvbc(1:pos-1))+1
        endif
        do i=1,n
            srg%ivrt(k) = ivrt(i)
            k = k+1
        enddo
        return
    end subroutine
27 Sep 2011 8:17 #9030

Quoted from jjgermis

It always pays off keeping an eye in the forum 😄

Agreed.

Array syntax is one of the cornerstones of Modern Fortran. My example above uses the fact that an array and a scalar are 'Conformable' for the == relational operator. The example creates a temporary array in memory, and whilst I think FTN95 serialises the comparison, other optimizing compilers use SSE processor instructions (on later ia32 microprocessors) to vectorise the comparison (making it very efficient).

As a further example of the power of the Fortran language, I believe some lines in your code can be replaced as follows:

Replace:

        if (pos == 1) then
            k = 1
        else
            k = sum(srg%nvbc(1:pos-1))+1
        endif
        do i=1,n
            srg%ivrt(k) = ivrt(i)
            k = k+1
        end do 

By:

       k = sum(srg%nvbc(1:pos-1))+1
       srg%ivrt(k:k+n-1) = ivrt(1:n)

Since the array srg%nvbc( : ) is of zero length and has zero sum when pos = 1.

Please login to reply.