Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models,...

24
Landau free energy density For large N we expect thermodynamic limit t=(T-T c )/T c (t=0 corresponds to the critical temperature Can think of this as averaging over many spins, ignoring spatial correlations/fluctuations …. like mean field theory

Transcript of Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models,...

Page 1: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Landau free energy density

For large N we expect thermodynamic limit t=(T-Tc)/Tc (t=0 corresponds to the critical temperature Can think of this as averaging over many spins, ignoring spatial correlations/fluctuations …. like mean field theory

Page 2: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Minima of the Landau free energy density

For H=0, t>0, we find η=0 For H=0, t<0, we find η=0, t=(T-Tc)/Tc (t=0 corresponds to the critical temperature)

Page 3: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Minimization using Metropolis Monte-Carlo….

Take H=0 and kBTc=1 (L in units of kBTc) Determine using Metropolis algorithm as a function of T What is the effect of changing N? Notice that T=Tc(t+1) a=1 and b=1 in definition of L

Page 4: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Coding it up… declarations

IMPLICIT NONE INTEGER, PARAMETER :: Prec14=SELECTED_REAL_KIND(14) INTEGER , PARAMETER :: mcmax=100000,N=1000,mcmin=mcmax/2 INTEGER :: mc,nt,ntot REAL(KIND=Prec14) :: l1,l2,eta,etalast,prob,rnd,bb,aa,t REAL(KIND=Prec14) :: etaaverage,etaanalytic REAL(KIND=Prec14), PARAMETER :: a=1,b=1,tsteps=100 REAL(KIND=Prec14), PARAMETER :: tmax=1.0d0,tmin=-1.0d0 REAL(KIND=Prec14), PARAMETER :: dtemp=(tmax-tmin)/tsteps REAL(KIND=Prec14), PARAMETER :: step=0.01d0 ! Parameters to go from Landau density to Landau free energy aa=a*N bb=b*N

Page 5: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Outermost “do” loop on reduced temperature t. etaaverage and ntot are for computing average value of the order parameter do nt=1,tsteps t=tmax-dtemp*(nt-1) etaaverage=0.0d0 ntot=0 Next “do” loop is over Monte-Carlo steps (random moves).. We need to take a random step and compute Landau energy before and after step do mc=1,mcmax ! save eta, take a random step etalast=eta call RANDOM_NUMBER(rnd) l1=aa*t*eta**2+0.5d0*bb*eta**4 eta=eta+step*(0.5d0-rnd) l2=aa*t*eta**2+0.5d0*bb*eta**4

Execution part…

Page 6: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Execution part… Metropolis MC algorithm…

if(l2.le.l1) then ! accept the step

If energy goes down, accept step…

If energy goes up, step accepted with some probability…

else ! accept with some probability call RANDOM_NUMBER(rnd) prob=dexp(-(l2-l1)/(1+t)) if(rnd.le.prob) ! Accept step

Page 7: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

if(mc.ge.mcmin) then etaaverage=etaaverage+eta ntot=ntot+1 endif

We need to accumulate data for each step, whether random move is accepted or not…

Here, mcmin is the minimum number of MC steps before we start to accumulate data… equilibration period

Accumulate data over MC steps for averages…

Page 8: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

l2=aa*t*etaaverage**2+0.5d0*bb*etaaverage**4 if(t.ge.0) etaanalytic=0.0d0 if(t.lt.0) etaanalytic=dsqrt(-(a*t/b)) write(6,100) t,etaaverage,etaanalytic,l2 100 format(f6.3,3f12.6)

Output results at each reduced temperature t, including average order parameter, expected value from minimum L, and the Landau free energy

Output results from MC simulation…

Page 9: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

What do we expect? For N=1000 ….

Page 10: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

What do we expect? For N=10 ….

Page 11: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Fluctuations… N=10, fluctuations are dominant

In the thermodynamic limit N--> infinity, η approaches values predicted by minimum of Landau free energy For a small N, fluctuations are important:

For example, for a small enough system, even for t<0 the system may periodically flip between + and - values of η As N--infinity, flips between + and - not possible below t=0… ergodicity breaking…

Page 12: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Spatially varying order parameter: Phase-field models

η --> η(r)

Gradient type term to treat domain-wall energy…and the Landau free energy functional is

“Coarse-grained” order parameter, which can be thought of as

Page 13: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Phase-field models, Monte Carlo approach

This shows us how to do Metropolis MC for the case of a spatially varying order parameter Random steps in (discretized) order parameter η(r) Accept/reject steps depending on Landau energy functional L[η(r)] Very general, can add along with continuity equation concentrations, describe mixing of elements, diffusion, and concomitant structural phase transitions In materials science the equations are called “Cahn-Hilliard” equations, can be studied computationally

Page 14: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Monte-Carlo for d=2 Ising model

The Hamiltonian is given by,

The Weiss theory in d=2 gives kBTc= 4J The exact relation from Onsager is kBTc= 2.2692J In project 4, we can come close to the exact result using Metroplis Monte Carlo I ran for a 100x100 spin lattice

Page 15: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Declarations

IMPLICIT NONE INTEGER, PARAMETER :: Prec14=SELECTED_REAL_KIND(14) INTEGER , PARAMETER :: mcmax=1000000,mcmin=mcmax/2 INTEGER, PARAMETER :: nn=50, ksteps=100 INTEGER, PARAMETER :: nx=nn,ny=nn INTEGER :: ix,iy INTEGER :: mc,kt,ktot REAL(KIND=Prec14) :: l1,en,en0,K,mag,lav,mav,rnd,prob REAL(KIND=Prec14), DIMENSION(nx,ny) :: S REAL(KIND=Prec14), PARAMETER :: kmax=2.0d0,kmin=1.0d0/3.0d0 REAL(KIND=Prec14), PARAMETER :: dk=(kmax-kmin)/ksteps

Direct Ising model code

Page 16: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Fortran functions

double precision function abs(x) double precision x if(x.lt.0.0d0) then

abs=-x else

abs=x endif return end

Using the function in your code: y=abs(x) ! Return the absolute value of x

In an intrinsic function, we can refer to the function and we don’t need code. But the code for a function might look like:

Page 17: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

In our code, we will use a function called energy to determine the change in energy due to flipping a spin double precision function energy(s0,s1,s2,s3,s4) INTEGER,PARAMETER ::Prec14=SELECTED_REAL_KIND(14) REAL(Kind=Prec14) :: s0,s1,s2,s3,s4 energy=2.0d0*s0*(s1+s2+s3+s4) return end The arguments of the function, s0 is the center spin, and s1,s2,s3,s4 are the four neighboring spins. This is a basically trivial use of functions in Fortran, but it teaches you to use them nonetheless.

Function energy

Page 18: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

etot=0.0d0 do ix=1,nx do iy=1,ny

s0=S(ix,iy) s1=S(ix+1,iy) ! Neighboring spin along +x …. etot=etot-0.25d0*energy(s0,s1,s2,s3,s4) enddo enddo

Initial energy

We can also use energy to find the total energy energy etot

Page 19: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Periodic boundary conditions

•  We have to be careful because if we just consider spins ix +/- 1 and iy +/- 1, we might go beyond the “boundaries” of our system

•  We need to implement periodic boundary conditions

•  For example in the last slide we might take s1=S(ix+1,iy)

•  However, if ix+1= nx+1, of the system in the x direction, we then take s1=S(1,iy)

Page 20: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Low to temperature

•  Start with an ordered array of spins

•  Work with parameter K=J/kBT

•  Start with K=kmax, do MC steps to compute properties

•  Decrease K in steps of dk

•  Decreasing K corresponds to increasing T

•  More spins will disorder as T increases

Page 21: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially
Page 22: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially

Monte-Carlo for d=2 Ising model

We showed, starting with the free-energy, that

Page 23: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially
Page 24: Landau free energy density - UCF Physicsschellin/teaching/phz5156_11/lecture6.pdfPhase-field models, Monte Carlo approach This shows us how to do Metropolis MC for the case of a spatially