45    type(ps_cpi_file_t), 
allocatable, 
private :: cpi_file
 
   46    type(ps_in_grid_t),  
allocatable          :: ps_grid
 
   48    type(valconf_t),     
allocatable, 
private :: conf
 
   55    type(ps_cpi_t),    
intent(inout) :: ps_cpi
 
   56    character(len=*),  
intent(in)    :: filename
 
   57    type(namespace_t), 
intent(in)    :: namespace
 
   65    safe_allocate(ps_cpi%cpi_file)
 
   66    safe_allocate(ps_cpi%ps_grid)
 
   67    safe_allocate(ps_cpi%conf)
 
   69    inquire(file = filename, exist = found)
 
   71      call messages_write(
"Pseudopotential file '" // trim(filename) // 
"' not found")
 
   75    iunit = 
io_open(filename, action=
'read', form=
'formatted', status=
'old')
 
   90    type(ps_cpi_t), 
intent(inout) :: ps_cpi
 
   95    safe_deallocate_a(ps_cpi%cpi_file)
 
   96    safe_deallocate_a(ps_cpi%ps_grid)
 
   97    safe_deallocate_a(ps_cpi%conf)
 
  104    type(ps_cpi_file_t), 
intent(in)  :: cpi_file
 
  105    type(ps_in_grid_t),  
intent(out) :: ps_grid
 
  109      logrid_cpi, cpi_file%a, cpi_file%rofi(2), cpi_file%nr,  &
 
  110      cpi_file%no_l_channels, 0)
 
  112    ps_grid%zval        = cpi_file%zval
 
  113    ps_grid%vps(:,:)    = cpi_file%vps(:,:)
 
  114    ps_grid%rphi(:,:,1) = cpi_file%rphi(:,:)
 
  115    ps_grid%rphi(:,:,2) = cpi_file%rphi(:,:)
 
  116    ps_grid%rphi(:,:,3) = cpi_file%rphi(:,:)
 
  118    ps_grid%core_corrections = cpi_file%core_corrections
 
  119    if (ps_grid%core_corrections) 
then 
  120      ps_grid%chcore(:) = cpi_file%chcore(:)
 
  128    type(ps_cpi_t),    
intent(inout) :: ps_cpi
 
  129    integer,           
intent(in)    :: lloc
 
  130    type(namespace_t), 
intent(in)    :: namespace
 
real(real64), parameter, public m_three
 
subroutine, public io_close(iunit, grp)
 
integer function, public io_open(file, namespace, action, status, form, position, die, recl, grp)
 
integer, parameter, public logrid_cpi
log grid used in FHI code
 
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
 
subroutine, public ps_cpi_file_read(unit, psf)
 
subroutine, public ps_cpi_file_end(psf)
 
subroutine, public ps_cpi_file_to_grid(cpi_file, ps_grid)
 
subroutine, public ps_cpi_end(ps_cpi)
 
subroutine, public ps_cpi_init(ps_cpi, filename, namespace)
 
subroutine, public ps_cpi_process(ps_cpi, lloc, namespace)
 
subroutine, public ps_in_grid_kb_projectors(ps)
KB-projectors kb = (vps - vlocal) |phi> * dknorm.
 
subroutine, public ps_in_grid_end(ps)
 
subroutine, public ps_in_grid_cutoff_radii(ps, lloc)
 
subroutine, public ps_in_grid_init(ps, flavor, a, b, nrval, no_l, so_no_l)
 
subroutine, public ps_in_grid_kb_cosines(ps, lloc)
KB-cosines and KB-norms: dkbcos stores the KB "cosines:" || (v_l - v_local) phi_l ||^2 / < (v_l - v_l...
 
subroutine, public ps_in_grid_vlocal(ps, l_loc, rcore, namespace)
 
subroutine, public ps_in_grid_check_rphi(ps, namespace)
checks normalization of the pseudo wavefunctions