SpinGlassSimulations added (and removed junk)
This commit is contained in:
BIN
SpinGlassSimulations/make spinglass/Debug/DF60.PDB
Executable file
BIN
SpinGlassSimulations/make spinglass/Debug/DF60.PDB
Executable file
Binary file not shown.
BIN
SpinGlassSimulations/make spinglass/Debug/Zero Temperature.obj
Executable file
BIN
SpinGlassSimulations/make spinglass/Debug/Zero Temperature.obj
Executable file
Binary file not shown.
BIN
SpinGlassSimulations/make spinglass/Debug/make spinglass.pdb
Executable file
BIN
SpinGlassSimulations/make spinglass/Debug/make spinglass.pdb
Executable file
Binary file not shown.
BIN
SpinGlassSimulations/make spinglass/Release/Zero Temperature.obj
Executable file
BIN
SpinGlassSimulations/make spinglass/Release/Zero Temperature.obj
Executable file
Binary file not shown.
BIN
SpinGlassSimulations/make spinglass/Release/field_simulation.obj
Executable file
BIN
SpinGlassSimulations/make spinglass/Release/field_simulation.obj
Executable file
Binary file not shown.
385
SpinGlassSimulations/make spinglass/Zero Temperature.f90
Executable file
385
SpinGlassSimulations/make spinglass/Zero Temperature.f90
Executable file
@ -0,0 +1,385 @@
|
||||
! Program to simulate thin film spinglasses.
|
||||
!
|
||||
! Ge Nieuwenhuys, June, 2002, Written as Ising Metropolis program
|
||||
! October 2005, Rewritten as Heisenberg Zero-Temperature
|
||||
! October 17, 2005 Bug in direct access file "removes" by
|
||||
! oversizing the recordlength
|
||||
!
|
||||
! October 12: periodic boundary conditions in y- z plane
|
||||
! October 14: random number start randomly (based on clock) for
|
||||
! batch calculations.
|
||||
! October 14: output-file-names are automatically indexed.
|
||||
!
|
||||
! Spins are located on a fcc lattice
|
||||
!
|
||||
! nspin number of spins
|
||||
! nsp number of spins asked
|
||||
! d thickness
|
||||
! a lattice constant
|
||||
! ah half of lattice constant
|
||||
!
|
||||
Use DFPORT ! library only needed for obtaining CPU-time
|
||||
Use DFLIB
|
||||
!
|
||||
parameter ( max_spins = 100000 )
|
||||
!
|
||||
structure /spin/
|
||||
integer*4 x,y,z
|
||||
real*8 c(3)
|
||||
end structure
|
||||
!
|
||||
structure /inter/
|
||||
integer si
|
||||
real*8 val
|
||||
end structure
|
||||
!
|
||||
integer*4 j,k,l,m,n, nsp, nspin, nat, steps_per_spin, mh, ix, iy, iz
|
||||
integer*4 l_calc, ifile, iseed
|
||||
record /spin/ s(max_spins)
|
||||
record /inter/ i(100,max_spins)
|
||||
real*8 d, concentration, c, dd(max_spins), rkky, norm, p(3), k_F
|
||||
real*8 b_ext(3), b_ext_K(3), moment, T_glass, mag(3)
|
||||
character*1 answer
|
||||
character*80 calculation, line
|
||||
logical open_inp
|
||||
character*8 dddd, tttt, zone
|
||||
character*4 file_index
|
||||
integer dt(8)
|
||||
real*4 runtime(2), start_time, end_time
|
||||
!
|
||||
! initialization
|
||||
!
|
||||
val = 0
|
||||
a = .407 ! nm, lattice parameter for Au
|
||||
k_F = 12.0 ! 1/nm, Fermi wavevector for Au
|
||||
moment = 2.2 ! mu_B, moment of the impurity spins
|
||||
b_ext(1) = 0.01
|
||||
b_ext(2) = 0.0
|
||||
b_ext(3) = 0.0 ! extrenal field of 100 gauss in x-direction
|
||||
T_glass = 15.0 ! glass_temperature in Kelvin
|
||||
ah = a / 2.0
|
||||
iseed = 1234567
|
||||
!
|
||||
Write(6,*) '-----------------------------------------------------'
|
||||
Write(6,*) '| SPIN-GLASS GROUNDSTATE SIMULATION |'
|
||||
Write(6,*) '| Version October 17, 2005 |'
|
||||
Write(6,*) '| |'
|
||||
Write(6,*) '| This program simulates a spin-glass groundstate |'
|
||||
Write(6,*) '| using the method as described by |'
|
||||
Write(6,*) '| Walstedt and Walker, Phys. Rev. B22 (1980) 3816 |'
|
||||
Write(6,*) '| |'
|
||||
Write(6,*) '| The program can be used in batch mode by |'
|
||||
Write(6,*) '| supplying the name of the calculation |'
|
||||
Write(6,*) '| (Enter will start the online mode) |'
|
||||
Write(6,*) '| |'
|
||||
Write(6,*) '| In de batch-mode the parameters will be read from |'
|
||||
Write(6,*) '| <calculation>.inp |'
|
||||
Write(6,*) '| A comment on the first line and then on |'
|
||||
Write(6,*) '| each line of this file |'
|
||||
Write(6,*) '| number of spins, |'
|
||||
Write(6,*) '| thickness of sample [nm], |'
|
||||
Write(6,*) '| lattice parameter [nm], |'
|
||||
Write(6,*) '| Fermi wave number [nm^-1] |'
|
||||
Write(6,*) '| concentration of spins [at.%], |'
|
||||
Write(6,*) '| glass temperature [K], |'
|
||||
Write(6,*) '| magnetic moment [mu_B], |'
|
||||
Write(6,*) '| external magnetic field (3 components) [tesla] |'
|
||||
Write(6,*) '| number of iterations |'
|
||||
Write(6,*) '| |'
|
||||
Write(6,*) '| <calculation> can be entered as a |'
|
||||
Write(6,*) '| commandline parameter |'
|
||||
Write(6,*) '-----------------------------------------------------'
|
||||
!
|
||||
! Ask name of calculation (and read if in batch mode )
|
||||
!
|
||||
!
|
||||
! files :
|
||||
!
|
||||
open(9,file='u:\simulations\counter.his',status='old')
|
||||
read(9,*) ifile ! initialize outputfile counter
|
||||
!
|
||||
IF ( iargc() .GT. 0 ) THEN
|
||||
call getarg(1, calculation)
|
||||
Write(6,*) ' Calculation taken from commandline > ',calculation
|
||||
ELSE
|
||||
777 write(6,778)
|
||||
778 format(' '/' Give name of the calculation > ', \)
|
||||
read(5,'(a80)') calculation
|
||||
END IF
|
||||
!
|
||||
IF ( calculation(1:1) .NE. ' ' ) THEN
|
||||
l_calc = index( calculation, ' ') - 1
|
||||
open(1,file=calculation(1:l_calc)//'.inp', status='old', action='read', err=777)
|
||||
open(2,file=calculation(1:l_calc)//'.out', status='unknown', action='write')
|
||||
END IF
|
||||
!
|
||||
inquire(1,opened=open_inp)
|
||||
IF (open_inp) read(1,'(a80)') comment
|
||||
!
|
||||
open(9,file='u:\simulations\counter.sgl',status='old')
|
||||
read(9,*) ifile
|
||||
!
|
||||
888 IF (open_inp) THEN ! new calculation
|
||||
889 ifile = ifile + 1 ! increase outputfile number
|
||||
rewind(9)
|
||||
write(9,*) ifile ! store for next program
|
||||
write(file_index,'(''_'',i3)') ifile ! generate file_name
|
||||
DO j = 2, 4
|
||||
IF (file_index(j:j) .EQ. ' ' ) file_index(j:j) = '0'
|
||||
END DO
|
||||
!
|
||||
! Although the length of the record /spin/ is 3*4 + 3*8 = 36, the length had to be
|
||||
! set to 40, otherwise the writing went wrong (s.c(3) always, except for the last
|
||||
! equal to zero
|
||||
!
|
||||
open(3,file=calculation(1:l_calc)//file_index//'.sgl',status='unknown', &
|
||||
& access='direct',form='binary',recl=40)
|
||||
!
|
||||
890 read(1,'(a80)',end=999) line
|
||||
IF ( line(1:1) .EQ. '!' ) THEN
|
||||
write(6,'(a)') line
|
||||
GOTO 890
|
||||
ELSE
|
||||
read(line,*,err=998,end=999) nsp, d, a, k_F, concentration, &
|
||||
& T_glass, moment, b_ext, &
|
||||
& steps_per_spin
|
||||
END IF
|
||||
!
|
||||
! Initialize randomnumber generator "randomly"
|
||||
!
|
||||
call date_and_time( dddd, tttt, zone, dt )
|
||||
DO j = 1, dt(8) ! number milliseconds on the clock
|
||||
dummy = rand(iseed)
|
||||
END DO
|
||||
!
|
||||
ELSE
|
||||
!
|
||||
! Ask size of the system
|
||||
!
|
||||
1 write(6,2)
|
||||
2 format( ' How many spins ? '\)
|
||||
read(5,*,err=1) nsp
|
||||
IF ( nsp .LE. 0 ) STOP ' Programm terminated by operator '
|
||||
IF ( nsp .GT. max_spins ) GOTO 1
|
||||
!
|
||||
3 write(6,4)
|
||||
4 format( ' What thickness [nm] ? '\)
|
||||
read(5,*,err=3) d
|
||||
!
|
||||
5 write(6,6)
|
||||
6 format( ' Which concentration [at.%] ? '\)
|
||||
read(5,*,err=5) concentration
|
||||
|
||||
7 write(6,8)
|
||||
8 format(' Give the T_glass and the magnetic moment > '\)
|
||||
read(5,*,err=7) T_glass, moment
|
||||
END IF
|
||||
!
|
||||
! end of getting all parameters
|
||||
!
|
||||
c = concentration / 100
|
||||
!
|
||||
! Calculate the magnetic field energy in Kelvin
|
||||
!
|
||||
b_ext_K = moment * (0.927 / 1.38) * b_ext
|
||||
!
|
||||
start_time = dtime(runtime) ! record the starttime
|
||||
!
|
||||
! Calculate the 'rounded' number of spins for a lattice n*m*m for
|
||||
! the given concentration
|
||||
!
|
||||
n = floor( d / ah )
|
||||
nat = floor( nsp / c )
|
||||
m = floor( sqrt( 2.0 * float(nat) / float(n) ) )
|
||||
mh = m / 2
|
||||
nat = m * m * n / 2
|
||||
nspin = floor( nat * c )
|
||||
!
|
||||
write(6,*) ' n = ', n,' m = ', m
|
||||
write(6,*) ' nat = ', nat
|
||||
write(6,*) ' nspin = ', nspin
|
||||
!
|
||||
write(2,*) ' n = ', n,' m = ', m
|
||||
write(2,*) ' nat = ', nat
|
||||
write(2,*) ' nspin = ', nspin
|
||||
!
|
||||
! Place the spins on the lattice
|
||||
!
|
||||
nspin = 0
|
||||
DO j = 0, n-1
|
||||
DO k = 0, m-1
|
||||
DO l = 0, m-1
|
||||
IF ( mod(j+k+l,2) .EQ. 0 ) THEN
|
||||
IF ( ran(iseed) .LT. c ) THEN
|
||||
nspin = nspin + 1
|
||||
s(nspin).x = j
|
||||
s(nspin).y = k
|
||||
s(nspin).z = l
|
||||
END IF
|
||||
END IF
|
||||
END DO
|
||||
END DO
|
||||
END DO
|
||||
!
|
||||
! Calculate the 100 shortest distances
|
||||
!
|
||||
write(6,*) ' '
|
||||
write(6,*) ' '
|
||||
!
|
||||
DO j = 1, nspin
|
||||
write(6,9) j, char(13)
|
||||
9 format(' Considering spin ', i5, a1,\)
|
||||
DO k = 1, nspin
|
||||
IF ( k .EQ. j ) THEN
|
||||
dd(k) = 1e10
|
||||
ELSE
|
||||
ix = s(j).x - s(k).x
|
||||
iy = s(j).y - s(k).y
|
||||
IF ( iy .LT. -mh ) iy = iy + m ! periodic boundary along y-axis
|
||||
IF ( iy .GT. mh ) iy = iy - m
|
||||
iz = s(j).z - s(k).z
|
||||
IF ( iz .LT. -mh ) iz = iz + m ! periodic boundary along z-axis
|
||||
IF ( iz .GT. mh ) iz = iz - m
|
||||
dd(k) = (ix*ix + iy*iy + iz*iz)
|
||||
END IF
|
||||
END DO
|
||||
!
|
||||
DO ii = 1, 100
|
||||
dd_min = 1E+10
|
||||
DO k = 1, nspin
|
||||
IF ( dd(k) .LT. dd_min ) THEN
|
||||
l = k
|
||||
dd_min = dd(k)
|
||||
END IF
|
||||
END DO
|
||||
i(ii,j).si = l
|
||||
i(ii,j).val = ah * sqrt(dd(l))
|
||||
dd(l) = 1e10
|
||||
END DO
|
||||
!
|
||||
! translate distance into interaction strength
|
||||
!
|
||||
DO ii = 1, 100
|
||||
i(ii,j).val = rkky( i(ii,j).val, k_F, T_glass )
|
||||
END DO
|
||||
!
|
||||
END DO
|
||||
!
|
||||
end_time = dtime(runtime)
|
||||
write(6,*) ' Finally, nspin = ', nspin,' in ', end_time - start_time,' seconds '
|
||||
write(2,*) ' Finally, nspin = ', nspin,' in ', end_time - start_time,' seconds '
|
||||
!
|
||||
! Initialize the spins
|
||||
!
|
||||
start_time = dtime(runtime)
|
||||
!
|
||||
DO j = 1, nspin
|
||||
DO k = 1, 3
|
||||
s(j).c(k) = 2.0*ran(iseed) - 1.0
|
||||
END DO
|
||||
norm = sqrt( sum( s(j).c * s(j).c ) )
|
||||
s(j).c = s(j).c / norm
|
||||
END DO
|
||||
!
|
||||
! Calculated the energy and magnetization
|
||||
!
|
||||
97 e = 0.0
|
||||
mag = 0.0
|
||||
!
|
||||
DO j = 1, nspin
|
||||
p = 0.0
|
||||
DO ii = 1, 100
|
||||
p = p + i(ii,j).val * s(i(ii,j).si).c
|
||||
END DO
|
||||
e = e + sum( p * s(j).c ) + sum( b_ext_K * s(j).c )
|
||||
mag = mag + s(j).c
|
||||
END DO
|
||||
!
|
||||
end_time = dtime(runtime)
|
||||
!
|
||||
Write(6,971) mag / float(nspin)
|
||||
Write(2,971) mag / float(nspin)
|
||||
971 format(' Magnetization = ',3F8.4)
|
||||
Write(6,972) e / float(nspin), end_time - start_time
|
||||
Write(2,972) e / float(nspin), end_time - start_time
|
||||
972 format( ' Energy = ', E14.4, ' after ', f8.2, ' seconds ' )
|
||||
!
|
||||
! Now start the serious running
|
||||
!
|
||||
91 IF ( .NOT. open_inp ) THEN
|
||||
98 write(6,99)
|
||||
99 format(' Give the number of steps per spin [0: new glass] > '\)
|
||||
read(5,*,err=98) steps_per_spin
|
||||
IF ( steps_per_spin .LE. 0 ) GOTO 777
|
||||
END IF
|
||||
!
|
||||
start_time = dtime(runtime) ! record the starttime
|
||||
write(6,*) ' '
|
||||
Write(6,*) ' ' ! to make space for the hashes
|
||||
!
|
||||
! Now comes the real hard work !!!!!!!!!!!
|
||||
!
|
||||
DO mon = 1, steps_per_spin
|
||||
DO j = 1, nspin
|
||||
e = 0.0
|
||||
p = 0.0
|
||||
DO ii = 1, 100
|
||||
p = p + i(ii,j).val * s(i(ii,j).si).c
|
||||
END DO
|
||||
p = p + b_ext_K
|
||||
norm = sqrt( sum( p * p ) )
|
||||
p = p / norm
|
||||
s(j).c = p
|
||||
END DO
|
||||
IF ( mod(mon,100) .EQ. 0 ) idummy = putc('#')
|
||||
END DO
|
||||
!
|
||||
876 write(6,*) ' '
|
||||
write(6,*) ' '
|
||||
write(3,rec=1) n,m,nspin,a,moment,T_glass
|
||||
write(3,rec=2) concentration,b_ext,steps_per_spin
|
||||
DO ispin = 1, nspin
|
||||
write(3,rec=ispin+2) s(ispin)
|
||||
END DO
|
||||
close(3)
|
||||
!
|
||||
IF ( open_inp ) THEN
|
||||
DO j = 1, nspin
|
||||
p = 0.0
|
||||
DO ii = 1, 100
|
||||
p = p + i(ii,j).val * s(i(ii,j).si).c
|
||||
END DO
|
||||
e = e + sum( p * s(j).c ) + sum( b_ext_K * s(j).c )
|
||||
mag = mag + s(j).c
|
||||
END DO
|
||||
!
|
||||
end_time = dtime(runtime)
|
||||
!
|
||||
Write(6,971) mag / float(nspin)
|
||||
Write(2,971) mag / float(nspin)
|
||||
Write(6,972) e / float(nspin), end_time - start_time
|
||||
Write(2,972) e / float(nspin), end_time - start_time
|
||||
GOTO 888
|
||||
ELSE
|
||||
GOTO 97
|
||||
END IF
|
||||
!
|
||||
998 STOP 'ERROR IN INPUT FILE '
|
||||
!
|
||||
999 STOP 'stopped at end of input'
|
||||
!
|
||||
END
|
||||
!
|
||||
!
|
||||
REAL*8 function RKKY(x, k_F, T_glass)
|
||||
real*8 x, k_F, T_glass, xx
|
||||
!
|
||||
! calculates the RKKY interaction,
|
||||
! Te factor of one thousand makes takes care that the RKKY still only
|
||||
! has to be multiplied by the glass-temperature.
|
||||
!
|
||||
xx = 2.0 * k_F * x
|
||||
rkky = 1.0D+03 * T_glass * ( xx * cos(xx) - sin(xx) ) /(xx*xx*xx*xx)
|
||||
!
|
||||
RETURN
|
||||
END
|
108
SpinGlassSimulations/make spinglass/make spinglass.dsp
Executable file
108
SpinGlassSimulations/make spinglass/make spinglass.dsp
Executable file
@ -0,0 +1,108 @@
|
||||
# Microsoft Developer Studio Project File - Name="make spinglass" - Package Owner=<4>
|
||||
# Microsoft Developer Studio Generated Build File, Format Version 6.00
|
||||
# ** DO NOT EDIT **
|
||||
|
||||
# TARGTYPE "Win32 (x86) Console Application" 0x0103
|
||||
|
||||
CFG=make spinglass - Win32 Debug
|
||||
!MESSAGE This is not a valid makefile. To build this project using NMAKE,
|
||||
!MESSAGE use the Export Makefile command and run
|
||||
!MESSAGE
|
||||
!MESSAGE NMAKE /f "make spinglass.mak".
|
||||
!MESSAGE
|
||||
!MESSAGE You can specify a configuration when running NMAKE
|
||||
!MESSAGE by defining the macro CFG on the command line. For example:
|
||||
!MESSAGE
|
||||
!MESSAGE NMAKE /f "make spinglass.mak" CFG="make spinglass - Win32 Debug"
|
||||
!MESSAGE
|
||||
!MESSAGE Possible choices for configuration are:
|
||||
!MESSAGE
|
||||
!MESSAGE "make spinglass - Win32 Release" (based on "Win32 (x86) Console Application")
|
||||
!MESSAGE "make spinglass - Win32 Debug" (based on "Win32 (x86) Console Application")
|
||||
!MESSAGE
|
||||
|
||||
# Begin Project
|
||||
# PROP AllowPerConfigDependencies 0
|
||||
# PROP Scc_ProjName ""
|
||||
# PROP Scc_LocalPath ""
|
||||
CPP=cl.exe
|
||||
F90=df.exe
|
||||
RSC=rc.exe
|
||||
|
||||
!IF "$(CFG)" == "make spinglass - Win32 Release"
|
||||
|
||||
# PROP BASE Use_MFC 0
|
||||
# PROP BASE Use_Debug_Libraries 0
|
||||
# PROP BASE Output_Dir "Release"
|
||||
# PROP BASE Intermediate_Dir "Release"
|
||||
# PROP BASE Target_Dir ""
|
||||
# PROP Use_MFC 0
|
||||
# PROP Use_Debug_Libraries 0
|
||||
# PROP Output_Dir "Release"
|
||||
# PROP Intermediate_Dir "Release"
|
||||
# PROP Ignore_Export_Lib 0
|
||||
# PROP Target_Dir ""
|
||||
# ADD BASE F90 /compile_only /nologo /warn:nofileopt
|
||||
# ADD F90 /compile_only /nologo /warn:nofileopt
|
||||
# ADD BASE CPP /nologo /W3 /GX /O2 /D "WIN32" /D "NDEBUG" /D "_CONSOLE" /D "_MBCS" /YX /FD /c
|
||||
# ADD CPP /nologo /W3 /GX /O2 /D "WIN32" /D "NDEBUG" /D "_CONSOLE" /D "_MBCS" /YX /FD /c
|
||||
# ADD BASE RSC /l 0x409 /d "NDEBUG"
|
||||
# ADD RSC /l 0x409 /d "NDEBUG"
|
||||
BSC32=bscmake.exe
|
||||
# ADD BASE BSC32 /nologo
|
||||
# ADD BSC32 /nologo
|
||||
LINK32=link.exe
|
||||
# ADD BASE LINK32 kernel32.lib /nologo /subsystem:console /machine:I386
|
||||
# ADD LINK32 kernel32.lib /nologo /subsystem:console /machine:I386 /out:"Release/make_spinglass.exe"
|
||||
# SUBTRACT LINK32 /incremental:yes
|
||||
|
||||
!ELSEIF "$(CFG)" == "make spinglass - Win32 Debug"
|
||||
|
||||
# PROP BASE Use_MFC 0
|
||||
# PROP BASE Use_Debug_Libraries 1
|
||||
# PROP BASE Output_Dir "Debug"
|
||||
# PROP BASE Intermediate_Dir "Debug"
|
||||
# PROP BASE Target_Dir ""
|
||||
# PROP Use_MFC 0
|
||||
# PROP Use_Debug_Libraries 1
|
||||
# PROP Output_Dir "Debug"
|
||||
# PROP Intermediate_Dir "Debug"
|
||||
# PROP Ignore_Export_Lib 0
|
||||
# PROP Target_Dir ""
|
||||
# ADD BASE F90 /check:bounds /compile_only /debug:full /nologo /traceback /warn:argument_checking /warn:nofileopt
|
||||
# ADD F90 /check:bounds /compile_only /debug:full /nologo /traceback /warn:argument_checking /warn:nofileopt
|
||||
# ADD BASE CPP /nologo /W3 /Gm /GX /ZI /Od /D "WIN32" /D "_DEBUG" /D "_CONSOLE" /D "_MBCS" /YX /FD /GZ /c
|
||||
# ADD CPP /nologo /W3 /Gm /GX /ZI /Od /D "WIN32" /D "_DEBUG" /D "_CONSOLE" /D "_MBCS" /YX /FD /GZ /c
|
||||
# ADD BASE RSC /l 0x409 /d "_DEBUG"
|
||||
# ADD RSC /l 0x409 /d "_DEBUG"
|
||||
BSC32=bscmake.exe
|
||||
# ADD BASE BSC32 /nologo
|
||||
# ADD BSC32 /nologo
|
||||
LINK32=link.exe
|
||||
# ADD BASE LINK32 kernel32.lib /nologo /subsystem:console /debug /machine:I386 /pdbtype:sept
|
||||
# ADD LINK32 kernel32.lib /nologo /subsystem:console /incremental:no /debug /machine:I386 /out:"Debug/make_spinglass.exe" /pdbtype:sept
|
||||
|
||||
!ENDIF
|
||||
|
||||
# Begin Target
|
||||
|
||||
# Name "make spinglass - Win32 Release"
|
||||
# Name "make spinglass - Win32 Debug"
|
||||
# Begin Group "Source Files"
|
||||
|
||||
# PROP Default_Filter "cpp;c;cxx;rc;def;r;odl;idl;hpj;bat;f90;for;f;fpp"
|
||||
# Begin Source File
|
||||
|
||||
SOURCE=".\Zero Temperature.f90"
|
||||
# End Source File
|
||||
# End Group
|
||||
# Begin Group "Header Files"
|
||||
|
||||
# PROP Default_Filter "h;hpp;hxx;hm;inl;fi;fd"
|
||||
# End Group
|
||||
# Begin Group "Resource Files"
|
||||
|
||||
# PROP Default_Filter "ico;cur;bmp;dlg;rc2;rct;bin;rgs;gif;jpg;jpeg;jpe"
|
||||
# End Group
|
||||
# End Target
|
||||
# End Project
|
19
SpinGlassSimulations/make spinglass/make spinglass.plg
Executable file
19
SpinGlassSimulations/make spinglass/make spinglass.plg
Executable file
@ -0,0 +1,19 @@
|
||||
<html>
|
||||
<body>
|
||||
<pre>
|
||||
<h1>Build Log</h1>
|
||||
<h3>
|
||||
--------------------Configuration: make spinglass - Win32 Debug--------------------
|
||||
</h3>
|
||||
<h3>Command Lines</h3>
|
||||
Creating command line "link.exe kernel32.lib /nologo /subsystem:console /incremental:no /pdb:"Debug/make_spinglass.pdb" /debug /machine:I386 /out:"Debug/make_spinglass.exe" /pdbtype:sept ".\Debug\Zero Temperature.obj" "
|
||||
<h3>Output Window</h3>
|
||||
Linking...
|
||||
|
||||
|
||||
|
||||
<h3>Results</h3>
|
||||
make_spinglass.exe - 0 error(s), 0 warning(s)
|
||||
</pre>
|
||||
</body>
|
||||
</html>
|
Reference in New Issue
Block a user