24小时热门版块排行榜    

查看: 3122  |  回复: 4

木子化十文武

金虫 (小有名气)

[求助] list-directed I/O syntax error,unit 12

fortran编译和运行都通过了,execute program时出现了这个问题,出问题的行是在读ME文件的时候,请问这可能是什么原因呀?急急急,先谢谢各位高手了!!!
回复此楼
平和!谦逊!
已阅   回复此楼   关注TA 给TA发消息 送TA红花 TA的回帖

snoopyzhao

至尊木虫 (职业作家)

【答案】应助回帖


jjdg(金币+1): 感谢参与 2011-10-19 06:39:09
木子化十文武(金币+5): 有帮助 2012-01-08 11:18:34
贴代码,以及应的数据文件……

另外,你可以参考这里,自己排除一下:
http://software.intel.com/en-us/forums/showthread.php?t=51831
2楼2011-10-18 20:23:38
已阅   回复此楼   关注TA 给TA发消息 送TA红花 TA的回帖

木子化十文武

金虫 (小有名气)

引用回帖:
2楼: Originally posted by snoopyzhao at 2011-10-18 20:23:38:
贴代码,以及应的数据文件……

另外,你可以参考这里,自己排除一下:
http://software.intel.com/en-us/forums/showthread.php?t=51831

!===================================================================
!该程序用于计算TB势
!         
!===================================================================
program TBenergy
  implicit none

