Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
integer, | private | :: | n_sites | = | -1 | ||
integer, | private | :: | n_connect_max | = | -1 | ||
integer, | private | :: | n_dim | = | -1 | ||
integer, | private, | allocatable | :: | lu_table(:,:,:) | |||
logical, | private, | allocatable | :: | bz_table(:,:,:) | |||
integer, | private | :: | kmin(sdim) | = | 0 | ||
integer, | private | :: | kmax(sdim) | = | 0 | ||
integer, | private | :: | r_min(sdim) | = | 0 | ||
integer, | private | :: | r_max(sdim) | = | 0 | ||
logical, | private | :: | t_periodic_x | = | .true. | ||
logical, | private | :: | t_periodic_y | = | .true. | ||
logical, | private | :: | t_periodic(3) | = | .true. | ||
logical, | private | :: | t_bipartite_order | = | .false. | ||
character(len=NAME_LEN), | private | :: | name | = | '' | ||
logical, | private | :: | t_momentum_space | = | .false. | ||
integer, | private | :: | lat_vec(3,3) | = | 0 | ||
integer, | private | :: | k_vec(3,3) | = | 0 | ||
integer, | private, | allocatable | :: | basis_vecs(:,:) | |||
integer, | public, | allocatable | :: | k_to_sym(:,:,:) | |||
integer, | public, | allocatable | :: | sym_to_k(:,:) | |||
integer, | public, | allocatable | :: | mult_table(:,:) | |||
integer, | public, | allocatable | :: | inv_table(:) | |||
type(site), | private, | allocatable | :: | sites(:) | |||
procedure(test), | private, | pointer | :: | a | => | null() |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | lattice_type | |||
integer, | intent(in) | :: | length_x | |||
integer, | intent(in) | :: | length_y | |||
integer, | intent(in) | :: | length_z | |||
logical, | intent(in) | :: | t_periodic_x | |||
logical, | intent(in) | :: | t_periodic_y | |||
logical, | intent(in) | :: | t_periodic_z | |||
character(len=*), | intent(in), | optional | :: | space | ||
logical, | intent(in), | optional | :: | t_bipartite_order |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | length_x | |||
integer, | intent(in) | :: | length_y | |||
integer, | intent(in) | :: | length_z | |||
logical, | intent(in) | :: | t_periodic_x | |||
logical, | intent(in) | :: | t_periodic_y | |||
logical, | intent(in) | :: | t_periodic_z | |||
logical, | intent(in), | optional | :: | t_bipartite_order |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice), | intent(in) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice), | intent(in) | :: | this | |||
integer, | intent(in), | optional | :: | dimen |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice), | intent(in) | :: | this | |||
integer, | intent(in), | optional | :: | dimen |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | ind |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | ind |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | ind |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | spinorb |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | sym_1 | |||
integer, | intent(in) | :: | sym_2 |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | sym |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | k_1(3) | |||
integer, | intent(in) | :: | k_2(3) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice), | intent(in) | :: | this | |||
integer, | intent(in) | :: | k(3) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | n_sites |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | n_connect_max |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
logical, | intent(in) | :: | t_periodic_x | |||
logical, | intent(in) | :: | t_periodic_y | |||
logical, | intent(in), | optional | :: | t_periodic_z |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | length_x | |||
integer, | intent(in) | :: | length_y | |||
integer, | intent(in), | optional | :: | length_z |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | length_x | |||
integer, | intent(in) | :: | length_y | |||
integer, | intent(in), | optional | :: | length_z |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | n_sites |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | k_vec(3) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | orb |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | orb |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | k_vec(3) | |||
integer, | intent(in) | :: | r_vec(3) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice), | intent(in) | :: | this | |||
integer, | intent(in) | :: | k_vec(sdim) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice), | intent(in) | :: | this | |||
integer, | intent(in) | :: | k_in(3) | |||
integer, | intent(in), | optional | :: | ind |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(in) | :: | k_in(3) | |||
integer, | intent(in), | optional | :: | spin |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(lattice) | :: | this | ||||
integer, | intent(out), | optional | :: | r_min(3) | ||
integer, | intent(out), | optional | :: | r_max(3) |
type, abstract :: lattice
private
! base class of lattice
! i think i want to try to store all this contigous in memory to
! speed up chache access
integer :: n_sites = -1
integer :: n_connect_max = -1
integer :: n_dim = -1
! Lookup table for momentum -> site index conversion
integer, allocatable :: lu_table(:, :, :)
! Lookup table for first BZ (contains all sums of up to three momenta)
logical, allocatable :: bz_table(:, :, :)
! size of the lookup tables
integer :: kmin(sdim) = 0
integer :: kmax(sdim) = 0
! also store an indexing for the real-space vectors
integer :: r_min(sdim) = 0
integer :: r_max(sdim) = 0
! actually i want to have more flexibility: maybe periodic in x
! but not y..
logical :: t_periodic_x = .true.
logical :: t_periodic_y = .true.
logical :: t_periodic(3) = .true.
logical :: t_bipartite_order = .false.
! i want to do a lattice type member also, do easier check, which
! lattice we are looking at.. but i need to make this nice
! having a defered lenght character component would be the best
! option:
! character(:), allocatable, public :: type
! but this needs gfortran version >= 4.9, which i guess is not
! available everywhere yet.. so do smth else for now:
character(NAME_LEN) :: name = ''
! and "just" use trim and align in the comparisons for lattice names!
! and also add a flag, if we want a momentum space lattice
! representation.
logical :: t_momentum_space = .false.
integer :: lat_vec(3, 3) = 0
! also store k_vec ..
integer :: k_vec(3, 3) = 0
! initialize the possible applicable basis vectors in the
! mapping to the BZ
integer, allocatable :: basis_vecs(:, :)
! i also need a matrix mapping from the k-vectors to the
! k-symbols to quickly access them!
integer, allocatable, public :: k_to_sym(:, :, :)
! and vice versa a mapping from the symbol to the k-vector
! or i could just use the orbital index? does this work with
! neci though?
! just use a matrix here and take the rows
integer, allocatable, public :: sym_to_k(:, :)
! and also store a multiplication table in the lattice class..
! to make it consistend and store everything necessary in here..
! this just make use of the symbols!
integer, allocatable, public :: mult_table(:, :)
! and also use an inverse table, which also just uses the
! symbols!
integer, allocatable, public :: inv_table(:)
! and i think additionally i want to store which type of lattice
! this is in a string or? so i do not always have to
! use the select type functionality
! i would need constant expression.. so stick with select type!
! and in the end a lattice is a collection of sites
! and all the topology could be stored in the connection of the
! sites
! and i just realized that if i want to use class(lattice)
! generally in the whole program, i have to provide all the
! functionality already for the lattice.. atleast in a dummy
! way.. hm.. maybe there is a better way to do it..
! maybe i have to use pointer attribute below to make it possible
! to call an constructor of class(type) ..
! well this also does not work as i like to have it..
! since it is not interpreted as an array of pointer, but as a
! pointer to an array of class(sites), so redo this in the end!
type(site), allocatable :: sites(:)
! this is just a small test if we can bring classic procedure
! pointers into the game.. but will be removed soon
procedure(test), pointer :: a => null()
contains
private
! i think i need some general interface here at the top of the
! type definition, so all of those function can get called
! but i need specifice ones then for each sub-class
! how do i do that?
procedure :: initialize => init_lattice
procedure, public :: get_nsites
procedure, public :: get_ndim
procedure, public :: get_nconnect_max
procedure, public :: is_periodic_x
procedure, public :: is_periodic_y
procedure(is_periodic_t), public, deferred :: is_periodic
procedure(get_length_t), public, deferred :: get_length
procedure, public :: get_site_index
! make the get neighbors function public on the lattice level
procedure, public :: get_neighbors => get_neighbors_lattice
procedure, public :: get_num_neighbors => get_num_neighbors_lattice
procedure, public :: get_spinorb_neighbors => get_spinorb_neighbors_lat
procedure, public :: is_k_space
! i definetly also want to have a print function!
procedure, public :: print_lat
procedure, public :: add_k_vec
procedure :: add_k_vec_symbol
procedure, public :: inv_k_vec
procedure :: inv_k_vec_symbol
procedure, public :: get_sym
procedure, public :: subtract_k_vec
procedure, public :: get_sym_from_k
procedure, public :: set_sym
procedure :: set_name
procedure, public :: get_name
! maybe i want set routines too?
! but i guess i want the private, because there is no need of
! them being used outside of this module
! but this would make it flexible to make these function public
procedure :: set_nsites
procedure :: set_ndim
procedure :: set_nconnect_max
procedure :: set_periodic
procedure(set_length_t), deferred :: set_length
procedure(calc_nsites_t), deferred :: calc_nsites
procedure :: allocate_sites
procedure(initialize_sites_t), deferred :: initialize_sites
procedure :: deallocate_sites
! for the k-space implementations also implement a lattice
! dependent dispersion relation function
procedure, public :: dispersion_rel => dispersion_rel_not_implemented
procedure, public :: dispersion_rel_orb
procedure, public :: dispersion_rel_spin_orb
procedure, public :: dot_prod => dot_prod_not_implemented
procedure, public :: get_k_vec
procedure, public :: get_r_vec
procedure, public :: round_sym
procedure, public :: map_k_vec
procedure :: inside_bz
procedure :: inside_bz_explicit
procedure :: apply_basis_vector
procedure, public :: get_orb_from_k_vec
! and procedures to initialize the site index lookup table and the
! matrix element lookup table
procedure :: initialize_lu_table
procedure :: fill_bz_table
procedure :: fill_lu_table
procedure :: get_lu_table_size
procedure :: deallocate_caches
! actually i should make i deferred: todo
procedure :: init_basis_vecs
procedure, public :: init_hop_cache_bounds
end type lattice