Skip to content

Commit

Permalink
Newsysteminlib (#64)
Browse files Browse the repository at this point in the history
* Added NEWSYSTEM logical variable

* Adopted NEWSYSTEM variable coming from the hosting code

* Disabled test with lammps for the moment

* bug fix
  • Loading branch information
cnegre authored Jun 21, 2018
1 parent 9fcad96 commit b610fe9
Show file tree
Hide file tree
Showing 11 changed files with 41 additions and 27 deletions.
2 changes: 1 addition & 1 deletion .travis.yml
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ before_script:
env:
- OPTIONS="CVR=ON" TEST="" CHOICES=gfort.lapack
- OPTIONS="CVR=ON PROGRESS=ON" TEST="" CHOICES=gfort.lapack
- OPTIONS="CVR=ON MAKELIB=ON lammps" TEST="_lmp" CHOICES=gfort.lapack
# - OPTIONS="CVR=ON MAKELIB=ON lammps" TEST="_lmp" CHOICES=gfort.lapack
- LATTE_CMAKE=yes CMAKE_WITH_PROGRESS=yes
- LATTE_CMAKE=yes LAMMPS_CMAKE=yes

Expand Down
Binary file added Manual/refman.pdf
Binary file not shown.
2 changes: 1 addition & 1 deletion src/Doxyfile.in
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ PROJECT_NAME = LATTE
# could be handy for archiving the generated documentation or if some version
# control system is used.

PROJECT_NUMBER = 1.0
PROJECT_NUMBER = v1.2.0

# Using the PROJECT_BRIEF tag one can provide an optional one line description
# for a project that appears at the top of each page and should give viewer a
Expand Down
1 change: 1 addition & 0 deletions src/constants_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ MODULE CONSTANTS_MOD
INTEGER :: RSLEVEL
INTEGER :: RESTARTLIB
INTEGER :: FREEZE
INTEGER :: NEWSYSTEMLATTE
REAL(LATTEPREC) :: BOX(3,3), BOX_OLD(3,3), BOXDIMS(3)
REAL(LATTEPREC) :: BNDFIL, TOTNE
REAL(LATTEPREC) :: COVE, TOTE, ENTE, KEE, ECOUL, EREP, TRRHOH
Expand Down
1 change: 0 additions & 1 deletion src/deallocateall.f90
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,6 @@ SUBROUTINE DEALLOCATEALL
USE PUREARRAY
USE VIRIALARRAY


IMPLICIT NONE
IF (EXISTERROR) RETURN

Expand Down
6 changes: 5 additions & 1 deletion src/diagmyh.f90
Original file line number Diff line number Diff line change
Expand Up @@ -48,8 +48,11 @@ SUBROUTINE DIAGMYH()
#ifdef XSYEV

#ifdef DOUBLEPREC


CALL DSYEV(JOBZ, UPLO, HDIM, EVECS, HDIM, EVALS, &
DIAG_WORK, DIAG_LWORK,INFO)

#elif defined(SINGLEPREC)

! ALLOCATE(TMPHMAT(HDIM, HDIM), TMPEVALS(HDIM), DWORK(3*HDIM - 1))
Expand Down Expand Up @@ -77,7 +80,7 @@ SUBROUTINE DIAGMYH()
DIAG_WORK, DIAG_LWORK, DIAG_IWORK, DIAG_LIWORK, INFO)
#endif

#endif
#endif


ELSE
Expand Down Expand Up @@ -130,6 +133,7 @@ SUBROUTINE DIAGMYH()

ENDIF


RETURN

END SUBROUTINE DIAGMYH
3 changes: 2 additions & 1 deletion src/getrho.f90
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,7 @@ SUBROUTINE GETRHO(MDITER)
ENDIF
#else
CALL DIAGMYH()

IF (SPINON .EQ. 0) THEN
CALL BOEVECS()
ELSE
Expand Down Expand Up @@ -80,7 +81,7 @@ SUBROUTINE GETRHO(MDITER)
#ifdef PROGRESSON

CALL SP2PRG

#else

IF (MDITER .LE. 10) THEN
Expand Down
14 changes: 8 additions & 6 deletions src/latte_c_bind.f90
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,8 @@
!! \param VEL Velocities passed to latte.
!! \param DT integration step passed to latte.
!! \param DT integration step passed to latte.
!! \param VIRIALINOUT Components of the second virial coefficient
!! \param VIRIAL_INOUT Components of the second virial coefficient
!! \param NEWSYSTEM Tells LATTE if a new system is passed.
!! \param EXISTERROR Returns an error flag (.true.) to the hosting code.
!!
!! \brief This routine will be used load call latte_lib from a C/C++ program:
Expand All @@ -58,9 +59,9 @@
!! \brief Note: All units are LATTE units by default.
!! See https://github.com/losalamos/LATTE/blob/master/Manual/LATTE_manual.pdf
!!
SUBROUTINE LATTE_C_BIND (FLAGS,NATS,COORDS,TYPES,NTYPES,MASSES,XLO &
,XHI,XY,XZ,YZ,FORCES,MAXITER,VENERG, &
VEL,DT,VIRIALINOUT,EXISTERROR) BIND (C, NAME="latte")
SUBROUTINE LATTE_C_BIND (FLAGS, NATS, COORDS, TYPES, NTYPES, MASSES, XLO &
, XHI, XY, XZ, YZ, FORCES, MAXITER, VENERG, &
VEL, DT, VIRIAL_INOUT, NEWSYSTEM, EXISTERROR) BIND (C, NAME="latte")

