Syntax error in argument list

1,663 views
Skip to first unread message

Gyanendra Pokharel

unread,
Feb 25, 2012, 1:47:23 AM2/25/12
to gg...@googlegroups.com
Hi Group, 
I have following code looks long but not so messy. 

program markovchain
  implicit none

  interface
     subroutine likelihood(alpha,beta)
       implicit none
       real, intent(in) :: alpha,beta
       !real, intent(out) :: loglike
     end subroutine likelihood
  end interface

real :: psi, u, logprior, like, aprop,bprop
integer:: r, niter
real, dimension(1:(1001)) :: aout, bout
real :: a, b, u1, u2

!!!!!!!!!!!!!change of random seed!!!!!!!!!!!!

INTEGER,ALLOCATABLE,DIMENSION(:) :: seed
INTEGER,DIMENSION(8) :: time1
INTEGER :: size
real :: ltmf
CALL RANDOM_SEED(size=size)
ALLOCATE (seed(size))
CALL DATE_AND_TIME(values=time1)
seed = 60*time1(6)+60*time1(7)+time1(8)
CALL RANDOM_SEED(put=seed)


!!!!!!!!!!!!!!!!!!!!!!!!! initial values !!!!!!!!!!!!!!!!!!!

aout(1) = 1.0
bout(1) = 1.0
a = 0.2
b = 0.2
niter = 1000
ltmf = log(1/(10.00**5))
do r = 2,niter

   u1 = 0.0
   u2 = 0.0

   call random_number(u1)
   u1= (2.0*a*u1)- a
   aprop = aout(r-1)+u1

   call random_number(u2)
   u2= (2.0*b*u2)- b
   bprop= bout(r-1)+u2

!!!!!!!!!!!!!!!!!!!!mcmc chain!!!!!!!!!!!!!!


   if(aprop > 0.0 .and. bprop > 0.0 .and. aprop < 10.0 .and. bprop<10.0) then
  psi = min(0.0,(like(aprop,bprop) -like(aout(r-1),bout(r-1))+ logprior(aprop)-logprior(aout(r-1))+logprior(bprop)-logprior(bout(r-1))))

      call random_number(u)
      u=log(u)

!!!!!!!!!!!!!! Test for acceptance probability!!!!!!!!!!!!!!!!!!!!!

      if(psi .le. u) then

         aout(r)= aprop
         bout(r) = bprop

      else
         aout(r)=aout(r-1)
         bout(r)=bout(r-1)

      endif
   else
      aout(r)=aout(r-1)
      bout(r)=bout(r-1)
   endif
enddo


OPEN(10, file="output.txt")
DO r = 2, (niter+1)
   write(*, *) aprop, bprop, like(aprop,bprop), logprior(r), psi
ENDDO
CLOSE(10)
end program markovchain


 Two functions "like" and "logprior" are well defined and working good. The subroutine is used for other function. When I run this code it shows an error 

 In file mhrw.f90:62

(bout
    1
Error: Syntax error in argument list at (1)

this is the error in the line of the function psi. When I simply put aout(r) and bout(r), it does not show any error but this is not the right way of my algorithm. May be there is some logical problem or indexing error.

Can some one suggest me for that?
Thanks

GP

Tobias Burnus

unread,
Feb 27, 2012, 5:31:57 AM2/27/12
to gg95, Tobias Burnus
On Feb 25, 7:47 am, Gyanendra Pokharel <gyanendra.pokha...@gmail.com>
wrote:
>   psi = min(0.0,(like(aprop,bprop) -like(aout(r-1),bout(r-1))+
> logprior(aprop)-logprior(aout(r-1))+logprior(bprop)-logprior(bout(r-1))))

>  In file mhrw.f90:62
>
> (bout
>     1
> Error: Syntax error in argument list at (1)

In Fortran (with free-form source code), the maximal line length is
132 characters. Thus, you should split the lines: Add a '&' followed
by a line break at the position, where the split should happen.

Alternatively, you could also use a compiler-specific flag to allow
longer lines.

Tobias,
who maintains/uses gfortran rather than g95.

Gyanendra Pokharel

unread,
Feb 27, 2012, 8:06:58 AM2/27/12
to gg...@googlegroups.com, Tobias Burnus
Thank you so much, your advise was really helpful.


--
You received this message because you are subscribed to the Google Groups "gg95" group.
To post to this group, send email to gg...@googlegroups.com.
To unsubscribe from this group, send email to gg95+uns...@googlegroups.com.
For more options, visit this group at http://groups.google.com/group/gg95?hl=en.


Reply all
Reply to author
Forward
0 new messages