!===================================================================
!ME文件读取和输入相关变量声明
  real::mass1,mass2
  integer::seq_1,seq_2,seq_3,seq_4,seq_5,n_Au,n_Ag
  real::angle, rand_v, start_time, finish_time
  integer::bi,c,d
  character*4::elem(2)
  integer,allocatable::seq1(,seq2(
!===================================================================
!主程序变量申明
  integer :: Natom, i, j, m, x_change1, x_change2, x_change3,element,ele(30000)
  real :: r, a_const(3), a_const0(3)
  real :: potential
  real :: pos_Au(25000, 3), pos_Ag(25000, 3), pos_r(3), pos_Au0(25000, 3), pos_Ag0(25000, 3)
  real :: min_energy,E0
  real :: ptable_r(70000, 3), ptable_b(70000, 3)
  real :: Rc, box_number, skin
  integer::flag,TB_ind,maxpair, Length_List
  real,allocatable :: pos(:,
  integer, allocatable :: point(:, , List(
  character*80 :: Input, SampIn, SampOut  
  namelist/ filename / SampIn, SampOut

  !common/resu/ potential
  common/ ene / ptable_r, ptable_b
  common/ canshu / Natom,Length_List,a_const,Rc
  common/min_one/min_energy,TB_ind
!=================================================================
  call cpu_time(start_time)
  open(13, file = 'TBsc.txt')
  read(13, filename)
  close(13)


!read the position of these atoms
!  ME  read the coordinate of atom
  open(12,file=SampIn,status='old')
  read(12,*)seq_1,(a_const0(i),i=1, 3)
  read(12,*)seq_2,angle,angle,angle
  read(12,*)seq_3,bi,bi
  read(12,*)seq_4,ele(1),c,n_Au,d     !出错行!!!  
  allocate(seq1(n_Au))
  do i=1,n_Au
        read(12,*) seq1(i),ele(1),d,(pos_Au0(i,j),j=1,3),mass1
  enddo
  read(12,*)seq_5,ele(2),c,n_Ag,d
  allocate(seq2(n_Ag))
  do i=1,n_Ag
        read(12,*) seq2(i),ele(2),d,(pos_Ag0(i,j),j=1,3),mass2
  enddo
close(12)
box_number = a_const0(1)/3.72
Natom = n_Au + n_Ag
Length_List = Natom*Natom   !更改了!!!
allocate( List(Length_List), point(Natom, 2))
allocate(pos(Natom,3))
ele(1:n_Au) = 1
ele((n_Au + 1):Natom) = 2
flag=1
min_energy=10000
do x_change1 = -5, 5, 1
  a_const(1) = a_const0(1)*(1 + x_change1*1.0/ 100.0)
  do x_change2 = -5, 5, 1
    a_const(2) = a_const0(2)*(1 + x_change2*1.0/ 100.0)  
    do x_change3 = -5, 5, 1
      a_const(3) = a_const0(3)*(1 + x_change1*1.0/ 100.0)


      do m = 1, 3
        pos_Au(:, m) = pos_Au0(:, m) * a_const(m)
        pos_Ag(:, m) = pos_Ag0(:, m) * a_const(m)
      end do
!======================================
      pos(1:n_Au, = pos_Au
      pos((n_Au + 1):Natom, = pos_Ag
      call potential(ptable_r, ptable_b)
      call update_list(list, point, pos)
      call energy_total(E0, pos, ele, List, point)
                          if(E0 < min_energy)   then
                        min_energy=E0
                        end if
     flag = flag + 1
    end do
  end do
end do
open (unit = 11, file = SampOut)   
write(*,*)'TB_energy', min_energy
write(11,*)'TB_energy', min_energy
close(11)
call cpu_time(finish_time)
write(*, *) 'running time = ', finish_time - start_time, 's'


end program TBenergy
!=================================================================

!=================================================================
subroutine update_list(list, point, pos)         !更新邻近原子
  implicit none
  integer :: i, j, Natom, L, length_List
    common/ canshu / Natom,Length_List,a_const
  integer :: List(Length_List), point(Natom, 2)
  real :: pos(Natom, 3), pos_r(3)
  real :: r, Rc, skin, a_const

   Rc =7        !截断半径
   skin =  0.4  !可以不用
  List = 0
  point = 0
  L = 1
  do i = 1, Natom
    point(i, 1) = L      !point(i, 数组用于存储i原子邻近原子在List数组中的索引号,point(i, 1)为开始,point(i, 2)终了(包括i本身)
loop_1 : do j = 1, Natom
          pos_r = (pos(i, - pos(j, )
!          pos_r = pos_r - a_const*nint(pos_r/a_const)  !周期性边界          
          r = sqrt(sum(pos_r*pos_r))
          if(r<(Rc + skin)) then           !
            if(i.eq.j) cycle loop_1
                List(L) = j   !矩阵维数溢出
                L = L + 1
          endif
        enddo loop_1
        List(L) = i            !把i原子本身存在point(i, 2)
        point(i, 2) = L
        L = L + 1
  enddo  
end subroutine update_List
!====================================================================

!===============================================================================
subroutine potential(ptable_r, ptable_b)
  implicit none
  integer :: i
  real :: A_p(3), e_p(3), p_p(3), q_p(3), r0_p(3)
  real :: ptable_r(50000, 3), ptable_b(50000, 3)

  A_p = (/0.2096, 0.1490, 0.1031/)
  e_p = (/1.8153, 1.4874, 1.1895/)
  p_p = (/10.139, 10.494, 10.850/)
  q_p = (/4.033, 3.607, 3.180/)
  r0_p = (/0.7738, 0.7350, 0.7751/)
  
  do i = 1, 50000
    ptable_r(i, = A_p*exp(-p_p*((i*1.0/10000)/r0_p - 1))        !- A_p*exp(-p_p*((50000*1.0/10000)/r0_p - 1))
  enddo
  do i = 1, 50000
    ptable_b(i, = e_p*e_p*exp(-2*q_p*((i*1.0/10000)/r0_p - 1))  !- e_p*e_p*exp(-2*q_p*((50000*1.0/10000)/r0_p - 1))
  enddo
end subroutine potential
!===============================================================================

!===============================================================================
subroutine energy_total(E, pos, ele, List, point)
  implicit none
  common/ ene / ptable_r, ptable_b
  common/ u_l / Natom, Length_List, rc, boxsize

  integer :: i, j
  integer :: Natom, length_List, Ir
  real :: pos(Natom, 3), pos_r(3)
  real :: r, rc, boxsize(3)
  real :: ptable_r(50000, 3), ptable_b(50000, 3), E, E_R, E_B
  integer :: point(Natom, 2), List(length_list), ele(Natom)
  E = 0
  do i = 1, Natom         ! 遍历系统所有原子,求系统总能量
    E_R = 0
        E_B = 0
    do j = point(i, 1), (point(i, 2)-1)
          pos_r = (pos(i, - pos(List(j), )*boxsize
          !pos_r(1) = pos_r(1) - boxsize(1)*nint(pos_r(1)/boxsize(1))     ! 周期性边界条件
          !pos_r(2) = pos_r(2) - boxsize(2)*nint(pos_r(2)/boxsize(2))
          !pos_r(3) = pos_r(3) - boxsize(3)*nint(pos_r(3)/boxsize(3))
          r = sqrt(sum(pos_r*pos_r))
          if(r.lt.Rc) then                !此处有Rc,故E_total和Rc有关,即晶胞大小和Rc有关;
            Ir = int(r*10000)
            E_R = E_R + ptable_r(Ir, ele(i) + ele(List(j)) - 1)
            E_B = E_B + ptable_b(Ir, ele(i) + ele(List(j)) - 1)
          endif
        enddo
        E = E + E_R - sqrt(E_B)
  enddo
end subroutine energy_total
!===============================================================================


TBsc.txt:
&filename
SampIn = '1.5cube.bdl'
SampOut = 'result_AuAg.txt'
/


谢谢大侠~
平和!谦逊!
3楼2011-10-19 08:45:29
已阅   回复此楼   关注TA 给TA发消息 送TA红花 TA的回帖

木子化十文武

金虫 (小有名气)

引用回帖:
2楼: Originally posted by snoopyzhao at 2011-10-18 20:23:38:
贴代码,以及应的数据文件……

另外,你可以参考这里,自己排除一下:
http://software.intel.com/en-us/forums/showthread.php?t=51831

你好,错误已经找出,不麻烦你了,非常感谢~
平和!谦逊!
4楼2011-10-19 09:35:29
已阅   回复此楼   关注TA 给TA发消息 送TA红花 TA的回帖

chenpeng8495

新虫 (初入文坛)

引用回帖:
4楼: Originally posted by 木子化十文武 at 2011-10-19 09:35:29
你好,错误已经找出,不麻烦你了,非常感谢~...

您好 最终什么问题呢 可否告知下
5楼2014-01-15 18:31:36
已阅   回复此楼   关注TA 给TA发消息 送TA红花 TA的回帖
相关版块跳转 我要订阅楼主 木子化十文武 的主题更新
信息提示
请填处理意见