USE ISO_C_BINDING, ONLY: C_CHAR, C_NULL_CHAR, C_DOUBLE, C_INT, C_BOOL
USE LATTE_LIB
Expand All @@ -73,11 +74,12 @@ SUBROUTINE LATTE_C_BIND (FLAGS,NATS,COORDS,TYPES,NTYPES,MASSES,XLO &
REAL(C_DOUBLE) :: XLO(3), EKIN, VENERG, DT
REAL(C_DOUBLE) :: XY, XZ, YZ
REAL(C_DOUBLE), INTENT(INOUT) :: FORCES(3, NATS), VEL(3, NATS)
REAL(C_DOUBLE), INTENT(INOUT) :: VIRIALINOUT(6)
REAL(C_DOUBLE), INTENT(INOUT) :: VIRIAL_INOUT(6)
LOGICAL(C_BOOL) :: EXISTERROR
INTEGER(C_INT), INTENT(INOUT) :: NEWSYSTEM

CALL LATTE(NTYPES, TYPES, COORDS, MASSES, XLO, XHI, XY, XZ, YZ, FORCES, &
MAXITER, VENERG, VEL, DT, VIRIALINOUT, EXISTERROR)
MAXITER, VENERG, VEL, DT, VIRIAL_INOUT, NEWSYSTEM, EXISTERROR)

RETURN

Expand Down
28 changes: 16 additions & 12 deletions src/latte_lib.f90
Original file line number Diff line number Diff line change
Expand Up @@ -88,8 +88,9 @@ MODULE LATTE_LIB
!! \param VENERG This is the potential Energy that is given back from latte to the hosting code.
!! \param VEL Velocities passed to latte.
!! \param DT integration step passed to latte.
!! \param VIRIALINOUT Components of the second virial coefficient
!! \param EXISTERROR Returns an error flag (.true.) to the hosting code.
!! \param VIRIAL_INOUT Components of the second virial coefficient.
!! \param NEWSYSTEM Tells LATTE if a new system is passed.
!! \param EXISTERROR_INOUT Returns an error flag (.true.) to the hosting code.
!!
!! \brief This routine will be used load call latte_lib from a C/C++ program:
!!
Expand All @@ -105,8 +106,8 @@ MODULE LATTE_LIB
!!
!! \brief Note: All units are LATTE units by default. See https://github.com/losalamos/LATTE/blob/master/Manual/LATTE_manual.pdf
!!
SUBROUTINE LATTE(NTYPES,TYPES,CR_IN,MASSES_IN,XLO,XHI,XY,XZ,YZ,FTOT_OUT, &
MAXITER_IN, VENERG, VEL_IN, DT_IN, VIRIALINOUT, EXISTERROR_INOUT)
SUBROUTINE LATTE(NTYPES, TYPES, CR_IN, MASSES_IN, XLO, XHI, XY, XZ, YZ, FTOT_OUT, &
MAXITER_IN, VENERG, VEL_IN, DT_IN, VIRIAL_INOUT, NEWSYSTEM, EXISTERROR_INOUT)

USE CONSTANTS_MOD, ONLY: EXISTERROR

