Skip to content

Commit

Permalink
removed atenv from crystalmod
Browse files Browse the repository at this point in the history
  • Loading branch information
aoterodelaroza committed Feb 12, 2024
1 parent ecc9a4d commit 5122ad2
Show file tree
Hide file tree
Showing 5 changed files with 109 additions and 59 deletions.
24 changes: 12 additions & 12 deletions src/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -311,7 +311,7 @@ module subroutine field_new(f,seed,c,id,sptr,errmsg,ti)
if (seed%nfile == 1) then
if (.not.allocated(f%grid)) allocate(f%grid)
call f%grid%end()
call f%grid%read_elk(seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
call f%grid%read_elk(c_loc(c),seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
f%type = type_grid
f%file = seed%file(1)
elseif (seed%nfile == 2) then
Expand All @@ -338,64 +338,64 @@ module subroutine field_new(f,seed,c,id,sptr,errmsg,ti)
elseif (seed%iff == ifformat_cube) then
if (.not.allocated(f%grid)) allocate(f%grid)
call f%grid%end()
call f%grid%read_cube(seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
call f%grid%read_cube(c_loc(c),seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
f%type = type_grid
f%file = seed%file(1)

elseif (seed%iff == ifformat_bincube) then
if (.not.allocated(f%grid)) allocate(f%grid)
call f%grid%end()
call f%grid%read_bincube(seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
call f%grid%read_bincube(c_loc(c),seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
f%type = type_grid
f%file = seed%file(1)

elseif (seed%iff == ifformat_abinit) then
if (.not.allocated(f%grid)) allocate(f%grid)
call f%grid%end()
call f%grid%read_abinit(seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
call f%grid%read_abinit(c_loc(c),seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
f%type = type_grid
f%file = seed%file(1)

elseif (seed%iff == ifformat_vasp .or. seed%iff == ifformat_vaspnov) then
if (.not.allocated(f%grid)) allocate(f%grid)
call f%grid%end()
call f%grid%read_vasp(seed%file(1),c%m_x2c,(seed%iff == ifformat_vasp),seed%vaspblk,c%env,&
call f%grid%read_vasp(c_loc(c),seed%file(1),c%m_x2c,(seed%iff == ifformat_vasp),seed%vaspblk,c%env,&
errmsg,ti=ti)
f%type = type_grid
f%file = seed%file(1)

elseif (seed%iff == ifformat_qub) then
if (.not.allocated(f%grid)) allocate(f%grid)
call f%grid%end()
call f%grid%read_qub(seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
call f%grid%read_qub(c_loc(c),seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
f%type = type_grid
f%file = seed%file(1)

elseif (seed%iff == ifformat_xsf) then
if (.not.allocated(f%grid)) allocate(f%grid)
call f%grid%end()
call f%grid%read_xsf(seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
call f%grid%read_xsf(c_loc(c),seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
f%type = type_grid
f%file = seed%file(1)

elseif (seed%iff == ifformat_fmt) then
if (.not.allocated(f%grid)) allocate(f%grid)
call f%grid%end()
call f%grid%read_fmt(seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
call f%grid%read_fmt(c_loc(c),seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
f%type = type_grid
f%file = seed%file(1)

elseif (seed%iff == ifformat_elkgrid) then
if (.not.allocated(f%grid)) allocate(f%grid)
call f%grid%end()
call f%grid%read_elk(seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
call f%grid%read_elk(c_loc(c),seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
f%type = type_grid
f%file = seed%file(1)

elseif (seed%iff == ifformat_siestagrid) then
if (.not.allocated(f%grid)) allocate(f%grid)
call f%grid%end()
call f%grid%read_siesta(seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
call f%grid%read_siesta(c_loc(c),seed%file(1),c%m_x2c,c%env,errmsg,ti=ti)
f%type = type_grid
f%file = seed%file(1)

Expand All @@ -412,7 +412,7 @@ module subroutine field_new(f,seed,c,id,sptr,errmsg,ti)

f%type = type_grid
f%file = seed%file(1)
call f%grid%read_pwc(seed%file(1),seed%pwcspin,seed%pwcikpt,seed%pwcibnd,&
call f%grid%read_pwc(c_loc(c),seed%file(1),seed%pwcspin,seed%pwcikpt,seed%pwcibnd,&
seed%pwcemin,seed%pwcemax,c%m_x2c,c%env,errmsg,ti=ti)
if (seed%nfile == 2) then
call f%grid%read_wannier_chk(seed%file(2),errmsg=errmsg,ti=ti)
Expand Down Expand Up @@ -496,7 +496,7 @@ module subroutine field_new(f,seed,c,id,sptr,errmsg,ti)
f%type = type_grid
f%file = ""
n = seed%n
call f%grid%new_eval(sptr,n,seed%expr,c%m_x2c,c%env)
call f%grid%new_eval(sptr,c_loc(c),n,seed%expr,c%m_x2c,c%env)
if (.not.f%grid%isinit) then
call f%grid%end()
f%grid%n = n
Expand Down
39 changes: 26 additions & 13 deletions src/grid3mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@

! Class for 3d grids and related tools.
module grid3mod
use iso_c_binding, only: c_ptr
use environmod, only: environ
use types, only: thread_info
use param, only: mlen
Expand Down Expand Up @@ -70,7 +71,7 @@ module grid3mod
real*8 :: c2xg(3,3) !< Cartesian to crystallographic matrix (grid)
real*8 :: dmax !< minimum and maximum grid steps
type(environ) :: env !< environment for grid nodes
type(environ), pointer :: atenv !< environment for atoms
type(c_ptr) :: cptr !< pointer to the crystal structure
integer :: nvec !< number of neighbor grid points
integer, allocatable :: vec(:,:) !< grid coordinates of neighbor grid points
real*8, allocatable :: area(:) !< area of the Voronoi facets
Expand Down Expand Up @@ -120,10 +121,11 @@ module grid3mod
public :: grid3

interface
module subroutine new_eval(f,sptr,n,expr,x2c,env)
module subroutine new_eval(f,sptr,cptr,n,expr,x2c,env)
use iso_c_binding, only: c_ptr
class(grid3), intent(inout) :: f
type(c_ptr), intent(in) :: sptr
type(c_ptr), intent(in) :: cptr
integer, intent(in) :: n(3)
character(*), intent(in) :: expr
real*8, intent(in) :: x2c(3,3)
Expand All @@ -140,46 +142,52 @@ module subroutine normalize(f,norm,omega)
class(grid3), intent(inout) :: f
real*8, intent(in) :: norm, omega
end subroutine normalize
module subroutine from_array3(f,g,x2c,env)
module subroutine from_array3(f,g,x2c,env,cptr)
class(grid3), intent(inout) :: f
real*8, intent(in) :: g(:,:,:)
real*8, intent(in) :: x2c(3,3)
type(environ), intent(in), target :: env
type(c_ptr), intent(in) :: cptr
end subroutine from_array3
module subroutine read_cube(f,file,x2c,env,errmsg,ti)
module subroutine read_cube(f,cptr,file,x2c,env,errmsg,ti)
class(grid3), intent(inout) :: f
type(c_ptr), intent(in) :: cptr
character*(*), intent(in) :: file
real*8, intent(in) :: x2c(3,3)
type(environ), intent(in), target :: env
character(len=:), allocatable, intent(out) :: errmsg
type(thread_info), intent(in), optional :: ti
end subroutine read_cube
module subroutine read_bincube(f,file,x2c,env,errmsg,ti)
module subroutine read_bincube(f,cptr,file,x2c,env,errmsg,ti)
class(grid3), intent(inout) :: f
type(c_ptr), intent(in) :: cptr
character*(*), intent(in) :: file
real*8, intent(in) :: x2c(3,3)
type(environ), intent(in), target :: env
character(len=:), allocatable, intent(out) :: errmsg
type(thread_info), intent(in), optional :: ti
end subroutine read_bincube
module subroutine read_siesta(f,file,x2c,env,errmsg,ti)
module subroutine read_siesta(f,cptr,file,x2c,env,errmsg,ti)
class(grid3), intent(inout) :: f
type(c_ptr), intent(in) :: cptr
character*(*), intent(in) :: file
real*8, intent(in) :: x2c(3,3)
type(environ), intent(in), target :: env
character(len=:), allocatable, intent(out) :: errmsg
type(thread_info), intent(in), optional :: ti
end subroutine read_siesta
module subroutine read_abinit(f,file,x2c,env,errmsg,ti)
module subroutine read_abinit(f,cptr,file,x2c,env,errmsg,ti)
class(grid3), intent(inout) :: f
type(c_ptr), intent(in) :: cptr
character*(*), intent(in) :: file
real*8, intent(in) :: x2c(3,3)
type(environ), intent(in), target :: env
character(len=:), allocatable, intent(out) :: errmsg
type(thread_info), intent(in), optional :: ti
end subroutine read_abinit
module subroutine read_vasp(f,file,x2c,vscal,ibl,env,errmsg,ti)
module subroutine read_vasp(f,cptr,file,x2c,vscal,ibl,env,errmsg,ti)
class(grid3), intent(inout) :: f
type(c_ptr), intent(in) :: cptr
character*(*), intent(in) :: file
real*8, intent(in) :: x2c(3,3)
logical, intent(in) :: vscal
Expand All @@ -188,32 +196,36 @@ module subroutine read_vasp(f,file,x2c,vscal,ibl,env,errmsg,ti)
character(len=:), allocatable, intent(out) :: errmsg
type(thread_info), intent(in), optional :: ti
end subroutine read_vasp
module subroutine read_qub(f,file,x2c,env,errmsg,ti)
module subroutine read_qub(f,cptr,file,x2c,env,errmsg,ti)
class(grid3), intent(inout) :: f
type(c_ptr), intent(in) :: cptr
character*(*), intent(in) :: file
real*8, intent(in) :: x2c(3,3)
type(environ), intent(in), target :: env
character(len=:), allocatable, intent(out) :: errmsg
type(thread_info), intent(in), optional :: ti
end subroutine read_qub
module subroutine read_xsf(f,file,x2c,env,errmsg,ti)
module subroutine read_xsf(f,cptr,file,x2c,env,errmsg,ti)
class(grid3), intent(inout) :: f
type(c_ptr), intent(in) :: cptr
character*(*), intent(in) :: file
real*8, intent(in) :: x2c(3,3)
type(environ), intent(in), target :: env
character(len=:), allocatable, intent(out) :: errmsg
type(thread_info), intent(in), optional :: ti
end subroutine read_xsf
module subroutine read_fmt(f,file,x2c,env,errmsg,ti)
module subroutine read_fmt(f,cptr,file,x2c,env,errmsg,ti)
class(grid3), intent(inout) :: f
type(c_ptr), intent(in) :: cptr
character*(*), intent(in) :: file
real*8, intent(in) :: x2c(3,3)
type(environ), intent(in), target :: env
character(len=:), allocatable, intent(out) :: errmsg
type(thread_info), intent(in), optional :: ti
end subroutine read_fmt
module subroutine read_pwc(f,fpwc,ispin,ikpt,ibnd,emin,emax,x2c,env,errmsg,ti)
module subroutine read_pwc(f,cptr,fpwc,ispin,ikpt,ibnd,emin,emax,x2c,env,errmsg,ti)
class(grid3), intent(inout) :: f
type(c_ptr), intent(in) :: cptr
character*(*), intent(in) :: fpwc
integer, intent(in) :: ispin
integer, intent(in), allocatable :: ikpt(:)
Expand All @@ -224,8 +236,9 @@ module subroutine read_pwc(f,fpwc,ispin,ikpt,ibnd,emin,emax,x2c,env,errmsg,ti)
character(len=:), allocatable, intent(out) :: errmsg
type(thread_info), intent(in), optional :: ti
end subroutine read_pwc
module subroutine read_elk(f,file,x2c,env,errmsg,ti)
module subroutine read_elk(f,cptr,file,x2c,env,errmsg,ti)
class(grid3), intent(inout) :: f
type(c_ptr), intent(in) :: cptr
character*(*), intent(in) :: file
real*8, intent(in) :: x2c(3,3)
type(environ), intent(in), target :: env
Expand Down
Loading

0 comments on commit 5122ad2

Please sign in to comment.