PROGRAM fcclattice IMPLICIT NONE REAL, DIMENSION(1000,3) :: atoms ! list of atomic coordinates REAL, DIMENSION(4,3) :: pcell ! atoms in primitive unit cell REAL, PARAMETER :: lc = 3.62 ! lattice constant in ang INTEGER :: i, j, k, m, n INTEGER, PARAMETER :: xcell=3, ycell=3, zcell=3 ! number of cells ! first atom in primitive unit cell pcell(1,1) = 0.0 pcell(1,2) = 0.0 pcell(1,3) = 0.0 ! second atom in primitive unit cell pcell(2,1) = 0.5 pcell(2,2) = 0.5 pcell(2,3) = 0.0 ! third atom in primitive unit cell pcell(3,1) = 0.5 pcell(3,2) = 0.0 pcell(3,3) = 0.5 ! fourth atom in primitive unit cell pcell(4,1) = 0.0 pcell(4,2) = 0.5 pcell(4,3) = 0.5 m=0 ! atoms position DO i = 0, xcell DO j = 0, ycell DO k = 0, zcell DO n = 1, 4 m = m+1 ! next atom position atoms(m,1) = (pcell(n,1) + i)*lc atoms(m,2) = (pcell(n,2) + j)*lc atoms(m,3) = (pcell(n,3) + k)*lc END DO END DO END DO END DO ! Print xyz file to stdout ! number of atoms print *, m ! comment print *, '4x4x4 FCC Cu lattice' ! atoms do i = 1, m print '(A,F10.5,F10.5,F10.5,I10)', 'Cu', atoms(i,:),i end do END PROGRAM fcclattice