Expand All @@ -122,27 +123,28 @@ SUBROUTINE LATTE(NTYPES,TYPES,CR_IN,MASSES_IN,XLO,XHI,XY,XZ,YZ,FTOT_OUT, &
REAL(LATTEPREC), INTENT(IN) :: CR_IN(:,:),VEL_IN(:,:), MASSES_IN(:),XLO(3),XHI(3)
REAL(LATTEPREC), INTENT(IN) :: DT_IN, XY, XZ, YZ
REAL(LATTEPREC), INTENT(OUT) :: FTOT_OUT(:,:), VENERG
REAL(LATTEPREC), INTENT(OUT) :: VIRIALINOUT(6)
REAL(LATTEPREC), INTENT(OUT) :: VIRIAL_INOUT(6)
INTEGER, INTENT(IN) :: NTYPES, TYPES(:), MAXITER_IN
LOGICAL(1), INTENT(INOUT) :: EXISTERROR_INOUT
REAL(LATTEPREC) :: MLSI, LUMO, HOMO
INTEGER, INTENT(INOUT) :: NEWSYSTEM

#ifdef PROGRESSON
TYPE(SYSTEM_TYPE) :: SY
#endif

#ifdef MPI_ON
INTEGER :: IERR, STATUS(MPI_STATUS_SIZE), NUMPROCS

CALL MPI_INIT( IERR )
CALL MPI_COMM_RANK( MPI_COMM_WORLD, MYID, IERR )
CALL MPI_COMM_SIZE( MPI_COMM_WORLD, NUMPROCS, IERR )
#endif

EXISTERROR = .FALSE. !We assume we start the lib call without errors

!INITIALIZATION
IF(.NOT. LIBINIT)THEN
IF(.NOT. LIBINIT .OR. NEWSYSTEM == 1)THEN

CALL DEALLOCATEALL()

LIBRUN = .TRUE.

Expand Down Expand Up @@ -288,10 +290,9 @@ SUBROUTINE LATTE(NTYPES,TYPES,CR_IN,MASSES_IN,XLO,XHI,XY,XZ,YZ,FTOT_OUT, &
CALL FLUSH(6)

ENDIF
!End of initialization


!END OF INITIALIZATION

IF (MDON .EQ. 0 .AND. RELAXME .EQ. 0 .AND. DOSFITON .EQ. 0 &
.AND. PPFITON .EQ. 0 .AND. ALLFITON .EQ. 0) THEN

Expand Down Expand Up @@ -607,7 +608,7 @@ SUBROUTINE LATTE(NTYPES,TYPES,CR_IN,MASSES_IN,XLO,XHI,XY,XZ,YZ,FTOT_OUT, &
CALL DTIME(TARRAY, RESULT)

IF (VERBOSE >= 1)WRITE(*,*)"Setting up TBMD ..."
CALL SETUPTBMD
CALL SETUPTBMD(NEWSYSTEM)

CALL FLUSH(6)

Expand Down Expand Up @@ -706,9 +707,10 @@ SUBROUTINE LATTE(NTYPES,TYPES,CR_IN,MASSES_IN,XLO,XHI,XY,XZ,YZ,FTOT_OUT, &

! CALL GETPRESSURE

VIRIALINOUT = -VIRIAL
VIRIAL_INOUT = -VIRIAL

LIBINIT = .TRUE.
NEWSYSTEM = 0 !Setting newsystem back to 0.

#ifdef PROGRESSON
IF(MOD(LIBCALLS,WRTFREQ) == 0)THEN
Expand Down Expand Up @@ -777,6 +779,7 @@ SUBROUTINE LATTE(NTYPES,TYPES,CR_IN,MASSES_IN,XLO,XHI,XY,XZ,YZ,FTOT_OUT, &
CALL FLUSH(6) !To force writing to file at every call

EXISTERROR_INOUT = EXISTERROR

RETURN

ELSEIF (MDON .EQ. 1 .AND. RELAXME .EQ. 0 .AND. MAXITER_IN >= 0) THEN
Expand Down Expand Up @@ -912,6 +915,7 @@ SUBROUTINE LATTE(NTYPES,TYPES,CR_IN,MASSES_IN,XLO,XHI,XY,XZ,YZ,FTOT_OUT, &
#endif

LIBINIT = .TRUE.
NEWSYSTEM = 0 !Setting newsystem back to 0.
EXISTERROR_INOUT = EXISTERROR

END SUBROUTINE LATTE
Expand Down
2 changes: 2 additions & 0 deletions src/qconsistency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ SUBROUTINE QCONSISTENCY(SWITCH, MDITER)
REAL(4) :: TIMEACC
REAL(LATTEPREC) :: MAXDQ
REAL(LATTEPREC), ALLOCATABLE :: QDIFF(:), SPINDIFF(:)

IF (EXISTERROR) RETURN

!
Expand Down Expand Up @@ -77,6 +78,7 @@ SUBROUTINE QCONSISTENCY(SWITCH, MDITER)
ENDIF
ENDIF


! Compute the density matrix

TX = START_TIMER(DMBUILD_TIMER)
Expand Down
9 changes: 5 additions & 4 deletions src/setuptbmd.f90
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@
! Public License for more details. !
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

SUBROUTINE SETUPTBMD
SUBROUTINE SETUPTBMD(NEWSYSTEM)

USE CONSTANTS_MOD
USE SETUPARRAY
Expand All @@ -41,14 +41,15 @@ SUBROUTINE SETUPTBMD
INTEGER :: START_CLOCK, STOP_CLOCK, CLOCK_RATE, CLOCK_MAX
REAL(LATTEPREC) :: THETIME, NEWESPIN, NEWECOUL
REAL(LATTEPREC) :: RN, MYVOL
INTEGER :: FLAGAND
INTEGER :: FLAGAND, NEWSYSTEM

IF (EXISTERROR) RETURN

!
! Read MDcontroller to determine what kind of MD simulation to do
!

IF(.NOT.LIBINIT)THEN
IF(NEWSYSTEM == 1 .OR. (.NOT.LIBINIT))THEN

IF (LATTEINEXISTS) THEN
CALL PARSE_MD("latte.in")
Expand All @@ -72,7 +73,7 @@ SUBROUTINE SETUPTBMD
! to get the bond-order
!

IF(.NOT.LIBINIT)THEN
IF(NEWSYSTEM == 1 .OR. .NOT.LIBINIT)THEN
IF (CONTROL .EQ. 1) THEN
CALL ALLOCATEDIAG
ELSEIF (CONTROL .EQ. 2 .OR. CONTROL .EQ. 4 .OR. CONTROL .EQ. 5) THEN
Expand Down

0 comments on commit b610fe9

Please sign in to comment.