Eötvös Quantum Utilities  v5.0.144
Providing the Horsepowers in the Quantum Realm
NTerminal.m
Go to the documentation of this file.
1 %% Eotvos Quantum Transport Utilities - NTerminal
2 % Copyright (C) 2016 Peter Rakyta, Ph.D.
3 %
4 % This program is free software: you can redistribute it and/or modify
5 % it under the terms of the GNU General Public License as published by
6 % the Free Software Foundation, either version 3 of the License, or
7 % (at your option) any later version.
8 %
9 % This program is distributed in the hope that it will be useful,
10 % but WITHOUT ANY WARRANTY; without even the implied warranty of
11 % MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 % GNU General Public License for more details.
13 %
14 % You should have received a copy of the GNU General Public License
15 % along with this program. If not, see http://www.gnu.org/licenses/.
16 %
17 %> @addtogroup utilities Utilities
18 %> @{
19 %> @file NTerminal.m
20 %> @brief A class describing an N-terminal geometry for equilibrium calculations mostly in the zero temperature limit.
21 %> @image html two_terminal_structure.jpg
22 %> @image latex two_terminal_structure.jpg
23 %> @}
24 %> @brief A class describing an N-terminal geometry for equilibrium calculations mostly in the zero temperature limit.
25 %> @Available
26 %> EQuUs v4.9 or later
27 %> <tr class="heading"><td colspan="2"><h2 class="groupheader"><a name="avail"></a>Structure described by the class</h2></td></tr>
28 %> @image html two_terminal_structure.jpg
29 %> @image latex two_terminal_structure.jpg
30 %> The drawing represents a two-terminal structure made of two leads, of a scattering region and of two interface regions between the leads and scattering center.
31 %> However, additional lead can be added to the structure.
32 %> Each rectangle describes a unit cell including singular and non-singular sites.
33 %> The scattering center is, on the other hand, represented by a larger rectangle corresponding to the Hamiltonian of the scattering region.
34 %> Arrows indicate the hopping direction stored by the attributes in the corresponding classes (see attributes #CreateLeadHamiltonians.H1 and #InterfaceRegion.Hcoupling for details).
35 %> The orientation of the lead is +1 if the lead is terminated by the interface region in the positive direction, and -1 if the lead is terminated by the interface region in the negative direction.
36 %> (see attribute #CreateLeadHamiltonians.Lead_Orientation for details)
37 %%
39 
40 
41  properties (Access = protected )
42  %> An instance of strucutre #param
43  param
44  %> Green operator of the scattering region
45  G
46  %> The inverse of the Green operator G
47  Ginv
48  %> The energy used in the calculations
49  E
50  %> The Fermi energy. Attribute #E is measured from this value. (Use for equilibrium calculations in the zero temperature limit.)
51  EF
52  %> The transverse momentum quantum number
53  q
54  %> Function handle to create custom Hamiltonians. Has the same inputs ans outputs as #Custom_Hamiltonians.LoadHamiltonians
55  CustomHamiltoniansHandle
56  end
57 
58 
59  properties (Access = public)
60  %> An instance of class #CreateHamiltonians or its subclass to manipulate the Hamiltonian of the scattering region
61  CreateH
62  %> An instance of class #Transport_Interface (or its subclass) for transport calculations.
63  FL_handles
64  %> A cell array of classes #InterfaceRegion to describe the interface region between the leads and the scattering region
65  Interface_Regions
66  %> An instance of class #Peierls object to describe the peirls substitution in the scattering region
67  PeierlsTransform_Scatter
68  %> An instance of class #Peierls object to describe the peirls substitution in the leads
69  PeierlsTransform_Leads
70  %> Function handle S = f( x,y) of the gauge transformation in the scattering center. (S is a N x 1 vector, where N is the number of the points given by the x and y coordinates.)
72  %> function handle for individual physical model of the leads
73  leadmodel
74  %> function handle for individual physical model of the interface regions
75  interfacemodel
76  %> Input filename containing the computational parameters. (Obsolete)
77  filenameIn
78  %> Output filename to export the computational parameters
79  filenameOut
80  %> A string of the working directory
81  WorkingDir
82  %> An instance of class #Custom_Hamiltonians to load the Hamiltonians from external source
83  cCustom_Hamiltonians
84  %> if true, no output messages are print
85  silent
86  end
87 
88 
89 methods ( Access = public )
90 
91 
92 %% Contructor of the class
93 %> @brief Constructor of the class.
94 %> @param varargin Cell array of optional parameters. For details see #InputParsing.
95 %> @return An instance of the class
96 function obj = NTerminal( varargin )
97 
98  obj.G = []; % Greens function of the scattering region
99  obj.Ginv = []; % inverse of G
100  obj.param = [];
101  obj.Opt = [];
102 
103  obj.CreateH = [];
104  obj.FL_handles = [];
105  obj.Interface_Regions = [];
106  obj.PeierlsTransform_Scatter = [];
107  obj.PeierlsTransform_Leads = [];
108  obj.gauge_field = [];
109  obj.leadmodel = [];
110  obj.filenameIn = [pwd, filesep, 'Basic_Input_zigzag_leads_orig.xml'];
111  obj.filenameOut = [pwd, filesep, 'Basic_Input_running_parameters.xml'];
112  obj.WorkingDir = pwd;
113  obj.silent = false;
114  obj.E = 0;
115  obj.EF = [];
116  obj.q = [];
117 
118 
119  if strcmpi( class(obj), 'NTerminal')
120  % processing the optional parameters
121  obj.InputParsing( varargin{:} );
122 
123  obj.cCustom_Hamiltonians = [];
124 
125  obj.display(['EQuUs:Utils:', class(obj), ':Creating NTerminal class.'])
126 
127 
128  % exporting calculation parameters into an XML format
129  createOutput( obj.filenameOut, obj.Opt, obj.param );
130 
131  % create class intances and initializing class attributes
132  obj.CreateHandles();
133 
134  % create Hamiltonian of the scattering region (or load from external source)
135  obj.CreateNTerminalHamiltonians();
136  end
137 
138 
139 
140 end
141 
142 
143 
144 
145 %% Transport
146 %> @brief Calculates the transport through the two terminal setup. Use for development pupose only.
147 %> @param Energy The energy value.
148 %> @param varargin Cell array of optional parameters (https://www.mathworks.com/help/matlab/ref/varargin.html):
149 %> @param 'constant_channels' Logical value. Set true (default) to keep constant the number of the open channels in the leads for each energy value, or false otherwise.
150 %> @param 'gfininvfromHamiltonian' Logical value. Set true calculate the surface Greens function of the scattering region from the Hamiltonaian of the scattering region, or false (default) to calculate it by the fast way (see Phys. Rev. B 90, 125428 (2014) for details).
151 %> @param 'decimateDyson' Logical value. Set true (default) to decimate the sites of the scattering region in the Dyson equation.
152 %> @param 'PotInScatter' Obsolete parameter. Use 'scatterPotential' instead.
153 %> @param 'scatterPotential' A function handle pot=f( #Coordinates ) or pot=f( #CreateHamiltonians, Energy) for the potential to be applied in the Hamiltonian (used when FiniteGreensFunctionFromHamiltonian=true).
154 %> @param 'selfEnergy' Logical value. Set true to use the self energies of the leads in the Dyson equation, or false (default) to use the surface Green function instead.
155 %> @return [1] Conductance_matrix The conductance tensor
156 %> @return [2] ny Array of the open channel in the leads.
157 %> @return [3] S The scattering matrix.
158  function [Conductance_matrix,ny,S] = Transport(obj, Energy, varargin)
159 
160  p = inputParser;
161  p.addParameter('constant_channels', false);
162  p.addParameter('gfininvfromHamiltonian', false);
163  p.addParameter('decimateDyson', true);
164  p.addParameter('PotInScatter', []) %OBSOLETE use scatterPotential instead
165  p.addParameter('scatterPotential', []) %NEW overrides optional argument 'PotInScatter'
166  p.addParameter('selfEnergy', false)
167  p.parse(varargin{:});
168  constant_channels = p.Results.constant_channels;
169  gfininvfromHamiltonian = p.Results.gfininvfromHamiltonian;
170 
171  scatterPotential = p.Results.PotInScatter;
172  if ~isempty( p.Results.scatterPotential )
173  scatterPotential = p.Results.scatterPotential;
174  end
175 
176  decimateDyson = p.Results.decimateDyson;
177  selfEnergy = p.Results.selfEnergy;
178 
179  obj.CalcSpectralFunction(Energy, 'constant_channels', constant_channels, 'gfininvfromHamiltonian', gfininvfromHamiltonian, ...
180  'decimateDyson', decimateDyson, 'scatterPotential', scatterPotential, 'SelfEnergy', selfEnergy );
181 
182 
183  [S,ny] = obj.FL_handles.SmatrixCalc();
184 
185  norma = norm(S*S'-eye(sum(ny)));
186 
187  if norma >= 1e-3
188  obj.display( ['error of the unitarity of S-matrix: ',num2str(norma)] )
189  end
190 
191 
192  Conductance_matrix = obj.FL_handles.Conduktance();
193 
194  end
195 
196 
197 %% CalcSpectralFunction
198 %> @brief Calculates the spectral density and the Green operator.
199 %> @param Energy The energy value.
200 %> @param varargin Cell array of optional parameters (https://www.mathworks.com/help/matlab/ref/varargin.html):
201 %> @param 'constant_channels' Logical value. Set true (default) to keep constant the number of the open channels in the leads for each energy value, or false otherwise.
202 %> @param 'gfininvfromHamiltonian' Logical value. Set true calculate the surface Greens function of the scattering region from the Hamiltonaian of the scattering region, or false (default) to calculate it by the fast way (see Phys. Rev. B 90, 125428 (2014) for details).
203 %> @param 'decimateDyson' Logical value. Set true (default) to decimate the sites of the scattering region in the Dyson equation.
204 %> @param 'PotInScatter' Obsolete parameter. Use 'scatterPotential' instead.
205 %> @param 'scatterPotential' A function handle pot=f( #Coordinates ) or pot=f( #CreateHamiltonians, Energy) for the potential to be applied in the Hamiltonian (used when FiniteGreensFunctionFromHamiltonian=true).
206 %> @param 'selfEnergy' Logical value. Set true to use the self energies of the leads in the Dyson equation, or false (default) to use the surface Green function instead.
207 %> @return [1] The spectral density.
208 %> @return [2] The Green operator.
209  function [A,G] = CalcSpectralFunction(obj, Energy, varargin)
210  obj.setEnergy( Energy )
211 
212  p = inputParser;
213  p.addParameter('constant_channels', false);
214  p.addParameter('gfininvfromHamiltonian', false);
215  p.addParameter('decimateDyson', true);
216  p.addParameter('PotInScatter', []) %OBSOLETE use scatterPotential instead
217  p.addParameter('scatterPotential', []) %NEW overrides optional argument 'PotInScatter'
218  p.addParameter('selfEnergy', false)
219  p.parse(varargin{:});
220  constant_channels = p.Results.constant_channels;
221  gfininvfromHamiltonian = p.Results.gfininvfromHamiltonian;
222 
223  scatterPotential = p.Results.PotInScatter;
224  if ~isempty( p.Results.scatterPotential )
225  scatterPotential = p.Results.scatterPotential;
226  end
227 
228  decimateDyson = p.Results.decimateDyson;
229  selfEnergy = p.Results.selfEnergy;
230  if ~gfininvfromHamiltonian
231  obj.CalcFiniteGreensFunction('gauge_trans', true, 'onlyGinv', true);
232  else
233  obj.CalcFiniteGreensFunctionFromHamiltonian('gauge_trans', true, 'scatterPotential', scatterPotential, 'onlyGinv', true);
234  end
235 
236  Dysonfunc = @()(obj.CustomDysonFunc( 'constant_channels', constant_channels, 'decimate', decimateDyson, 'SelfEnergy', selfEnergy ));
237  try
238  G = obj.FL_handles.DysonEq( 'CustomDyson', Dysonfunc );
239  catch errCause
240  err = MException(['EQuUs:Utils:', class(obj),':CalcSpectralFunction'], 'Error occured in calculating the Greens function');
241  err = addCause(err, errCause);
242  save(['Error_', class(obj), '_CalcSpectralFunction.mat']);
243  obj.display(errCause.identifier, 1 );
244  obj.display( errCause.stack(1), 1 );
245  throw( errCause );
246  end
247 
248  A = -imag( trace(G))/pi;
249 
250 
251  end
252 
253 %% getCoordinates
254 %> @brief Gets the coordinates of the central region
255 %> @return [1] Coordinates of the central region.
256 %> @return [2] Coordinates of the interface region.
257 function [coordinates, coordinates_interface] = getCoordinates( obj )
258  try
259  coordinates = obj.CreateH.Read('coordinates');
260 
261  catch errCause
262  err = MException(['EQuUs:Utils:', class(obj), ':getCoordinates'], 'Error occured when retriving the coordinates');
263  err = addCause(err, errCause);
264  save('Error_Ribbon_getCoordinatesFromRibbon.mat');
265  throw( err );
266  end
267 
268 
269  try
270  if isempty( obj.Interface_Regions )
271  coordinates_interface = [];
272  return
273  end
274 
275  coordinates_interface = cell( length(obj.Interface_Regions), 1);
276  for idx = 1:length( obj.Interface_Regions )
277  coordinates_interface{idx} = obj.Interface_Regions{idx}.Read('coordinates');
278  end
279 
280  catch errCause
281  err = MException(['EQuUs:Utils:', class(obj), ':getCoordinates', 'Error occured when retriving the coordinates']);
282  err = addCause(err, errCause);
283  save('Error_Ribbon_getCoordinatesFromRibbon.mat');
284  throw( err );
285  end
286 
287 end
288 
289 
290 %% CreateScatter
291 %> @brief Creates an instance of class #CreateHamiltonians for storing and manipulate the Hamiltonian of the the scattering region. The created object is stored in attribute #CreateH.
292  function CreateH = CreateScatter( obj )
293 
294  %> Create an instance of class CreateHamiltonians to create the Hamiltonian of the scattering region
295  if ~strcmpi( class(obj.CreateH), 'CreateHamiltonians')
296  obj.CreateH = CreateHamiltonians(obj.Opt, obj.param, 'q', obj.q);
297  else
298  CreateH = obj.CreateH;
299  end
300 
301  %y Create the Hamiltonian of the scattering region if not created
302  if ~(obj.CreateH.Read('HamiltoniansCreated') && (~obj.CreateH.Read('HamiltoniansDecimated')))
303  obj.CreateH.CreateScatterH( 'CustomHamiltonian', obj.cCustom_Hamiltonians );
304  end
305 
306  %> apply magnetic field in scatter
307  if ~isempty( obj.PeierlsTransform_Scatter ) && isempty(obj.q) %for finite q vector potential must be parallel to q, and perpendicular to the unit cell vector
308  obj.display('Applying magnetic field in the scattering region')
309  obj.PeierlsTransform_Scatter.PeierlsTransfor( obj.CreateH );
310  end
311 
312  end
313 
314 %% setEnergy
315 %> @brief Sets the energy for the calculations
316 %> @param Energy The value of the energy in the same units as the Hamiltonian.
317  function setEnergy( obj, Energy )
318  obj.E = Energy;
319 
320  % resetting the class describing the N-terminal geometry
321  if ~isempty( obj.FL_handles ) && strcmpi(class(obj.FL_handles), 'Transport_Interface')
322  obj.FL_handles.setEnergy( obj.E );
323  end
324 
325  % reset the class describing the scattering region
326  if strcmpi( class(obj.CreateH), 'CreateHamiltonians')
327  obj.CreateH.Reset();
328  end
329 
330  % create interface regions
331  for idx = 1:length(obj.Interface_Regions)
332  obj.Interface_Regions{idx}.Reset();
333  end
334 
335  % recreate the Hamiltonian of the scattering region
336  if ~isempty( obj.CreateH ) && strcmpi( class(obj), 'NTerminal' )
337  obj.CreateNTerminalHamiltonians();
338  end
339 
340  end
341 
342 
343 %% getEnergy
344 %> @brief Retrives the energy value (attribute #E) used in the calculations
345 %> @return The energy value
346  function ret = getEnergy(obj)
347  ret = obj.E;
348  end
349 
350 
351 %% getFermiEnergy
352 %> @brief Retrives the Fermi level (attribute #EF) used in the calculations
353 %> @return The Femi level
354  function ret = getFermiEnergy(obj)
355  ret = obj.EF;
356  end
357 
358 
359 %% CustomDysonFunc
360 %> @brief Custom Dyson function for a general two terminal arrangement.
361 %> @param varargin Cell array of optional parameters (https://www.mathworks.com/help/matlab/ref/varargin.html):
362 %> @param 'gfininv' The inverse of the Greens function of the scattering region. For default the inverse of the attribute #G is used.
363 %> @param 'constant_channels' Logical value. Set true (default) to keep constant the number of the open channels in the leads for each energy value, or false otherwise.
364 %> @param 'onlyGinverz' Logical value. Set true to calculate only the inverse of the total Green operator, or false (default) to calculate #G as well.
365 %> @param 'recalculateSurface' A vector of the identification numbers of the lead surfaces to be recalculated.
366 %> @param 'decimate' Logical value. Set true (default) to eliminate all inner sites in the Greens function and keep only the selected sites. Set false to omit the decimation procedure.
367 %> @param 'kulso_szabfokok' Array of sites to be kept after the decimation procedure. (Use parameter 'keep_sites' instead)
368 %> @param 'selfEnergy' Logical value. Set true to use the self energies of the leads in the Dyson equation, or false (default) to use the surface Green function instead.
369 %> @param 'keep_sites' Name of sites to be kept in the resulted Green function (POssible values are: 'scatter', 'interface', 'lead').
370 %> @param 'UseHamiltonian' Set true if the interface region is matched to the whole Hamiltonian of the scattering center, or false (default) if the surface Green operator of the scattering center is used in the calculations.
371 %> @return [1] The calculated Greens function.
372 %> @return [2] The inverse of the Green operator.
373 %> @return [3] An instance of structure #junction_sites describing the sites in the calculated Green operator.
374  function [Gret, Ginverz, junction_sites] = CustomDysonFunc( obj, varargin )
375 
376  p = inputParser;
377  p.addParameter('gfininv', []);
378  p.addParameter('constant_channels', true);
379  p.addParameter('onlyGinverz', false );
380  p.addParameter('recalculateSurface', 1:length(obj.param.Leads) );
381  p.addParameter('decimate', true );
382  p.addParameter('kulso_szabfokok', []); %The list of sites to be left after the decimation procedure
383  p.addParameter('SelfEnergy', false); %set true to calculate the Dyson equation with the self energy
384  p.addParameter('keep_sites', 'lead'); %identification of sites to be kept (scatter, interface, lead)
385  p.addParameter('UseHamiltonian', false); %true if the interface region is matched to the whole Hamiltonian of the scattering center, false if the surface Green operator of the scattering center is used in the calculations.
386  p.parse(varargin{:});
387  gfininv = p.Results.gfininv;
388  constant_channels = p.Results.constant_channels;
389  onlyGinverz = p.Results.onlyGinverz;
390  recalculateSurface = p.Results.recalculateSurface;
391  decimate = p.Results.decimate;
392  kulso_szabfokok = p.Results.kulso_szabfokok;
393  useSelfEnergy = p.Results.SelfEnergy;
394  keep_sites = p.Results.keep_sites;
395  UseHamiltonian = p.Results.UseHamiltonian;
396 
397  if isempty(gfininv)
398  if ~isempty( obj.Ginv )
399  gfininv = obj.Ginv;
400  else
401  rcond_G = rcond(obj.G);
402  if isnan(rcond_G) || abs( rcond_G ) < 1e-15
403  gfininv = obj.inv_SVD( obj.G );
404  else
405  gfininv = inv(obj.G);
406  end
407  end
408  end
409 
410  if ~isempty(recalculateSurface)
411 
412  % creating interfaces for the Leads
413  if constant_channels
414  shiftLeads = ones(length(obj.param.Leads),1)*obj.E;
415  else
416  shiftLeads = ones(length(obj.param.Leads),1)*0;
417  end
418 
419  % creating objects describing the Leads
420  Leads = obj.FL_handles.LeadCalc('shiftLeads', shiftLeads, ...
421  'SelfEnergy', useSelfEnergy, 'SurfaceGreensFunction', ~useSelfEnergy, 'gauge_field', obj.gauge_field, 'leads', recalculateSurface, 'q', obj.q, ...
422  'leadmodel', obj.leadmodel, 'CustomHamiltonian', obj.cCustom_Hamiltonians);
423  else
424  Leads = obj.FL_handles.Read( 'Leads' );
425  end
426 
427 
428  Neffs = obj.FL_handles.Get_Neff();
429 
430 
431  if useSelfEnergy
432  Ginverz = CalcGinverzwithSelfEnergy();
433  else
434  Ginverz = CalcGinverz();
435  end
436 
437  junction_sites = GetJunctionSites();
438 
439  if decimate
440  GetSitesForDecimation();
441  Ginverz = obj.DecimationFunction( kulso_szabfokok, Ginverz);
442  end
443 
444 
445 
446  if onlyGinverz
447  Gret = [];
448  return
449  end
450 
451  if issparse( Ginverz )
452  err = MException(['EQuUs:Utils:', class(obj), ':CustomDysonFunc', 'Ginverz is sparse. Calculation of the inverse of a sparse matrix is not supported at this point']);
453  save('Error_Ribbon_CustomDysonFunc.mat');
454  throw(err);
455  end
456 
457  rcond_Ginverz = rcond(Ginverz);
458  if isnan( rcond_Ginverz )
459  err = MException(['EQuUs:Utils:', class(obj), ':CustomDysonFunc'], 'NaN is the condition number for Ginverz');
460  save('Error_Ribbon_CustomDysonFunc.mat');
461  throw(err);
462  end
463 
464  if abs( rcond_Ginverz ) < 1e-15
465  obj.display( ['EQuUs:Utils:', class(obj), ':CustomDysonFunc: Regularizing Ginverz by SVD'],1);
466  Gret = obj.inv_SVD( Ginverz );
467  else
468  Gret = inv( Ginverz );
469  end
470 
471  % nested functions
472 
473  %-------------------------------
474  %> calculate the inverse Greens function
475  function Ginverz = CalcGinverz()
476 
477  Gsurfinverz = cell(length(Neffs),1);
478  for idx = 1:length(Neffs)
479  Gsurfinverz{idx} = Leads{idx}.Read('gsurfinv');
480  end
481 
482  K_interface = cell(length(Neffs),1);
483  K1_sc = cell(length(Neffs),1);
484  K1adj_sc = cell(length(Neffs),1);
485  K1 = cell(length(Neffs),1);
486  K1adj = cell(length(Neffs),1);
487  for idx = 1:length(recalculateSurface)
488  obj.CreateInterface( recalculateSurface(idx), 'UseHamiltonian', UseHamiltonian );
489  end
490  for idx = 1:length( obj.Interface_Regions )
491  [K_interface{idx}, K1{idx}, K1adj{idx}, K1_sc{idx}, K1adj_sc{idx}] = obj.Interface_Regions{idx}.Get_Effective_Hamiltonians();
492  end
493 
494  %> getting dimensions
495  rows_interface= zeros(size(Neffs));
496  cols_interface= zeros(size(Neffs));
497  for idx = 1:length(Neffs)
498  rows_interface(idx) = size(K_interface{idx},1);
499  cols_interface(idx) = size(K_interface{idx},2);
500  end
501  cols_scatter = size(gfininv,2);
502 
503  % check whether gfininv is sparse
504  if issparse(gfininv)
505  Ginverz = sparse( [], [], [], sum(Neffs)+sum(rows_interface)+size(gfininv,1), sum(Neffs)+sum(cols_interface)+size(gfininv,2) );
506  else
507  Ginverz = zeros( sum(Neffs)+sum(rows_interface)+size(gfininv,1), sum(Neffs)+sum(cols_interface)+size(gfininv,2) );
508  end
509 
510  for idx = 1:length(Neffs)
511  % surface Green function of leads
512  row_indexes_lead = sum(Neffs(1:idx-1))+1:sum(Neffs(1:idx));
513  col_indexes_lead = sum(Neffs(1:idx-1))+1:sum(Neffs(1:idx));
514  Ginverz( row_indexes_lead, col_indexes_lead ) = Gsurfinverz{idx};
515 
516  %interface region and coupling to the leads
517  row_indexes_interface = sum(Neffs) + (sum(rows_interface(1:idx-1))+1:sum(rows_interface(1:idx)));
518  col_indexes_interface = sum(Neffs) + (sum(cols_interface(1:idx-1))+1:sum(cols_interface(1:idx)));
519  Ginverz( row_indexes_lead, col_indexes_interface ) = -K1{idx};
520  Ginverz( row_indexes_interface, col_indexes_lead ) = -K1adj{idx};
521  Ginverz( row_indexes_interface, col_indexes_interface ) = -K_interface{idx};
522 
523  %scattering region and coupling to the interface regions
524  col_indexes_scatter = sum(Neffs) + sum(cols_interface) + (1:cols_scatter);
525  Ginverz( row_indexes_interface, col_indexes_scatter ) = -K1_sc{idx};
526  Ginverz( col_indexes_scatter, col_indexes_interface ) = -K1adj_sc{idx};
527  end
528 
529  Ginverz( end-size(gfininv,1)+1:end, end-size(gfininv,2)+1:end) = gfininv;
530 
531  %[K0_lead, K1_lead, K1adj_lead] = Leads{1}.Get_Effective_Hamiltonians();
532  %Ginverz = [Gsurfinverz{1}, -K1_lead; -K1adj_lead, Gsurfinverz{2}];
533  end
534 
535 
536  %-------------------------------
537  % calculate the inverse Greens function with the self energy
538  function Ginverz = CalcGinverzwithSelfEnergy()
539  SelfEnergy = cell(length(Neffs),1);
540  for iidx = 1:length(Neffs)
541  SelfEnergy{iidx} = Leads{iidx}.Read('Sigma');
542  end
543 
544  K_interface = cell(length(Neffs),1);
545  K1_sc = cell(length(Neffs),1);
546  K1adj_sc = cell(length(Neffs),1);
547  K1 = cell(length(Neffs),1);
548  K1adj = cell(length(Neffs),1);
549 
550  for idx = 1:length(recalculateSurface)
551  obj.CreateInterface( recalculateSurface(idx), 'UseHamiltonian', UseHamiltonian );
552  end
553  for idx = 1:length( obj.Interface_Regions )
554  [K_interface{idx}, K1{idx}, K1adj{idx}, K1_sc{idx}, K1adj_sc{idx}] = obj.Interface_Regions{idx}.Get_Effective_Hamiltonians();
555  end
556 
557  % getting dimensions
558  rows_interface= zeros(size(Neffs));
559  cols_interface= zeros(size(Neffs));
560  for idx = 1:length(Neffs)
561  rows_interface(idx) = size(K_interface{idx},1);
562  cols_interface(idx) = size(K_interface{idx},2);
563  end
564  cols_scatter = size(gfininv,2);
565 
566  % check whether gfininv is sparse
567  if issparse(gfininv)
568  Ginverz = sparse( [], [], [], sum(rows_interface)+size(gfininv,1), sum(cols_interface)+size(gfininv,2) );
569  else
570  Ginverz = zeros( sum(rows_interface)+size(gfininv,1), sum(cols_interface)+size(gfininv,2) );
571  end
572 
573  for idx = 1:length(Neffs)
574  %interface region with the self energies of the leads
575  K_interface{idx}(1:Neffs(idx), 1:Neffs(idx)) = K_interface{idx}(1:Neffs(idx), 1:Neffs(idx)) + SelfEnergy{idx};
576  row_indexes_interface = (sum(rows_interface(1:idx-1))+1:sum(rows_interface(1:idx)));
577  col_indexes_interface = (sum(cols_interface(1:idx-1))+1:sum(cols_interface(1:idx)));
578  Ginverz( row_indexes_interface, col_indexes_interface ) = -K_interface{idx};
579 
580  %scattering region and coupling to the interface regions
581  col_indexes_scatter = sum(cols_interface) + (1:cols_scatter);
582  Ginverz( row_indexes_interface, col_indexes_scatter ) = -K1_sc{idx};
583  Ginverz( col_indexes_scatter, col_indexes_interface ) = -K1adj_sc{idx};
584  end
585 
586  Ginverz( end-size(gfininv,1)+1:end, end-size(gfininv,2)+1:end) = gfininv;
587 
588 % [K0, K1, K1adj] = Leads{1}.Get_Effective_Hamiltonians();
589 % %[K_interface{1}, K1_interface{1}, K1adj_interface{1}, K1_sc{1}, K1adj_sc{1}] = obj.Interface_Regions{1}.Get_Effective_Hamiltonians();
590 % Hscatter = obj.CreateH.Read('Hscatter');
591 % Sscatter = obj.CreateH.Read('Sscatter');
592 % Kscatter = Hscatter - Sscatter*obj.E;
593 %
594 % Ginverz2 = [-K_interface{1}, -K1, zeros(size(K_interface{2}));
595 % -K1', gfininv, -K1;
596 % zeros(size(K_interface{2})), -K1', -K_interface{2}];
597 %
598 % 5
599 
600 
601  end
602 
603 
604  % creating site indexes corresponding to the elements of the calculated Green operator
605  function junction_sites = GetJunctionSites()
606 
608 
609  % determine the matrix sizes
610  size_K0_leads = zeros(length(Leads), 1);
611  size_K0_interface = zeros(length(Leads), 1);
612  for kdx = 1:length(Leads)
613  K0_lead = Leads{kdx}.Get_Effective_Hamiltonians();
614  size_K0_leads(kdx) = size(K0_lead,1);
615 
616  K0_interface = obj.Interface_Regions{kdx}.Get_Effective_Hamiltonians();
617  size_K0_interface(kdx) = size(K0_interface,1);
618  end
619 
620  % determine junction sites corresponding to the scattering region
621  junction_sites.Scatter = structures('sites');
622  junction_sites.Scatter.coordinates = obj.CreateH.Read('coordinates');
623  junction_sites.Scatter.kulso_szabfokok = obj.CreateH.Read('kulso_szabfokok');
624 
625  if useSelfEnergy
626  junction_sites.Scatter.site_indexes = sum(size_K0_interface) + (1:size(gfininv,1)); %including 2*interface regions
627  else
628  junction_sites.Scatter.site_indexes = sum(size_K0_leads) + sum(size_K0_interface) + (1:size(gfininv,1)); %including 2*interface regions and 2 leads
629  end
630 
631  % determine junction sites corresponding to the interface
632  % regions and leads
633  junction_sites.Leads = cell(length(Leads),1);
634  junction_sites.Interface = cell(length(Leads),1);
635  [~, coordinates_interface] = obj.getCoordinates();
636  for kdx = 1:length(Leads)
637  junction_sites.Interface{kdx} = structures('sites');
638  junction_sites.Leads{kdx} = structures('sites');
639 
640  if useSelfEnergy
641  junction_sites.Interface{kdx}.site_indexes = sum(size_K0_interface(1:kdx-1)) + (1:size_K0_interface(kdx));
642  junction_sites.Interface{kdx}.coordinates = coordinates_interface{kdx};
643 
644  junction_sites.Leads{kdx}.site_indexes = sum(size_K0_interface(1:kdx-1)) + (1:size_K0_leads(kdx));
645  junction_sites.Leads{kdx}.coordinates = Leads{kdx}.Read('coordinates');
646  junction_sites.Leads{kdx}.kulso_szabfokok = Leads{kdx}.Read('kulso_szabfokok');
647  else
648  junction_sites.Leads{kdx}.site_indexes = sum(size_K0_leads(1:kdx-1)) + (1:size_K0_leads(kdx));
649  junction_sites.Leads{kdx}.coordinates = Leads{kdx}.Read('coordinates');
650  junction_sites.Leads{kdx}.kulso_szabfokok = Leads{kdx}.Read('kulso_szabfokok');
651 
652  junction_sites.Interface{kdx}.site_indexes = sum(size_K0_leads) + sum(size_K0_interface(1:kdx-1)) + (1:size_K0_interface(kdx));
653  junction_sites.Interface{kdx}.coordinates = coordinates_interface{kdx};
654  end
655 
656 
657 
658  end
659 
660  end
661 
662 
663  % Obtain the site indexes to be decimated out and removes the unnecesarry sites from the structure junction_sites according to the
664  % performed decimation
665  function GetSitesForDecimation()
666 
667  if isempty(kulso_szabfokok)
668  if strcmpi(keep_sites, 'scatter')
669  kulso_szabfokok = get_scatter_sites();
670 
671  junction_sites.Scatter.site_indexes = 1:length(kulso_szabfokok);
672  junction_sites.Interface = [];
673  junction_sites.Leads = [];
674 
675  elseif strcmpi(keep_sites, 'interface')
676  kulso_szabfokok = get_interface_sites();
677 
678  junction_sites.Scatter = [];
679  interface_size = 0;
680  for idx = 1:length( junction_sites.Interface )
681  junction_sites.Interface{idx}.site_indexes = interface_size + (1: length(junction_sites.Interface{idx}.site_indexes));
682  interface_size = interface_size + length(junction_sites.Interface{idx}.site_indexes);
683  end
684  junction_sites.Leads = [];
685 
686  elseif strcmpi(keep_sites, 'lead')
687  kulso_szabfokok = get_lead_sites();
688 
689  junction_sites.Scatter = [];
690  junction_sites.Interface = [];
691  leads_size = 0;
692  for idx = 1:length( junction_sites.Leads )
693  junction_sites.Leads{idx}.site_indexes = leads_size + (1: length(junction_sites.Leads{idx}.site_indexes));
694  leads_size = leads_size + length(junction_sites.Leads{idx}.site_indexes);
695  end
696  else
697  error(['EQuUs:Utils:', class(obj), ':CustomDysonFunc'], ['Undifined Sites: ', keep_sites]);
698  end
699 
700  else
701  % for custom given kulso_szabfokok
702 
703  % determine sites in the scattering center
704  junction_sites.Scatter = SelectSites( junction_sites.Scatter );
705 
706 
707  % determine sites in the interface regions
708  for idx = 1:length(junction_sites.Interface)
709  junction_sites.Interface{idx} = SelectSites( junction_sites.Interface{idx} );
710  end
711 
712 
713  % determine sites in the interface regions
714  for idx = 1:length(junction_sites.Leads)
715  junction_sites.Leads{idx} = SelectSites( junction_sites.Leads{idx} );
716  end
717 
718 
719  end
720 
721  %-------------------------------------------------------------
722  % an auxilary function to select the sites to be kept
723  function sites_ret = SelectSites( sites )
724  site_indexes_tmp = sites.site_indexes;
725  start_index = find( min(site_indexes_tmp) <= kulso_szabfokok, 1, 'first');
726  end_index = find( max(site_indexes_tmp) >= kulso_szabfokok, 1, 'last');
727 
728  if isempty(start_index)
729  sites_ret = [];
730  return
731  end
732 
733  sites_ret = structures('sites');
734  sites_ret.coordinates = sites.coordinates;
735 
736  % selecting site indexes
737  if isempty(end_index)
738  sites_ret.site_indexes = 1:length(kulso_szabfokok(start_index:end));
739  else
740  sites_ret.site_indexes = 1:length(kulso_szabfokok(start_index:end_index));
741  end
742 
743  % selecting coordinate sof the sites
744  names = fieldnames( sites.coordinates );
745  for iidx = 1:length(names)
746  fieldname = names(iidx);
747  if strcmpi( fieldname, 'a') || strcmpi( fieldname, 'b')
748  continue
749  end
750 
751  field_tmp = sites_ret.coordinates.(fieldname);
752 
753  if isempty(field_tmp)
754  continue
755  end
756 
757  if isempty(end_index)
758  field_tmp = field_tmp( kulso_szabfokok(start_index:end) - min(site_indexes_tmp) + 1 );
759  else
760  field_tmp = field_tmp( kulso_szabfokok(start_index:end_index) - min(site_indexes_tmp) + 1 );
761  end
762  sites_ret.coordinates.(fieldname) = field_tmp;
763  end
764 
765 
766  end
767 
768  end
769 
770 
771  %-------------------------------
772  % determine the site indexes of the scattering region within Ginverz
773  function kulso_szabfokok = get_scatter_sites()
774  kulso_szabfokok = junction_sites.Scatter.site_indexes;
775  end
776 
777  %-------------------------------
778  % determine the site indexes of the interface region within Ginverz
779  function kulso_szabfokok = get_interface_sites()
780  size_interface = 0;
781  for idx = 1:length( junction_sites.Interface )
782  size_interface = size_interface + length(junction_sites.Interface{idx}.site_indexes);
783  end
784 
785  kulso_szabfokok = zeros( size_interface, 1);
786  size_interface = 0;
787  for idx = 1:length( junction_sites.Interface )
788  indexes = size_interface + ( 1:length(junction_sites.Interface{idx}.site_indexes) );
789  kulso_szabfokok(indexes) = junction_sites.Interface{idx}.site_indexes;
790  size_interface = size_interface + length(junction_sites.Interface{idx}.site_indexes);
791  end
792 
793  end
794 
795  %-------------------------------
796  % determine the site indexes of the leads within Ginverz
797  function kulso_szabfokok = get_lead_sites()
798 
799  size_leads = 0;
800  for idx = 1:length( junction_sites.Leads )
801  size_leads = size_leads + length(junction_sites.Leads{idx}.site_indexes);
802  end
803 
804  kulso_szabfokok = zeros( size_leads, 1);
805  size_leads = 0;
806  for idx = 1:length( junction_sites.Leads )
807  indexes = size_leads + ( 1:length(junction_sites.Leads{idx}.site_indexes) );
808  kulso_szabfokok(indexes) = junction_sites.Leads{idx}.site_indexes;
809  size_leads = size_leads + length(junction_sites.Leads{idx}.site_indexes);
810  end
811 
812 
813  end
814 
815  % end nested functions
816 
817  end
818 
819 
820 %% DecimationFunction
821 %> @brief Performs the decimation procedure on the inverse Green operator.
822 %> @param kulso_szabfokok Array of sites to be kept after the decimation.
823 %> @param ginv The inverse of the Green operator.
824 %> @param varargin Cell array of optional parameters (https://www.mathworks.com/help/matlab/ref/varargin.html):
825 %> @param 'coordinates' An instance of the structure #Coordinates containing the coordinates of the sites.
826 %> @return [1] The matrix of the decimated inverse Greens operator.
827 %> @return [2] An instance of structure #Coordinates containing the sites remained after the decimation.
828  function [ret, coordinates_ret] = DecimationFunction( obj, kulso_szabfokok, ginv, varargin)
829  p = inputParser;
830  p.addParameter('coordinates', [] );
831  p.parse(varargin{:});
832  coordinates = p.Results.coordinates;
833 
834  CreateH = CreateHamiltonians(obj.Opt, obj.param);
835 
836  Hamiltoni = eye(size(ginv))*obj.E - ginv;
837  ginv = [];
838 
839  CreateH.Write('Hscatter', Hamiltoni);
840  clear Hamiltoni;
841 
842  CreateH.Write('kulso_szabfokok', kulso_szabfokok);
843  CreateH.Write('coordinates', coordinates);
844  CreateH.Write('HamiltoniansCreated', 1);
845  CreateH.Write('HamiltoniansDecimated', 0);
846 
847  Decimation_Procedure = Decimation(obj.Opt);
848  Decimation_Procedure.DecimationFunc(obj.E, CreateH, 'Hscatter', 'kulso_szabfokok');
849 
850  Hamiltoni = CreateH.Read('Hscatter');
851  CreateH.Clear('Hscatter');
852 
853  ret = eye(size(Hamiltoni))*obj.E - Hamiltoni;
854  Hamiltoni = [];
855 
856 
857  coordinates_ret = CreateH.Read('coordinates');
858 
859 
860  end
861 
862 
863 %% GetFiniteGreensFunction
864 %> @brief Query fo the calculated Green operator of the scattering center.
865 %> @return [1] The Green operator.
866 %> @return [2] The inverse Green operator.
867  function [Gret, Ginvret] = GetFiniteGreensFunction( obj )
868  Gret = obj.G;
869  Ginvret = obj.Ginv;
870  end
871 
872 %% CalcFiniteGreensFunction
873 %> @brief Calculates the Green operator of the scattering region.
874 %> @param varargin Cell array of optional parameters (https://www.mathworks.com/help/matlab/ref/varargin.html):
875 %> @param 'gauge_trans' Logical value. Set true to perform gauge transformation on the Green operator and on the Hamiltonians.
876 %> @param 'onlyGinv' Logical value. Set true to calculate only the inverse of the surface Greens function #Ginv, or false (default) to calculate #G as well. In the latter case the attribute #Ginv is set to empty at the end.
877  function CalcFiniteGreensFunction( obj, varargin )
878 
879  p = inputParser;
880  p.addParameter('gauge_trans', false); % logical: true if want to perform gauge transformation on the Green's function and Hamiltonians
881  p.addParameter('onlyGinv', false);
882  p.parse(varargin{:});
883  gauge_trans = p.Results.gauge_trans;
884  onlyGinv = p.Results.onlyGinv;
885 
886  obj.CalcFiniteGreensFunctionFromHamiltonian('gauge_trans', gauge_trans, 'onlyGinv', onlyGinv);
887 
888  end
889 
890 
891 %% CalcFiniteGreensFunctionFromHamiltonian
892 %> @brief Calculates the Green operator of the scattering region from the whole Hamiltonian.
893 %> @param varargin Cell array of optional parameters (https://www.mathworks.com/help/matlab/ref/varargin.html):
894 %> @param 'gauge_trans' Logical value. Set true to perform gauge transformation on the Green operator and on the Hamiltonians.
895 %> @param 'onlyGinv' Logical value. Set true to calculate only the inverse of the surface Greens function #Ginv, or false (default) to calculate #G as well. In the latter case the attribute #Ginv is set to empty at the end.
896 %> @param 'PotInScatter' Obsolete parameter. Use 'scatterPotential' instead.
897 %> @param 'scatterPotential' A function handle pot=f( #Coordinates ) or pot=f( #CreateHamiltonians, Energy) for the potential to be applied in the Hamiltonian (used when FiniteGreensFunctionFromHamiltonian=true).
898  function CalcFiniteGreensFunctionFromHamiltonian( obj, varargin )
899 
900 
901 
902  p = inputParser;
903  p.addParameter('gauge_trans', false); % logical: true if want to perform gauge transformation on the Green's function and Hamiltonians
904  p.addParameter('onlyGinv', false);
905  p.addParameter('PotInScatter', []) %OBSOLETE use scatterPotential instead
906  p.addParameter('scatterPotential', []) %NEW overrides optional argument 'PotInScatter'
907  p.parse(varargin{:});
908  gauge_trans = p.Results.gauge_trans;
909  onlyGinv = p.Results.onlyGinv;
910 
911 
912  scatterPotential = p.Results.PotInScatter;
913  if ~isempty( p.Results.scatterPotential )
914  scatterPotential = p.Results.scatterPotential;
915  end
916 
917 
918  obj.CreateScatter();
919 %****************************************
920  CreateH = obj.CreateH;
921  Hscatter = CreateH.Read('Hscatter');
922  Sscatter = CreateH.Read('Sscatter');
923  coordinates = CreateH.Read('coordinates');
924  kulso_szabfokok = CreateH.Read( 'kulso_szabfokok' );
925 
926 
927  if ~isempty(scatterPotential)
928  obj.ApplyPotentialInScatter( CreateH, scatterPotential)
929  Hscatter = CreateH.Read('Hscatter');
930  end
931 
932 
933  q = obj.CreateH.Read('q');
934  if ~isempty( q ) && ~obj.CreateH.Read('HamiltoniansDecimated')
935  Hscatter_transverse = obj.CreateH.Read('Hscatter_transverse');
936  Hscatter = Hscatter + Hscatter_transverse*diag(exp(-1i*q)) + Hscatter_transverse'*diag(exp(1i*q));
937  obj.CreateH.Clear('Hscatter_transverse');
938  end
939 
940  % Applying overlap matrices
941  if isempty( Sscatter )
942  Hscatter = (sparse(1:size(Hscatter,1), 1:size(Hscatter,1), obj.E, size(Hscatter,1),size(Hscatter,1)) - Hscatter);
943  else
944  Hscatter = obj.E*Sscatter - Hscatter;
945  end
946 
947  indexes = false( size(Hscatter,1), 1);
948  indexes(kulso_szabfokok) = true;
949  Hscatter = [ Hscatter( ~indexes, ~indexes) , Hscatter(~indexes, indexes);
950  Hscatter(indexes, ~indexes), Hscatter(indexes, indexes)];
951 
952  obj.G = obj.partialInv( Hscatter, length(kulso_szabfokok) );
953 
954 
955 % Hscatter = obj.CreateH.Read('Hscatter');
956 % Hscatter = (sparse(1:size(Hscatter,1), 1:size(Hscatter,1), obj.E, size(Hscatter,1),size(Hscatter,1)) - Hscatter);
957 % obj.G = inv(Hscatter);
958 %**************************************************
959 
960  % gauge transformation of the vector potential in the effective Hamiltonians
961  if gauge_trans
962  try
963  surface_coordinates = obj.getCoordinates();
964  % gauge transformation on Green's function
965  if ~isempty(obj.G) && ~isempty(obj.PeierlsTransform_Scatter) && isempty(obj.q)
966  % gauge transformation on the inverse Green's function
967  obj.G = obj.PeierlsTransform_Scatter.gaugeTransformation( obj.G, surface_coordinates, obj.gauge_field );
968  end
969  catch errCause
970  err = MException(['EQuUs:Utils:', class(obj), ':CalcFiniteGreensFunctionFromHamiltonian'], 'Unable to perform gauge transformation');
971  err = addCause(err, errCause);
972  save('Error_Ribbon_CalcFiniteGreensFunctionFromHamiltonian.mat')
973  throw(err);
974  end
975  end
976 
977  if onlyGinv
978  rcond_G = rcond(obj.G);
979  if isnan(rcond_G ) || abs( rcond_G ) < 1e-15
980  obj.display( ['EQuUs:Utils:', class(obj), ':CalcFiniteGreensFunctionFromHamiltonian: Regularizing Ginv by SVD'],1);
981  obj.Ginv = obj.inv_SVD( obj.G );
982  else
983  obj.Ginv = inv(obj.G);
984  end
985  obj.G = [];
986  else
987  obj.Ginv = [];
988  end
989 
990  end
991 
992 
993 
994 
995 %% setInterfaceRegions
996 %> @brief Replaces the attribute Interface_Region with the given value.
997 %> @param Interface_Regions A two component array of classes InterfaceRegion
998  function setInterfaceRegions( obj, Interface_Regions )
999  if length( Interface_Regions ) ~= length(obj.param.Leads)
1000  err = MException(['EQuUs:Utils:', class(obj), ':setInterfaceRegions'], ['The length of Interface_Regions must be ', num2str(length(obj.param.Leads))]);
1001  save('Error_Ribbon_setInterfaceRegions.mat');
1002  throw(err);
1003  end
1004 
1005  if ~iscell( Interface_Regions )
1006  err = MException(['EQuUs:Utils:', class(obj), ':setInterfaceRegions'], 'The Interface_Regions must be a cell containing of instances of class InterfaceRegion.');
1007  save('Error_Ribbon_setInterfaceRegions.mat');
1008  throw(err);
1009  end
1010 
1011  obj.Interface_Regions = Interface_Regions;
1012 
1013  end
1014 
1015 %% CreateInterface
1016 %> @brief Creates the Hamiltonians for the interface regions between the leads and scattering center.
1017 %> @param idx Identification number of the interface region.
1018 %> @param varargin Cell array of optional parameters (https://www.mathworks.com/help/matlab/ref/varargin.html):
1019 %> @param 'UseHamiltonian' Set true if the Dyson equation is constructed from the whole Hamiltonian of the scattering region and the interface region is not needed to be truncated
1020  function CreateInterface( obj, idx, varargin )
1021 
1022  p = inputParser;
1023  p.addParameter('UseHamiltonian', false); %Set true if the Dyson equation is constructed from the whole Hamiltonian of the scattering region and the interface region is not needed to be truncated
1024  p.parse(varargin{:});
1025  UseHamiltonian = p.Results.UseHamiltonian;
1026 
1027  Interface_Region = obj.Interface_Regions{idx} ;
1028 
1029  if ~obj.Interface_Regions{idx}.Read( 'HamiltoniansCreated' )
1030  obj.display(['EQuUs:Utils:', class(obj), ':CreateInterface: Creating interface region ', num2str(idx)])
1031  H0 = obj.cCustom_Hamiltonians.Read( 'H0' );
1032  S0 = obj.cCustom_Hamiltonians.Read( 'S0' );
1033  H1 = obj.cCustom_Hamiltonians.Read( 'H1' );
1034  S1 = obj.cCustom_Hamiltonians.Read( 'S1' );
1035  H_coupling = obj.cCustom_Hamiltonians.Read( 'Hcoupling' );
1036  S_coupling = obj.cCustom_Hamiltonians.Read( 'Scoupling' );
1037  coordinates = obj.cCustom_Hamiltonians.Read( 'coordinates' );
1038  Interface_Region.Write( 'H0', H0{idx} );
1039  if ~isempty( S0 )
1040  Interface_Region.Write( 'S0', S0{idx} );
1041  end
1042 
1043  Interface_Region.Write( 'H1', H1{idx} );
1044  Interface_Region.Write( 'H1adj', H1{idx}' );
1045  if ~isempty( S1 )
1046  Interface_Region.Write( 'S1', S1{idx} );
1047  end
1048 
1049 
1050 
1051  Interface_Region.Write('Hcoupling', H_coupling{idx});
1052  Interface_Region.Write('Hcouplingadj', H_coupling{idx}');
1053  if ~isempty( S_coupling )
1054  Interface_Region.Write('Scoupling', S_coupling{idx});
1055  end
1056 
1057  Interface_Region.Write( 'M', size(H0{idx},1) );
1058  Interface_Region.Write( 'coordinates', coordinates{idx} );
1059  Interface_Region.Write( 'coordinates2', obj.CreateH.Read('coordinates') );
1060 
1061  % Transforming the Hamiltonians according to the BdG model
1062  Interface_Region.Transform2BdG();
1063 
1064  % truncating the coupling Hamiltonians to fit the scattering region
1065  if ~UseHamiltonian
1066  surface_points = obj.CreateH.Read( 'kulso_szabfokok' );
1067  H_coupling = Interface_Region.Read('Hcoupling');
1068  indexes = false( size(H_coupling, 2), 1);
1069  indexes( surface_points ) = true;
1070  H_coupling = H_coupling(:,indexes);
1071  Interface_Region.Write('Hcoupling', H_coupling);
1072  Interface_Region.Write('Hcouplingadj', H_coupling');
1073 
1074 
1075  S_coupling = Interface_Region.Read('Scoupling');
1076  if ~isempty( S_coupling )
1077  S_coupling = S_coupling(:,surface_points);
1078  Interface_Region.Write('Scoupling', S_coupling);
1079  end
1080 
1081  % keeping data on the surface sites of the scattering region
1082  coordinates2 = obj.Interface_Regions{idx}.Read('coordinates2');
1083  coordinates2 = coordinates2.KeepSites( indexes );
1084  obj.Interface_Regions{idx}.Write('coordinates2', coordinates2);
1085 
1086  end
1087 
1088  end
1089 
1090 
1091  % apply magnetic field in the interface region
1092  if ~isempty( obj.PeierlsTransform_Leads )
1093  % In superconducting lead one must not include nonzero magnetic
1094  % field.
1095  % Hamiltonians in transverse computations must remain
1096  % traslational invariant.
1097  if ~Interface_Region.isSuperconducting() %&& isempty( obj.Interface_Regions{idx}.Read('q') )
1098  obj.display(['EQuUs:Utils:', class(obj), 'CreateInterface: Applying magnetic field in the Hamiltonians of interface region ', num2str(idx)])
1099  obj.PeierlsTransform_Leads.PeierlsTransformLeads( Interface_Region );
1100  else %&& isempty( obj.Interface_Regions{idx}.Read('q') )
1101  obj.display(['EQuUs:Utils:', class(obj), 'CreateInterface: Applying gauge transformation in the Hamiltonians of interface region ', num2str(idx)])
1102  obj.PeierlsTransform_Leads.gaugeTransformationOnLead( Interface_Region, obj.gauge_field );
1103  end
1104  end
1105 
1106  Interface_Region.ApplyOverlapMatrices( obj.E );
1107 
1108  % method to adjust the interface region and coupling to the scattering region by an external function.
1109  if ~isempty( obj.interfacemodel )
1110  obj.interfacemodel( Interface_Region );
1111  end
1112 
1113  % The regularization of the interface is performed according to the Leads
1114  Leads = obj.FL_handles.Read( 'Leads' );
1115  Lead = Leads{idx};
1116  Interface_Region.Calc_Effective_Hamiltonians( obj.E, 'Lead', Lead );
1117  end
1118 
1119 
1120 
1121 
1122 
1123 
1124 %% setHandlesForMagneticField
1125 %> @brief Sets the function handles of the vector potential and gauge transformation.
1126 %> @param varargin Cell array of optional parameters (https://www.mathworks.com/help/matlab/ref/varargin.html):
1127 %> @param 'scatter' Function handle A = f( x,y) of the vector potential to be used in the scattering region (A is a N x 2 vector, where N is the number of the points given by the x and y coordinates.)
1128 %> @param 'lead' Function handle A = f( x,y) of the vector potential to be used in the leads. (A is a N x 2 vector, where N is the number of the points given by the x and y coordinates.)
1129 %> @param 'gauge_field' Function handle S = f( x,y) of the gauge transformation. (S is a N x 1 vector, where N is the number of the points given by the x and y coordinates.)
1130  function setHandlesForMagneticField( obj, varargin )
1131 
1132  p = inputParser;
1133  p.addParameter('scatter', [] );
1134  p.addParameter('lead', [] );
1135  p.addParameter('gauge_field', [] );
1136 
1137  p.parse(varargin{:});
1138 
1139 
1140  hscatter = p.Results.scatter;
1141  hlead = p.Results.lead;
1142  obj.gauge_field = p.Results.gauge_field;
1143 
1144 
1145  obj.display(['EQuUs:Utils:', class(obj), ':setHandlesForMagneticField: Adding handles of the magnetic field to the scattering region'])
1146  if obj.Opt.magnetic_field && isempty( obj.PeierlsTransform_Scatter )
1147  % setting the vector potential for the scattering region
1148  obj.PeierlsTransform_Scatter = Peierls(obj.Opt, 'Vectorpotential', hscatter);
1149  elseif ~isempty( obj.PeierlsTransform_Scatter ) && ~isempty(hscatter)
1150  % setting the vector potential for the scattering region if the Peierls class was already constructed
1151  obj.PeierlsTransform_Scatter.setVectorPotential( hscatter );
1152  end
1153 
1154  if obj.Opt.magnetic_field && isempty( obj.PeierlsTransform_Leads )
1155  % setting the vector potential for the leads
1156  obj.PeierlsTransform_Leads = Peierls(obj.Opt, 'Vectorpotential', hlead);
1157  elseif ~isempty( obj.PeierlsTransform_Leads ) && ~isempty(hlead)
1158  % setting the vector potential for the leads if the Peierls class was already constructed
1159  obj.PeierlsTransform_Leads.setVectorPotential( hlead );
1160  end
1161 
1162  end
1163 
1164 
1165 
1166 %% CreateClone
1167 %> @brief Creates a clone of the present object.
1168 %> @return Returns with the cloned object.
1169  function ret = CreateClone( obj )
1170 
1171  % cerating new instance of class NTerminal
1172  ret = NTerminal( ...
1173  'filenameIn', obj.filenameIn, ...
1174  'filenameOut', obj.filenameOut, ...
1175  'E', obj.E, ...
1176  'EF', obj.EF, ...
1177  'phi', obj.phi, ...
1178  'silent', obj.silent, ...
1179  'Opt', obj.Opt, ...
1180  'param', obj.param, ...
1181  'q', obj.q, ...
1182  'leadmodel', obj.leadmodel, ...
1183  'interfacemodel', obj.interfacemodel );
1184 
1185  %> cloning the individual attributes
1186  ret.CreateH = obj.CreateH.CreateClone();
1187  ret.FL_handles = obj.FL_handles.CreateClone();
1188  ret.Interface_Regions = cell(size(obj.Interface_Regions));
1189  for idx = 1:length(obj.Interface_Regions)
1190  ret.Interface_Regions{idx} = obj.Interface_Regions{idx}.CreateClone();
1191  end
1192  if ~isempty( obj.PeierlsTransform_Scatter )
1193  ret.PeierlsTransform_Scatter = obj.PeierlsTransform_Scatter.CreateClone();
1194  end
1195 
1196  if ~isempty( obj.PeierlsTransform_Leads )
1197  ret.PeierlsTransform_Leads = obj.PeierlsTransform_Leads.CreateClone();
1198  end
1199 
1200  %> setting the gauge field
1201  ret.gauge_field = obj.gauge_field; % function handle for the scalar field to transform the vector potential from Landauy to Landaux
1202 
1203  end
1204 
1205 
1206 
1207 %% setParam
1208 %> @brief Sets the structure #param in the attributes.
1209 %> @param param An instance of structure #param.
1210  function setParam(obj, param)
1211  obj.param = param;
1212 
1213  if ~isempty( obj.CreateH )
1214  obj.CreateH.Write('param', param);
1215  end
1216 
1217  if ~isempty( obj.FL_handles )
1218  obj.FL_handles.Write('param', param);
1219  end
1220 
1221  if ~isempty( obj.cCustom_Hamiltonians )
1222  obj.cCustom_Hamiltonians.Write('param', param);
1223  end
1224 
1225  for idx = 1:length( obj.Interface_Regions )
1226  obj.Interface_Regions{idx}.Write('param', param);
1227  end
1228 
1229  end
1230 
1231 %% getParam
1232 %> @brief Retrives a copy of the structure #param used in the current calculations.
1233 %> @return param An instance of structure #param.
1234  function ret = getParam(obj)
1235  ret = obj.param;
1236  end
1237 
1238 %% getTransverseMomentum
1239 %> @brief Retrives the value of the transverse momentum quantum number.
1240 %> @return q The transverse momentum quantum number.
1241  function ret = getTransverseMomentum(obj)
1242  ret = obj.q;
1243  end
1244 
1245 
1246 %% ApplyPotentialInScatter
1247 %> @brief Applies the potential in the scattering region
1248 %> @param CreateH An instance of class #CreateHamiltonians containing the Hamiltonian of the scattering center.
1249 %> @param scatterPotential A function handle pot=f( #Coordinates ) or pot=f( #CreateHamiltonians, Energy) for the potential to be applied in the Hamiltonian (used when FiniteGreensFunctionFromHamiltonian=true).
1250  function ApplyPotentialInScatter( obj, CreateH, scatterPotential )
1251 
1252 
1253  if nargin( scatterPotential ) == 1
1254  %> calculating the potential if the scattering potential has one input arguments
1255  %> obtaining coordinates of the scattering region
1256  coordinates = CreateH.Read('coordinates');
1257  %> calculating the potential from the coordinates
1258  potential = scatterPotential( coordinates );
1259  elseif nargin( scatterPotential ) == 2
1260  %> calculating the potential if the scattering potential has two input arguments
1261  potential = scatterPotential( CreateH, obj.E );
1262  %> obtaining coordinates of the scattering region that might have been changed inside the scatterPotential function
1263  coordinates = CreateH.Read('coordinates'); % coordinates might be changed in function scatterPotential
1264  else
1265  error('EQuUs:Ribbon:ApplyPotentialInScatter', 'To many input arguments in function handle scatterPotential');
1266  end
1267 
1268  % obtaining the scattering Hamiltonian
1269  Hscatter = CreateH.Read('Hscatter');
1270 
1271  if isvector(potential) && length(potential) == size(Hscatter,1)
1272  % applying potential in case of a diagonal on-site potential
1273 
1274  % transforming the potential for the case of the BdG model.
1275  if isprop(coordinates, 'BdG_u')
1276  potential(~coordinates.BdG_u) = -potential(~coordinates.BdG_u);
1277  end
1278 
1279  %creating diagonal sparse matrix from the potential
1280  potential = sparse(1:size(Hscatter,1), 1:size(Hscatter,1), potential, size(Hscatter,1), size(Hscatter,1));
1281 
1282  elseif length(size(potential)) == 2 && norm( size(potential)-size(Hscatter) ) == 0
1283  % applying potential in case, when the potential is given in a matrix form
1284 
1285  % transforming the potential for the case of the BdG model.
1286  if isprop(coordinates, 'BdG_u')
1287  potential(~coordinates.BdG_u, ~coordinates.BdG_u) = -potential(~coordinates.BdG_u, ~coordinates.BdG_u);
1288  end
1289  else
1290  error(['EQuUs:utils:', class(obj), ':ApplyPotentialInScatter'], 'Wrong output format of the function handle scatterPotential');
1291  end
1292 
1293 
1294  % Ensure not to overload the memory
1295  if issparse(Hscatter) && ~issparse(potential)
1296  error(['EQuUs:utils:', class(obj), ':ApplyPotentialInScatter'], 'If the Hamiltonian is sparse, potential should also be sparse');
1297  end
1298 
1299  % adding potential to the scattering region
1300  Hscatter = Hscatter + potential;
1301 
1302  % save the Hamiltonain
1303  CreateH.Write('Hscatter', Hscatter);
1304 
1305  end
1306 
1307 
1308 end %methods public
1309 
1310 methods ( Access = protected )
1311 
1312 %% CreateNTerminalHamiltonians
1313 %> @brief Extracts the Hamiltonians from the external source.
1314  function CreateNTerminalHamiltonians( obj )
1315 
1316  % Creating attribute Custom_Hamiltonian providing Hamiltonians from external source
1317  if ~strcmpi( class(obj.cCustom_Hamiltonians), 'Custom_Hamiltonian' )
1318  obj.cCustom_Hamiltonians = Custom_Hamiltonians( obj.Opt, obj.param, 'EF', obj.EF, 'CustomHamiltoniansHandle', obj.CustomHamiltoniansHandle );
1319  end
1320 
1321  % load Hamiltonians from the external source
1322  if ~obj.cCustom_Hamiltonians.Read( 'Hamiltonians_loaded' )
1323  obj.cCustom_Hamiltonians.LoadHamiltonians( 'WorkingDir', obj.WorkingDir );
1324  end
1325 
1326  % cerating the Hamiltonain for the scattering region
1327  obj.CreateScatter();
1328  end
1329 
1330 
1331 %% CreateHandles
1332 %> @brief Initializes the attributes of the class.
1333  function CreateHandles( obj )
1334 
1335  % creating classes for managing the magnetic field
1336  obj.setHandlesForMagneticField();
1337 
1338  % create class storing the Hamiltonian of the scattering region
1339  obj.CreateH = CreateHamiltonians(obj.Opt, obj.param, 'q', obj.q);
1340 
1341  % create class for transport calculations
1342  obj.FL_handles = Transport_Interface(obj.E, obj.Opt, obj.param, 'CreateH', obj.CreateH, 'PeierlsTransform', obj.PeierlsTransform_Leads );
1343 
1344  % read out structure Opt containing the computational parameters
1345  obj.Opt = obj.FL_handles.Read( 'Opt' );
1346 
1347  % creating classes of the interface regions
1348  obj.Interface_Regions = cell(length(obj.param.Leads),1);
1349  for idx = 1:length(obj.Interface_Regions)
1350  Lead_Orientation = obj.param.Leads{idx}.Lead_Orientation;
1351  obj.Interface_Regions{idx} = InterfaceRegion(obj.Opt, obj.param, 'Hanyadik_Lead', idx, 'q', obj.q, 'Lead_Orientation', Lead_Orientation);
1352  end
1353 
1354  end
1355 
1356 
1357 end % protected methods
1358 
1359 methods (Access=protected)
1360 
1361 
1362 %% InputParsing
1363 %> @brief Parses the optional parameters for the class constructor.
1364 %> @param varargin Cell array of optional parameters (https://www.mathworks.com/help/matlab/ref/varargin.html):
1365 %> @param 'filenameIn' The input filename containing the computational parameters. (Use parameters 'Op' and 'param' instead)
1366 %> @param 'filenameOut' The output filename to export the computational parameters.
1367 %> @param 'WorkingDir' The absolute path to the working directoy.
1368 %> @param 'CustomHamiltoniansHandle' function handle for the custom Hamiltonians. Has the same inputs as #Custom_Hamiltonians.LoadHamiltonians and output values defined by the example #Hamiltonians.
1369 %> @param 'E' The energy value used in the calculations (in the same units as the Hamiltonian).
1370 %> @param 'EF' The Fermi energy in the same units as the Hamiltonian. Attribute #E is measured from this value. (Use for equilibrium calculations in the zero temperature limit. Overrides the one comming from the external source)
1371 %> @param 'silent' Set true to suppress output messages.
1372 %> @param 'leadmodel' A function handle #Lead=f( idx, E, varargin ) of the alternative lead model with equivalent inputs and return values as #Transport_Interface.SurfaceGreenFunctionCalculator and with E standing for the energy.
1373 %> @param 'interfacemodel' A function handle f( #InterfaceRegion ) to manually adjus the interface regions. (Usefull when 'leadmodel' is also given. For example see @InterfaceModel)
1374 %> @param 'Opt' An instance of the structure #Opt.
1375 %> @param 'param' An instance of the structure #param.
1376 %> @param 'q' The transverse momentum quantum number.
1377  function InputParsing( obj, varargin)
1378 
1379  p = inputParser;
1380  p.addParameter('filenameIn', obj.filenameIn, @ischar);
1381  p.addParameter('filenameOut', obj.filenameOut, @ischar);
1382  p.addParameter('WorkingDir', obj.WorkingDir, @ischar);
1383  p.addParameter('CustomHamiltoniansHandle', obj.CustomHamiltoniansHandle); %function handle for the custom Hamiltonians
1384  p.addParameter('E', obj.E, @isscalar);
1385  p.addParameter('EF', obj.EF);
1386  p.addParameter('silent', obj.silent);
1387  p.addParameter('leadmodel', obj.leadmodel); %individual physical model for the contacts
1388  p.addParameter('interfacemodel', obj.interfacemodel); %individual physical model for the interface regions
1389  p.addParameter('Opt', obj.Opt);
1390  p.addParameter('param', obj.param);
1391  p.addParameter('q', obj.q);
1392 
1393  p.parse(varargin{:});
1394 
1395 
1396  obj.filenameIn = p.Results.filenameIn;
1397  obj.filenameOut = p.Results.filenameOut;
1398  obj.WorkingDir = p.Results.WorkingDir;
1399  obj.CustomHamiltoniansHandle = p.Results.CustomHamiltoniansHandle;
1400  obj.E = p.Results.E;
1401  obj.EF = p.Results.EF;
1402  obj.silent = p.Results.silent;
1403  obj.leadmodel = p.Results.leadmodel;
1404  obj.interfacemodel = p.Results.interfacemodel;
1405  obj.q = p.Results.q;
1406  obj.Opt = p.Results.Opt;
1407  obj.param = p.Results.param;
1408 
1409 
1410  if isempty(obj.Opt) || isempty(obj.param)
1411  [ obj.Opt, obj.param ] = parseInput( obj.filenameIn );
1412  end
1413 
1414  end
1415 
1416 end % methods private
1417 
1418 end
A class describing an N-terminal geometry for equilibrium calculations mostly in the zero temperature...
Definition: NTerminal.m:38
function LoadHamiltonians(varargin)
Obtain the Hamiltonians from the external source.
A class containing methodes for displaying several standard messages.
Definition: Messages.m:24
function Write(MemberName, input)
Sets the value of an attribute in the class.
Structure Opt contains the basic computational parameters used in EQuUs.
Definition: structures.m:60
Property gauge
String containing the name of the built-in gauge ('LandauX', 'LandauY').
Definition: Peierls.m:31
Class to create and store Hamiltonian of the translational invariant leads.
A class for calculations on a ribbon of finite width for equilibrium calculations mostly in the zero ...
Definition: Ribbon.m:34
Property H1
The coupling Hamiltonian between the unit cells.
sites Interface
Structure sites describing the geometry of the interface regions.
Definition: structures.m:182
function Transport(Energy, B)
Calculates the conductance at a given energy value.
A class to evaluate the Dyson equation and to calculate the scattering matrix for equilibrium process...
function Hamiltonians(varargin)
Function to create the custom Hamiltonians for the 1D chain.
function CreateScatterH(varargin)
Creates a Hamiltonian of a rectangle shaped area.
A class providing function handle to reduce the number of sites in the Hamiltonian via decimation pro...
Definition: Decimation.m:29
function createOutput(filename, Opt, param)
This function creates an output file containing the running parameters.
function CreateHamiltonians(Opt, param, varargin)
Constructor of the class.
Property q
A transverse momentum.
kulso_szabfokok
An array containing the site indexes connected to other parts.
Definition: structures.m:193
A class to import custom Hamiltonians provided by other codes or created manually
A class containing common basic functionalities.
function Clear(MemberName)
Clears the value of an attribute in the class.
Property Hcoupling
Coupling Hamiltonian from the interface region to the scattering region.
A class describing the interface region between the scattering region and a lead.
A class to calculate the Green functions and self energies of a translational invariant lead The nota...
Definition: Lead.m:29
Structure param contains data structures describing the physical parameters of the scattering center ...
Definition: structures.m:45
Property Lead_Orientation
The orientation of the lead. Set +1 is the "incoming" direction of the propagating states is defined ...
site_indexes
An array containing the site indexes of the given system part.
Definition: structures.m:191
Structure sites contains data to identify the individual sites in a matrix.
Definition: structures.m:187
sites Leads
Structure sites describing the geometry of the leads.
Definition: structures.m:178
A class responsible for the Peierls and gauge transformations.
Definition: Peierls.m:24
function gauge_field(x, y, eta_B, Aconst, height, lattice_constant)
Scalar gauge field connecting Landaux and Landauy gauges.
coordinates
An instance of structure coordinates describing the geometry.
Definition: structures.m:189
sites Scatter
Structure sites describing the geometry of the scattering region.
Definition: structures.m:180
Structure containing the coordinates and other quantum number identifiers of the sites in the Hamilto...
Definition: Coordinates.m:24
function Read(MemberName)
Query for the value of an attribute in the class.
function structures(name)
Structure junction_sites contains data to identify the individual sites of the leads,...
Definition: structures.m:176
A class to create and store Hamiltonian of the scattering region.