From 127f12e6fafb402fec7bb47eebcd409e431b78a1 Mon Sep 17 00:00:00 2001 From: sjplimp Date: Wed, 15 Aug 2012 14:18:34 +0000 Subject: [PATCH 01/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8669 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- examples/COUPLE/fortran2/LAMMPS-wrapper.cpp | 1 + examples/COUPLE/fortran2/LAMMPS-wrapper.h | 8 +- examples/COUPLE/fortran2/LAMMPS.F90 | 2300 ++++++++++--------- examples/COUPLE/fortran2/README | 6 +- examples/COUPLE/fortran2/makefile | 2 +- 5 files changed, 1212 insertions(+), 1105 deletions(-) diff --git a/examples/COUPLE/fortran2/LAMMPS-wrapper.cpp b/examples/COUPLE/fortran2/LAMMPS-wrapper.cpp index ff6f8cf4ae..6e8bbec5ae 100644 --- a/examples/COUPLE/fortran2/LAMMPS-wrapper.cpp +++ b/examples/COUPLE/fortran2/LAMMPS-wrapper.cpp @@ -30,6 +30,7 @@ #include #include #include +#include using namespace LAMMPS_NS; diff --git a/examples/COUPLE/fortran2/LAMMPS-wrapper.h b/examples/COUPLE/fortran2/LAMMPS-wrapper.h index dce39cad89..68e03ae05a 100644 --- a/examples/COUPLE/fortran2/LAMMPS-wrapper.h +++ b/examples/COUPLE/fortran2/LAMMPS-wrapper.h @@ -21,12 +21,6 @@ library.h. All prototypes herein COULD be added to library.h instead of including this as a separate file. See the README for instructions. */ -/* These prototypes probably belong in mpi.h in the src/STUBS directory. */ -#ifndef OPEN_MPI -#define MPI_Comm_f2c(a) a -#define MPI_Fint int -#endif - #ifdef __cplusplus extern "C" { #endif @@ -38,7 +32,7 @@ int lammps_extract_compute_vectorsize (void*, char*, int); void lammps_extract_compute_arraysize (void*, char*, int, int*, int*); int lammps_extract_fix_vectorsize (void*, char*, int); void lammps_extract_fix_arraysize (void*, char*, int, int*, int*); -void lammps_error_all (void *ptr, const char*, int, const char*); +void lammps_error_all (void*, const char*, int, const char*); #ifdef __cplusplus } diff --git a/examples/COUPLE/fortran2/LAMMPS.F90 b/examples/COUPLE/fortran2/LAMMPS.F90 index 3d07a55feb..7895873d8e 100644 --- a/examples/COUPLE/fortran2/LAMMPS.F90 +++ b/examples/COUPLE/fortran2/LAMMPS.F90 @@ -1,1094 +1,1206 @@ -!! ----------------------------------------------------------------------- -! LAMMPS - Large-scale Atomic/Molecular Massively Parallel Simulator -! www.cs.sandia.gov/~sjplimp/lammps.html -! Steve Plimpton, sjplimp@sandia.gov, Sandia National Laboratories -! -! Copyright (2003) Sandia Corporation. Under the terms of Contract -! DE-AC04-94AL85000 with Sandia Corporation, the U.S. Government retains -! certain rights in this software. This software is distributed under -! the GNU General Public License. -! -! See the README file in the top-level LAMMPS directory. -!-------------------------------------------------------------------------- - -!! ------------------------------------------------------------------------ -! Contributing author: Karl D. Hammond -! University of Tennessee, Knoxville (USA), 2012 -!-------------------------------------------------------------------------- - -!! LAMMPS, a Fortran 2003 module containing an interface between Fortran -!! programs and the C-style functions in library.cpp that ship with LAMMPS. -!! This file should be accompanied by LAMMPS-wrapper.cpp and LAMMPS-wrapper.h, -!! which define wrapper functions that ease portability and enforce array -!! dimensions. -!! -!! Everything in this module should be 100% portable by way of Fortran 2003's -!! ISO_C_BINDING intrinsic module. See the README for instructions for -!! compilation and use. -!! -!! Here are the PUBLIC functions and subroutines included in this module. -!! subroutine lammps_open (command_line, communicator, ptr) -!! subroutine lammps_open_no_mpi (command_line, ptr) -!! subroutine lammps_close (ptr) -!! subroutine lammps_file (ptr, str) -!! subroutine lammps_command (ptr, str) -!! subroutine lammps_free (ptr) -!! subroutine lammps_extract_global (global, ptr, name) -!! subroutine lammps_extract_atom (atom, ptr, name) -!! subroutine lammps_extract_fix (fix, ptr, id, style, type, i, j) -!! subroutine lammps_extract_compute (compute, ptr, id, style, type) -!! subroutine lammps_extract_variable (variable, ptr, name, group) -!! function lammps_get_natoms (ptr) -!! subroutine lammps_get_coords (ptr, coords) -!! subroutine lammps_put_coords (ptr, coords) - -#define FLERR __FILE__,__LINE__ -! The above line allows for similar error checking as is done with standard -! LAMMPS files. - -module LAMMPS - - use, intrinsic :: ISO_C_binding, only : C_double, C_int, C_ptr, C_char, & - C_NULL_CHAR, C_loc, C_F_pointer, lammps_instance => C_ptr - implicit none - private - public :: lammps_open, lammps_open_no_mpi, lammps_close, lammps_file, & - lammps_command, lammps_free, lammps_extract_global, & - lammps_extract_atom, lammps_extract_compute, lammps_extract_fix, & - lammps_extract_variable, lammps_get_natoms, lammps_get_coords, & - lammps_put_coords, lammps_instance - - !! Functions supplemental to the prototypes in library.h. {{{1 - !! The function definitions (in C++) are contained in LAMMPS-wrapper.cpp. - !! I would have written the first in Fortran, but the MPI libraries (which - !! were written in C) have C-based functions to convert from Fortran MPI - !! handles to C MPI handles, and there is no Fortran equivalent for those - !! functions. - interface - subroutine lammps_open_wrapper (argc, argv, communicator, ptr) & - bind (C, name='lammps_open_fortran_wrapper') - import :: C_int, C_ptr - integer (C_int), value :: argc - type (C_ptr), dimension(*) :: argv - integer, value :: communicator - type (C_ptr) :: ptr - end subroutine lammps_open_wrapper - subroutine lammps_actual_error_all (ptr, file, line, str) & - bind (C, name='lammps_error_all') - import :: C_int, C_char, C_ptr - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*), intent(in) :: file, str - integer (C_int), value :: line - end subroutine lammps_actual_error_all - function lammps_get_ntypes (ptr) result (ntypes) & - bind (C, name='lammps_get_ntypes') - import :: C_int, C_ptr - type (C_ptr), value :: ptr - integer (C_int) :: ntypes - end function lammps_get_ntypes - function lammps_actual_extract_compute_vectorsize (ptr, id, style) & - result (vectorsize) bind (C, name='lammps_extract_compute_vectorsize') - import :: C_int, C_char, C_ptr - integer (C_int) :: vectorsize - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*) :: id - integer (C_int), value :: style - end function lammps_actual_extract_compute_vectorsize - subroutine lammps_actual_extract_compute_arraysize (ptr, id, style, & - nrows, ncols) bind (C, name='lammps_extract_compute_arraysize') - import :: C_int, C_char, C_ptr - integer (C_int) :: arraysize - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*) :: id - integer (C_int), value :: style - integer (C_int) :: nrows, ncols - end subroutine lammps_actual_extract_compute_arraysize - function lammps_actual_extract_fix_vectorsize (ptr, id, style) & - result (vectorsize) bind (C, name='lammps_extract_fix_vectorsize') - import :: C_int, C_char, C_ptr - integer (C_int) :: vectorsize - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*) :: id - integer (C_int), value :: style - end function lammps_actual_extract_fix_vectorsize - subroutine lammps_actual_extract_fix_arraysize (ptr, id, style, & - nrows, ncols) bind (C, name='lammps_extract_fix_arraysize') - import :: C_int, C_char, C_ptr - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*) :: id - integer (C_int), value :: style - integer (C_int) :: nrows, ncols - end subroutine lammps_actual_extract_fix_arraysize - end interface - - !! Functions/subroutines defined in library.h and library.cpp {{{1 - interface - subroutine lammps_actual_open_no_mpi (argc, argv, ptr) & - bind (C, name='lammps_open_no_mpi') - import :: C_int, C_ptr - integer (C_int), value :: argc - type (C_ptr), dimension(*) :: argv - type (C_ptr) :: ptr - end subroutine lammps_actual_open_no_mpi - - subroutine lammps_close (ptr) bind (C, name='lammps_close') - import :: C_ptr - type (C_ptr), value :: ptr - end subroutine lammps_close - - subroutine lammps_actual_file (ptr, str) bind (C, name='lammps_file') - import :: C_ptr, C_char - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*) :: str - end subroutine lammps_actual_file - - function lammps_actual_command (ptr, str) result (command) & - bind (C, name='lammps_command') - import :: C_ptr, C_char - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*) :: str - type (C_ptr) :: command - end function lammps_actual_command - - subroutine lammps_free (ptr) bind (C, name='lammps_free') - import :: C_ptr - type (C_ptr), value :: ptr - end subroutine lammps_free - - function lammps_actual_extract_global (ptr, name) & - bind (C, name='lammps_extract_global') result (global) - import :: C_ptr, C_char - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*) :: name - type (C_ptr) :: global - end function lammps_actual_extract_global - - function lammps_actual_extract_atom (ptr, name) & - bind (C, name='lammps_extract_atom') result (atom) - import :: C_ptr, C_char - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*) :: name - type (C_ptr) :: atom - end function lammps_actual_extract_atom - - function lammps_actual_extract_compute (ptr, id, style, type) & - result (compute) bind (C, name='lammps_extract_compute') - import :: C_ptr, C_char, C_int - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*) :: id - integer (C_int), value :: style, type - type (C_ptr) :: compute - end function lammps_actual_extract_compute - - function lammps_actual_extract_fix (ptr, id, style, type, i, j) & - result (fix) bind (C, name='lammps_extract_fix') - import :: C_ptr, C_char, C_int - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*) :: id - integer (C_int), value :: style, type, i, j - type (C_ptr) :: fix - end function lammps_actual_extract_fix - - function lammps_actual_extract_variable (ptr, name, group) & - result (variable) bind (C, name='lammps_extract_variable') - import :: C_ptr, C_char - type (C_ptr), value :: ptr - character (kind=C_char), dimension(*) :: name, group - type (C_ptr) :: variable - end function lammps_actual_extract_variable - - function lammps_get_natoms (ptr) result (natoms) & - bind (C, name='lammps_get_natoms') - import :: C_ptr, C_int - type (C_ptr), value :: ptr - integer (C_int) :: natoms - end function lammps_get_natoms - - subroutine lammps_actual_get_coords (ptr, coords) & - bind (C, name='lammps_get_coords') - import :: C_ptr - type (C_ptr), value :: ptr, coords - end subroutine lammps_actual_get_coords - - subroutine lammps_actual_put_coords (ptr, coords) & - bind (C, name='lammps_put_coords') - import :: C_ptr, C_double - type (C_ptr), value :: ptr - real (C_double), dimension(*) :: coords - end subroutine lammps_actual_put_coords - end interface - - ! Generic functions for the wrappers below {{{1 - - ! Check the dimensions of the arrays these return; they are not always - ! easy to find. Note that I consider returning pointers to arbitrary - ! memory locations with no information as to array size/shape to be - ! extremely sloppy and error-prone. It would appear the Fortran standards - ! committee would agree, as they chose not to allow that sort of nonsense. - - interface lammps_extract_global - module procedure lammps_extract_global_i, lammps_extract_global_r, & - lammps_extract_global_dp - end interface lammps_extract_global - - interface lammps_extract_atom - module procedure lammps_extract_atom_ia, lammps_extract_atom_ra, & - lammps_extract_atom_dpa, lammps_extract_atom_dp2a, & - lammps_extract_atom_r2a - end interface lammps_extract_atom - - interface lammps_extract_compute - module procedure lammps_extract_compute_r, lammps_extract_compute_dp, & - lammps_extract_compute_ra, lammps_extract_compute_dpa, & - lammps_extract_compute_r2a, lammps_extract_compute_dp2a - end interface lammps_extract_compute - - interface lammps_extract_fix - module procedure lammps_extract_fix_r, lammps_extract_fix_dp, & - lammps_extract_fix_ra, lammps_extract_fix_dpa, & - lammps_extract_fix_r2a, lammps_extract_fix_dp2a - end interface lammps_extract_fix - - interface lammps_extract_variable - module procedure lammps_extract_variable_i, & - lammps_extract_variable_dp, & - lammps_extract_variable_r, & - lammps_extract_variable_ra, & - lammps_extract_variable_ia, & - lammps_extract_variable_dpa - end interface lammps_extract_variable - -contains !! Wrapper functions local to this module {{{1 - - subroutine lammps_open (command_line, communicator, ptr) - character (len=*), intent(in) :: command_line - integer, intent(in) :: communicator - type (C_ptr) :: ptr - integer (C_int) :: argc - type (C_ptr), dimension(:), allocatable :: argv - character (kind=C_char), dimension(len_trim(command_line)+1), target :: & - c_command_line - c_command_line = string2Cstring (command_line) - call Cstring2argcargv (c_command_line, argc, argv) - call lammps_open_wrapper (argc, argv, communicator, ptr) - deallocate (argv) - end subroutine lammps_open - -!----------------------------------------------------------------------------- - - subroutine lammps_open_no_mpi (command_line, ptr) - character (len=*), intent(in) :: command_line - type (C_ptr) :: ptr - integer (C_int) :: argc - type (C_ptr), dimension(:), allocatable :: argv - character (kind=C_char), dimension(len_trim(command_line)+1), target :: & - c_command_line - c_command_line = string2Cstring (command_line) - call Cstring2argcargv (c_command_line, argc, argv) - call lammps_actual_open_no_mpi (argc, argv, ptr) - deallocate (argv) - end subroutine lammps_open_no_mpi - -!----------------------------------------------------------------------------- - - subroutine lammps_file (ptr, str) - type (C_ptr) :: ptr - character (len=*) :: str - character (kind=C_char), dimension(len_trim(str)+1) :: Cstr - Cstr = string2Cstring (str) - call lammps_actual_file (ptr, Cstr) - end subroutine lammps_file - -!----------------------------------------------------------------------------- - - subroutine lammps_command (ptr, str) - type (C_ptr) :: ptr - character (len=*) :: str - character (kind=C_char), dimension(len_trim(str)+1) :: Cstr - type (C_ptr) :: dummy - Cstr = string2Cstring (str) - dummy = lammps_actual_command (ptr, Cstr) - end subroutine lammps_command - -!----------------------------------------------------------------------------- - -! lammps_extract_global {{{2 - function lammps_extract_global_Cptr (ptr, name) result (global) - type (C_ptr) :: global - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - character (kind=C_char), dimension(len_trim(name)+1) :: Cname - Cname = string2Cstring (name) - global = lammps_actual_extract_global (ptr, Cname) - end function lammps_extract_global_Cptr - subroutine lammps_extract_global_i (global, ptr, name) - integer, intent(out) :: global - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - type (C_ptr) :: Cptr - integer (C_int), pointer :: Fptr - Cptr = lammps_extract_global_Cptr (ptr, name) - call C_F_pointer (Cptr, Fptr) - global = Fptr - nullify (Fptr) - end subroutine lammps_extract_global_i - subroutine lammps_extract_global_dp (global, ptr, name) - double precision, intent(out) :: global - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - type (C_ptr) :: Cptr - real (C_double), pointer :: Fptr - Cptr = lammps_extract_global_Cptr (ptr, name) - call C_F_pointer (Cptr, Fptr) - global = Fptr - nullify (Fptr) - end subroutine lammps_extract_global_dp - subroutine lammps_extract_global_r (global, ptr, name) - real :: global - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - type (C_ptr) :: Cptr - real (C_double), pointer :: Fptr - Cptr = lammps_extract_global_Cptr (ptr, name) - call C_F_pointer (Cptr, Fptr) - global = real (Fptr) - nullify (Fptr) - end subroutine lammps_extract_global_r - -!----------------------------------------------------------------------------- - -! lammps_extract_atom {{{2 - function lammps_extract_atom_Cptr (ptr, name) result (atom) - type (C_ptr) :: atom - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - character (kind=C_char), dimension(len_trim(name)+1) :: Cname - Cname = string2Cstring (name) - atom = lammps_actual_extract_atom (ptr, Cname) - end function lammps_extract_atom_Cptr - subroutine lammps_extract_atom_ia (atom, ptr, name) - integer, dimension(:), allocatable, intent(out) :: atom - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - type (C_ptr) :: Cptr - integer (C_int), pointer :: Fptr - integer :: natoms - natoms = lammps_get_natoms (ptr) - if ( allocated (atom) ) deallocate (atom) - allocate (atom(natoms)) - Cptr = lammps_extract_atom_Cptr (ptr, name) - call C_F_pointer (Cptr, Fptr, (/natoms/)) - atom = Fptr - nullify (Fptr) - end subroutine lammps_extract_atom_ia - subroutine lammps_extract_atom_dpa (atom, ptr, name) - double precision, dimension(:), allocatable, intent(out) :: atom - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - type (C_ptr) :: Cptr - real (C_double), dimension(:), pointer :: Fptr - integer :: nelements - if ( name == 'mass' ) then - nelements = lammps_get_ntypes (ptr) - else if ( name == 'x' .or. name == 'v' .or. name == 'f' ) then - ! We should not be getting 'x' or 'v' or 'f' here! - call lammps_error_all (ptr, FLERR, 'You cannot extract those atom& - & data (x, v, or f) into a rank 1 array.') - return - else - ! Everything else we can get is probably nlocal units long - call lammps_extract_global_i (nelements, ptr, 'nlocal') - end if - if ( allocated (atom) ) deallocate (atom) - allocate (atom(nelements)) - Cptr = lammps_extract_atom_Cptr (ptr, name) - if ( name == 'mass' ) then - call C_F_pointer (Cptr, Fptr, (/nelements + 1/)) - atom = Fptr(2:) ! LAMMPS starts numbering at 1 (C does not) - else - call C_F_pointer (Cptr, Fptr, (/nelements/)) - atom = Fptr - end if - nullify (Fptr) - end subroutine lammps_extract_atom_dpa - subroutine lammps_extract_atom_ra (atom, ptr, name) - real, dimension(:), allocatable, intent(out) :: atom - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - double precision, dimension(:), allocatable :: d_atom - call lammps_extract_atom_dpa (d_atom, ptr, name) - if ( allocated (atom) ) deallocate (atom) - allocate (atom(size(d_atom))) - atom = real(d_atom) - deallocate (d_atom) - end subroutine lammps_extract_atom_ra - subroutine lammps_extract_atom_dp2a (atom, ptr, name) - double precision, dimension(:,:), allocatable, intent(out) :: atom - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - type (C_ptr) :: Cptr - integer :: nelements - if ( allocated (atom) ) deallocate (atom) - if ( name /= 'x' .and. name /= 'v' .and. name /= 'f' ) then - call lammps_error_all (ptr, FLERR, 'You cannot extract ' // name // & - ' into a rank 2 array.') - return - end if - Cptr = lammps_extract_atom_Cptr (ptr, name) - nelements = lammps_get_natoms (ptr) - allocate (atom(nelements,3)) - atom = Cdoublestar_to_2darray (Cptr, nelements, 3) - end subroutine lammps_extract_atom_dp2a - subroutine lammps_extract_atom_r2a (atom, ptr, name) - real, dimension(:,:), allocatable, intent(out) :: atom - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - double precision, dimension(:,:), allocatable :: d_atom - call lammps_extract_atom_dp2a (d_atom, ptr, name) - if ( allocated (atom) ) deallocate (atom) - if ( allocated (d_atom) ) then - allocate (atom(size(d_atom,1), size(d_atom,2))) - else - return - end if - atom = real(d_atom) - deallocate (d_atom) - end subroutine lammps_extract_atom_r2a - -!----------------------------------------------------------------------------- - -! lammps_extract_compute {{{2 - function lammps_extract_compute_Cptr (ptr, id, style, type) result (compute) - type (C_ptr) :: compute - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type - integer (kind=C_int) :: Cstyle, Ctype - character (kind=C_char), dimension(len_trim(id)+1) :: Cid - Cid = string2Cstring (id) - Cstyle = style - Ctype = type - compute = lammps_actual_extract_compute (ptr, Cid, Cstyle, Ctype) - end function lammps_extract_compute_Cptr - subroutine lammps_extract_compute_dp (compute, ptr, id, style, type) - double precision, intent(out) :: compute - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type - type (C_ptr) :: Cptr - real (C_double), pointer :: Fptr - ! The only valid values of (style,type) are (0,0) for scalar 'compute' - if ( style /= 0 ) then - call lammps_error_all (ptr, FLERR, 'You cannot pack per-atom/local& - & data into a scalar.') - return - end if - if ( type == 1 ) then - call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& - & vector (rank 1) into a scalar.') - return - else if ( type == 2 ) then - call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& - & array (rank 2) into a scalar.') - return - end if - Cptr = lammps_extract_compute_Cptr (ptr, id, style, type) - call C_F_pointer (Cptr, Fptr) - compute = Fptr - nullify (Fptr) - ! C pointer should not be freed! - end subroutine lammps_extract_compute_dp - subroutine lammps_extract_compute_r (compute, ptr, id, style, type) - real, intent(out) :: compute - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type - double precision :: d_compute - call lammps_extract_compute_dp (d_compute, ptr, id, style, type) - compute = real(d_compute) - end subroutine lammps_extract_compute_r - subroutine lammps_extract_compute_dpa (compute, ptr, id, style, type) - double precision, dimension(:), allocatable, intent(out) :: compute - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type - type (C_ptr) :: Cptr - real (C_double), dimension(:), pointer :: Fptr - integer :: nelements - if ( allocated (compute) ) deallocate (compute) - ! Check for the correct dimensionality - if ( type == 0 ) then - call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& - & scalar (rank 0) into a rank 1 variable.') - return - else if ( type == 2 ) then - call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& - & array (rank 2) into a rank 1 variable.') - return - end if - nelements = lammps_extract_compute_vectorsize (ptr, id, style) - allocate (compute(nelements)) - Cptr = lammps_extract_compute_Cptr (ptr, id, style, type) - call C_F_pointer (Cptr, Fptr, (/nelements/)) - compute = Fptr - nullify (Fptr) - ! C pointer should not be freed - end subroutine lammps_extract_compute_dpa - subroutine lammps_extract_compute_ra (compute, ptr, id, style, type) - real, dimension(:), allocatable, intent(out) :: compute - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type - double precision, dimension(:), allocatable :: d_compute - call lammps_extract_compute_dpa (d_compute, ptr, id, style, type) - if ( allocated (compute) ) deallocate (compute) - allocate (compute(size(d_compute))) - compute = real(d_compute) - deallocate (d_compute) - end subroutine lammps_extract_compute_ra - subroutine lammps_extract_compute_dp2a (compute, ptr, id, style, type) - double precision, dimension(:,:), allocatable, intent(out) :: compute - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type - type (C_ptr) :: Cptr - real (C_double), dimension(:,:), pointer :: Fptr - integer :: nr, nc - if ( allocated (compute) ) deallocate (compute) - ! Check for the correct dimensionality - if ( type == 0 ) then - call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& - & scalar (rank 0) into a rank 2 variable.') - return - else if ( type == 1 ) then - call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& - & array (rank 1) into a rank 2 variable.') - return - end if - call lammps_extract_compute_arraysize (ptr, id, style, nr, nc) - allocate (compute(nr, nc)) - Cptr = lammps_extract_compute_Cptr (ptr, id, style, type) - call C_F_pointer (Cptr, Fptr, (/nr, nc/)) - compute = Fptr - nullify (Fptr) - ! C pointer should not be freed - end subroutine lammps_extract_compute_dp2a - subroutine lammps_extract_compute_r2a (compute, ptr, id, style, type) - real, dimension(:,:), allocatable, intent(out) :: compute - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type - double precision, dimension(:,:), allocatable :: d_compute - call lammps_extract_compute_dp2a (d_compute, ptr, id, style, type) - if ( allocated (compute) ) deallocate (compute) - allocate (compute(size(d_compute,1), size(d_compute,2))) - compute = real(d_compute) - deallocate (d_compute) - end subroutine lammps_extract_compute_r2a - -!----------------------------------------------------------------------------- - -! lammps_extract_fix {{{2 - function lammps_extract_fix_Cptr (ptr, id, style, type, i, j) & - result (fix) - type (C_ptr) :: fix - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type, i, j - character (kind=C_char), dimension(len_trim(id)+1) :: Cid - integer (kind=C_int) :: Cstyle, Ctype, Ci, Cj - Cid = string2Cstring (id) - Cstyle = style - Ctype = type - Ci = i - 1 ! This is for consistency with the values from f_ID[i], - Cj = j - 1 ! which is different from what library.cpp uses! - if ( (type >= 1 .and. Ci < 0) .or. & - (type == 2 .and. (Ci < 0 .or. Cj < 0) ) ) then - call lammps_error_all (ptr, FLERR, 'Index out of range in& - & lammps_extract_fix') - end if - fix = lammps_actual_extract_fix (ptr, Cid, Cstyle, Ctype, Ci, Cj) - end function lammps_extract_fix_Cptr - subroutine lammps_extract_fix_dp (fix, ptr, id, style, type, i, j) - double precision, intent(out) :: fix - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type, i, j - type (C_ptr) :: Cptr - real (C_double), pointer :: Fptr - ! Check for the correct dimensionality - if ( style /= 0 ) then - select case (type) - case (0) - call lammps_error_all (ptr, FLERR, 'There is no per-atom or local& - & scalar data available from fixes.') - case (1) - call lammps_error_all (ptr, FLERR, 'You cannot extract a fix''s & - &per-atom/local vector (rank 1) into a scalar.') - case (2) - call lammps_error_all (ptr, FLERR, 'You cannot extract a fix''s & - &per-atom/local array (rank 2) into a scalar.') - case default - call lammps_error_all (ptr, FLERR, 'Invalid extract_fix style& - & value.') - end select - return - end if - Cptr = lammps_extract_fix_Cptr (ptr, id, style, type, i, j) - call C_F_pointer (Cptr, Fptr) - fix = Fptr - nullify (Fptr) - ! Memory is only allocated for "global" fix variables - if ( style == 0 ) call lammps_free (Cptr) - end subroutine lammps_extract_fix_dp - subroutine lammps_extract_fix_r (fix, ptr, id, style, type, i, j) - real, intent(out) :: fix - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type, i, j - double precision :: d_fix - call lammps_extract_fix_dp (d_fix, ptr, id, style, type, i, j) - fix = real(d_fix) - end subroutine lammps_extract_fix_r - subroutine lammps_extract_fix_dpa (fix, ptr, id, style, type, i, j) - double precision, dimension(:), allocatable, intent(out) :: fix - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type, i, j - type (C_ptr) :: Cptr - real (C_double), dimension(:), pointer :: Fptr - integer :: fix_len - if ( allocated (fix) ) deallocate (fix) - ! Check for the correct dimensionality - if ( style == 0 ) then - call lammps_error_all (ptr, FLERR, 'You can''t extract the& - & whole vector from global fix data') - return - else if ( type == 0 ) then - call lammps_error_all (ptr, FLERR, 'You can''t extract a fix& - & scalar into a rank 1 variable') - return - else if ( type == 2 ) then - call lammps_error_all (ptr, FLERR, 'You cannot extract a fix& - & array into a rank 1 variable.') - return - else if ( type /= 1 ) then - call lammps_error_all (ptr, FLERR, 'Invalid type for fix extraction.') - return - end if - fix_len = lammps_extract_fix_vectorsize (ptr, id, style) - allocate (fix(fix_len)) - Cptr = lammps_extract_fix_Cptr (ptr, id, style, type, i, j) - call C_F_pointer (Cptr, Fptr, (/fix_len/)) - fix = Fptr - nullify (Fptr) - ! Memory is only allocated for "global" fix variables - if ( style == 0 ) call lammps_free (Cptr) - end subroutine lammps_extract_fix_dpa - subroutine lammps_extract_fix_ra (fix, ptr, id, style, type, i, j) - real, dimension(:), allocatable, intent(out) :: fix - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type, i, j - double precision, dimension(:), allocatable :: d_fix - call lammps_extract_fix_dpa (d_fix, ptr, id, style, type, i, j) - if ( allocated (fix) ) deallocate (fix) - allocate (fix(size(d_fix))) - fix = real(d_fix) - deallocate (d_fix) - end subroutine lammps_extract_fix_ra - subroutine lammps_extract_fix_dp2a (fix, ptr, id, style, type, i, j) - double precision, dimension(:,:), allocatable, intent(out) :: fix - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type, i, j - type (C_ptr) :: Cptr - real (C_double), dimension(:,:), pointer :: Fptr - integer :: nr, nc - if ( allocated (fix) ) deallocate (fix) - ! Check for the correct dimensionality - if ( style == 0 ) then - call lammps_error_all (ptr, FLERR, 'It is not possible to extract the& - & entire array from global fix data.') - return - else if ( type == 0 ) then - call lammps_error_all (ptr, FLERR, 'You cannot extract a fix& - & scalar (rank 0) into a rank 2 variable.') - return - else if ( type == 1 ) then - call lammps_error_all (ptr, FLERR, 'You cannot extract a fix& - & vector (rank 1) into a rank 2 variable.') - return - end if - call lammps_extract_fix_arraysize (ptr, id, style, nr, nc) - allocate (fix(nr, nc)) - Cptr = lammps_extract_fix_Cptr (ptr, id, style, type, i, j) - call C_F_pointer (Cptr, Fptr, (/nr, nc/)) - fix = Fptr - nullify (Fptr) - ! C pointer should not be freed - end subroutine lammps_extract_fix_dp2a - subroutine lammps_extract_fix_r2a (fix, ptr, id, style, type, i, j) - real, dimension(:,:), allocatable, intent(out) :: fix - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style, type, i, j - double precision, dimension(:,:), allocatable :: d_fix - call lammps_extract_fix_dp2a (d_fix, ptr, id, style, type, i, j) - if ( allocated (fix) ) deallocate (fix) - allocate (fix(size(d_fix,1), size(d_fix,2))) - fix = real(d_fix) - deallocate (d_fix) - end subroutine lammps_extract_fix_r2a - -!----------------------------------------------------------------------------- - -! lammps_extract_variable {{{2 - function lammps_extract_variable_Cptr (ptr, name, group) result (variable) - type (C_ptr) :: ptr, variable - character (len=*) :: name - character (len=*), optional :: group - character (kind=C_char), dimension(len_trim(name)+1) :: Cname - character (kind=C_char), dimension(:), allocatable :: Cgroup - Cname = string2Cstring (name) - if ( present(group) ) then - allocate (Cgroup(len_trim(group)+1)) - Cgroup = string2Cstring (group) - else - allocate (Cgroup(1)) - Cgroup(1) = C_NULL_CHAR - end if - variable = lammps_actual_extract_variable (ptr, Cname, Cgroup) - deallocate (Cgroup) - end function lammps_extract_variable_Cptr - subroutine lammps_extract_variable_i (variable, ptr, name, group) - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - character (len=*), intent(in), optional :: group - integer, intent(out) :: variable - type (C_ptr) :: Cptr - integer (C_int), pointer :: Fptr - if ( present(group) ) then - Cptr = lammps_extract_variable_Cptr (ptr, name, group) - else - Cptr = lammps_extract_variable_Cptr (ptr, name) - end if - call C_F_pointer (Cptr, Fptr) - variable = Fptr - nullify (Fptr) - call lammps_free (Cptr) - end subroutine lammps_extract_variable_i - subroutine lammps_extract_variable_dp (variable, ptr, name, group) - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - character (len=*), intent(in), optional :: group - double precision, intent(out) :: variable - type (C_ptr) :: Cptr - real (C_double), pointer :: Fptr - if ( present(group) ) then - Cptr = lammps_extract_variable_Cptr (ptr, name, group) - else - Cptr = lammps_extract_variable_Cptr (ptr, name) - end if - call C_F_pointer (Cptr, Fptr) - variable = Fptr - nullify (Fptr) - call lammps_free (Cptr) - end subroutine lammps_extract_variable_dp - subroutine lammps_extract_variable_r (variable, ptr, name, group) - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - character (len=*), intent(in), optional :: group - real, intent(out) :: variable - double precision :: d_var - if ( present (group) ) then - call lammps_extract_variable_dp (d_var, ptr, name, group) - else - call lammps_extract_variable_dp (d_var, ptr, name) - end if - variable = real(d_var) - end subroutine lammps_extract_variable_r - - subroutine lammps_extract_variable_ia (variable, ptr, name, group) - integer, dimension(:), allocatable, intent(out) :: variable - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - character (len=*), intent(in), optional :: group - type (C_ptr) :: Cptr - integer (C_int), dimension(:), pointer :: Fptr - integer :: natoms - nullify (Fptr) - if ( present(group) ) then - Cptr = lammps_extract_variable_Cptr (ptr, name, group) - else - Cptr = lammps_extract_variable_Cptr (ptr, name) - end if - natoms = lammps_get_natoms (ptr) - if ( allocated (variable) ) deallocate (variable) - allocate (variable(natoms)) - call C_F_pointer (Cptr, Fptr, (/natoms/)) - variable = Fptr - nullify (Fptr) - call lammps_free (Cptr) - end subroutine lammps_extract_variable_ia - subroutine lammps_extract_variable_dpa (variable, ptr, name, group) - double precision, dimension(:), allocatable, intent(out) :: variable - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - character (len=*), intent(in), optional :: group - type (C_ptr) :: Cptr - real (C_double), dimension(:), pointer :: Fptr - integer :: natoms - if ( present(group) ) then - Cptr = lammps_extract_variable_Cptr (ptr, name, group) - else - Cptr = lammps_extract_variable_Cptr (ptr, name) - end if - natoms = lammps_get_natoms (ptr) - if ( allocated (variable) ) deallocate (variable) - allocate (variable(natoms)) - call C_F_pointer (Cptr, Fptr, (/natoms/)) - variable = Fptr - nullify (Fptr) - call lammps_free (Cptr) - end subroutine lammps_extract_variable_dpa - subroutine lammps_extract_variable_ra (variable, ptr, name, group) - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: name - character (len=*), intent(in), optional :: group - real, dimension(:), allocatable, intent(out) :: variable - double precision, dimension(:), allocatable :: d_var - if ( present (group) ) then - call lammps_extract_variable_dpa (d_var, ptr, name, group) - else - call lammps_extract_variable_dpa (d_var, ptr, name) - end if - if ( allocated (variable) ) deallocate (variable) - allocate (variable(size(d_var))) - variable = real(d_var) - deallocate (d_var) - end subroutine lammps_extract_variable_ra - -!-------------------------------------------------------------------------2}}} - - subroutine lammps_get_coords (ptr, coords) - type (C_ptr) :: ptr - double precision, dimension(:), allocatable :: coords - real (C_double), dimension(:), allocatable, target :: C_coords - integer :: natoms - natoms = lammps_get_natoms (ptr) - if ( allocated(coords) ) deallocate (coords) - allocate (coords(3*natoms)) - allocate (C_coords(3*natoms)) - call lammps_actual_get_coords (ptr, C_loc(C_coords)) - coords = C_coords - deallocate (C_coords) - end subroutine lammps_get_coords - -!----------------------------------------------------------------------------- - - subroutine lammps_put_coords (ptr, coords) - type (C_ptr) :: ptr - double precision, dimension(:) :: coords - real (C_double), dimension(size(coords)) :: C_coords - C_coords = coords - call lammps_actual_put_coords (ptr, C_coords) - end subroutine lammps_put_coords - -!----------------------------------------------------------------------------- - - function lammps_extract_compute_vectorsize (ptr, id, style) & - result (vectorsize) - integer :: vectorsize - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style - integer (C_int) :: Cvectorsize, Cstyle - character (kind=C_char), dimension(len_trim(id)+1) :: Cid - Cid = string2Cstring (id) - Cstyle = int(style, C_int) - Cvectorsize = lammps_actual_extract_compute_vectorsize (ptr, Cid, Cstyle) - vectorsize = int(Cvectorsize, kind(vectorsize)) - end function lammps_extract_compute_vectorsize - -!----------------------------------------------------------------------------- - - function lammps_extract_fix_vectorsize (ptr, id, style) & - result (vectorsize) - integer :: vectorsize - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style - integer (C_int) :: Cvectorsize, Cstyle - character (kind=C_char), dimension(len_trim(id)+1) :: Cid - Cid = string2Cstring (id) - Cstyle = int(style, C_int) - Cvectorsize = lammps_actual_extract_fix_vectorsize (ptr, Cid, Cstyle) - vectorsize = int(Cvectorsize, kind(vectorsize)) - end function lammps_extract_fix_vectorsize - -!----------------------------------------------------------------------------- - - subroutine lammps_extract_compute_arraysize (ptr, id, style, nrows, ncols) - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style - integer, intent(out) :: nrows, ncols - integer (C_int) :: Cstyle, Cnrows, Cncols - character (kind=C_char), dimension(len_trim(id)+1) :: Cid - Cid = string2Cstring (id) - Cstyle = int (style, C_int) - call lammps_actual_extract_compute_arraysize (ptr, Cid, Cstyle, & - Cnrows, Cncols) - nrows = int (Cnrows, kind(nrows)) - ncols = int (Cncols, kind(ncols)) - end subroutine lammps_extract_compute_arraysize - -!----------------------------------------------------------------------------- - - subroutine lammps_extract_fix_arraysize (ptr, id, style, nrows, ncols) - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: id - integer, intent(in) :: style - integer, intent(out) :: nrows, ncols - integer (C_int) :: Cstyle, Cnrows, Cncols - character (kind=C_char), dimension(len_trim(id)+1) :: Cid - Cid = string2Cstring (id) - Cstyle = int (style, kind(Cstyle)) - call lammps_actual_extract_fix_arraysize (ptr, Cid, Cstyle, & - Cnrows, Cncols) - nrows = int (Cnrows, kind(nrows)) - ncols = int (Cncols, kind(ncols)) - end subroutine lammps_extract_fix_arraysize - -!----------------------------------------------------------------------------- - - subroutine lammps_error_all (ptr, file, line, str) - type (C_ptr), intent(in) :: ptr - character (len=*), intent(in) :: file, str - integer, intent(in) :: line - character (kind=C_char), dimension(len_trim(file)+1) :: Cfile - character (kind=C_char), dimension(len_trim(str)+1) :: Cstr - integer (C_int) :: Cline - Cline = int(line, kind(Cline)) - Cfile = string2Cstring (file) - Cstr = string2Cstring (str) - call lammps_actual_error_all (ptr, Cfile, Cline, Cstr) - end subroutine lammps_error_all - -!----------------------------------------------------------------------------- - -! Locally defined helper functions {{{1 - - pure function string2Cstring (string) result (C_string) - use, intrinsic :: ISO_C_binding, only : C_char, C_NULL_CHAR - character (len=*), intent(in) :: string - character (len=1, kind=C_char) :: C_string (len_trim(string)+1) - integer :: i, n - n = len_trim (string) - forall (i = 1:n) - C_string(i) = string(i:i) - end forall - C_string(n+1) = C_NULL_CHAR - end function string2Cstring - -!----------------------------------------------------------------------------- - - subroutine Cstring2argcargv (Cstring, argc, argv) - !! Converts a C-style string to argc and argv, that is, words in Cstring - !! become C-style strings in argv. IMPORTANT: Cstring is modified by - !! this routine! I would make Cstring local TO this routine and accept - !! a Fortran-style string instead, but we run into scoping and - !! allocation problems that way. This routine assumes the string is - !! null-terminated, as all C-style strings must be. - - character (kind=C_char), dimension(*), target, intent(inout) :: Cstring - integer (C_int), intent(out) :: argc - type (C_ptr), dimension(:), allocatable, intent(out) :: argv - - integer :: StringStart, SpaceIndex, strlen, argnum - - argc = 1_C_int - - ! Find the length of the string - strlen = 1 - do while ( Cstring(strlen) /= C_NULL_CHAR ) - strlen = strlen + 1 - end do - - ! Find the number of non-escaped spaces - SpaceIndex = 2 - do while ( SpaceIndex < strlen ) - if ( Cstring(SpaceIndex) == ' ' .and. & - Cstring(SpaceIndex-1) /= '\' ) then - argc = argc + 1_C_int - ! Find the next non-space character - do while ( Cstring(SpaceIndex+1) == ' ') - SpaceIndex = SpaceIndex + 1 - end do - end if - SpaceIndex = SpaceIndex + 1 - end do - - ! Now allocate memory for argv - allocate (argv(argc)) - - ! Now find the string starting and ending locations - StringStart = 1 - SpaceIndex = 2 - argnum = 1 - do while ( SpaceIndex < strlen ) - if ( Cstring(SpaceIndex) == ' ' .and. & - Cstring(SpaceIndex-1) /= '\' ) then - ! Found a real space => split strings and store this one - Cstring(Spaceindex) = C_NULL_CHAR ! Replaces space with NULL - argv(argnum) = C_loc(Cstring(StringStart)) - argnum = argnum + 1 - ! Find the next non-space character - do while ( Cstring(SpaceIndex+1) == ' ') - SpaceIndex = SpaceIndex + 1 - end do - StringStart = SpaceIndex + 1 - else if ( Cstring(SpaceIndex) == ' ' .and. & - Cstring(SpaceIndex-1) == '\' ) then - ! Escaped space => remove backslash and move rest of array - Cstring(SpaceIndex-1:strlen-1) = Cstring(SpaceIndex:strlen) - strlen = strlen - 1 ! Last character is still C_NULL_CHAR - end if - SpaceIndex = SpaceIndex + 1 - end do - ! Now handle the last argument - argv(argnum) = C_loc(Cstring(StringStart)) - - end subroutine Cstring2argcargv - -!----------------------------------------------------------------------------- - - function Cdoublestar_to_2darray (Carray, nrows, ncolumns) result (Farray) - - ! Take a C/C++ array of pointers to pointers to doubles (sort of like a - ! two-dimensional array, and handled the same way from the programmer's - ! perspective) into a Fortran-style array. Note that columns in C still - ! correspond to columns in Fortran here and the same for rows. - - type (C_ptr), intent(in) :: Carray - integer, intent(in) :: nrows, ncolumns - double precision, dimension(nrows, ncolumns) :: Farray - type (C_ptr), dimension(:), pointer :: C_rows - real (C_double), dimension(:), pointer :: F_row - integer :: i - - ! Convert each "C row pointer" into an array of rows - call C_F_pointer (Carray, C_rows, (/nrows/)) - do i = 1, nrows - ! Convert each C pointer (an entire row) into a Fortran pointer - call C_F_pointer (C_rows(i), F_row, (/ncolumns/)) - Farray (i,:) = real(F_row, kind(0.0D0)) - end do - - end function Cdoublestar_to_2darray -! 1}}} - -end module LAMMPS - -! vim: foldmethod=marker ts=3 sts=3 expandtab +!! ----------------------------------------------------------------------- +! LAMMPS - Large-scale Atomic/Molecular Massively Parallel Simulator +! www.cs.sandia.gov/~sjplimp/lammps.html +! Steve Plimpton, sjplimp@sandia.gov, Sandia National Laboratories +! +! Copyright (2003) Sandia Corporation. Under the terms of Contract +! DE-AC04-94AL85000 with Sandia Corporation, the U.S. Government retains +! certain rights in this software. This software is distributed under +! the GNU General Public License. +! +! See the README file in the top-level LAMMPS directory. +!-------------------------------------------------------------------------- + +!! ------------------------------------------------------------------------ +! Contributing author: Karl D. Hammond +! University of Tennessee, Knoxville (USA), 2012 +!-------------------------------------------------------------------------- + +!! LAMMPS, a Fortran 2003 module containing an interface between Fortran +!! programs and the C-style functions in library.cpp that ship with LAMMPS. +!! This file should be accompanied by LAMMPS-wrapper.cpp and LAMMPS-wrapper.h, +!! which define wrapper functions that ease portability and enforce array +!! dimensions. +!! +!! Everything in this module should be 100% portable by way of Fortran 2003's +!! ISO_C_BINDING intrinsic module. See the README for instructions for +!! compilation and use. +!! +!! Here are the PUBLIC functions and subroutines included in this module. +!! subroutine lammps_open (command_line, communicator, ptr) +!! subroutine lammps_open_no_mpi (command_line, ptr) +!! subroutine lammps_close (ptr) +!! subroutine lammps_file (ptr, str) +!! subroutine lammps_command (ptr, str) +!! subroutine lammps_free (ptr) +!! subroutine lammps_extract_global (global, ptr, name) +!! subroutine lammps_extract_atom (atom, ptr, name) +!! subroutine lammps_extract_fix (fix, ptr, id, style, type, i, j) +!! subroutine lammps_extract_compute (compute, ptr, id, style, type) +!! subroutine lammps_extract_variable (variable, ptr, name, group) +!! function lammps_get_natoms (ptr) +!! subroutine lammps_gather_atoms (ptr, name, count, data) +!! subroutine lammps_scatter_atoms (ptr, name, data) + +#define FLERR __FILE__,__LINE__ +! The above line allows for similar error checking as is done with standard +! LAMMPS files. + +module LAMMPS + + use, intrinsic :: ISO_C_binding, only : C_double, C_int, C_ptr, C_char, & + C_NULL_CHAR, C_loc, C_F_pointer, lammps_instance => C_ptr + implicit none + private + public :: lammps_open, lammps_open_no_mpi, lammps_close, lammps_file, & + lammps_command, lammps_free, lammps_extract_global, & + lammps_extract_atom, lammps_extract_compute, lammps_extract_fix, & + lammps_extract_variable, lammps_get_natoms, lammps_gather_atoms, & + lammps_scatter_atoms + public :: lammps_instance + + !! Functions supplemental to the prototypes in library.h. {{{1 + !! The function definitions (in C++) are contained in LAMMPS-wrapper.cpp. + !! I would have written the first in Fortran, but the MPI libraries (which + !! were written in C) have C-based functions to convert from Fortran MPI + !! handles to C MPI handles, and there is no Fortran equivalent for those + !! functions. + interface + subroutine lammps_open_wrapper (argc, argv, communicator, ptr) & + bind (C, name='lammps_open_fortran_wrapper') + import :: C_int, C_ptr + integer (C_int), value :: argc + type (C_ptr), dimension(*) :: argv + integer, value :: communicator + type (C_ptr) :: ptr + end subroutine lammps_open_wrapper + subroutine lammps_actual_error_all (ptr, file, line, str) & + bind (C, name='lammps_error_all') + import :: C_int, C_char, C_ptr + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*), intent(in) :: file, str + integer (C_int), value :: line + end subroutine lammps_actual_error_all + function lammps_get_ntypes (ptr) result (ntypes) & + bind (C, name='lammps_get_ntypes') + import :: C_int, C_ptr + type (C_ptr), value :: ptr + integer (C_int) :: ntypes + end function lammps_get_ntypes + function lammps_actual_extract_compute_vectorsize (ptr, id, style) & + result (vectorsize) bind (C, name='lammps_extract_compute_vectorsize') + import :: C_int, C_char, C_ptr + integer (C_int) :: vectorsize + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*) :: id + integer (C_int), value :: style + end function lammps_actual_extract_compute_vectorsize + subroutine lammps_actual_extract_compute_arraysize (ptr, id, style, & + nrows, ncols) bind (C, name='lammps_extract_compute_arraysize') + import :: C_int, C_char, C_ptr + integer (C_int) :: arraysize + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*) :: id + integer (C_int), value :: style + integer (C_int) :: nrows, ncols + end subroutine lammps_actual_extract_compute_arraysize + function lammps_actual_extract_fix_vectorsize (ptr, id, style) & + result (vectorsize) bind (C, name='lammps_extract_fix_vectorsize') + import :: C_int, C_char, C_ptr + integer (C_int) :: vectorsize + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*) :: id + integer (C_int), value :: style + end function lammps_actual_extract_fix_vectorsize + subroutine lammps_actual_extract_fix_arraysize (ptr, id, style, & + nrows, ncols) bind (C, name='lammps_extract_fix_arraysize') + import :: C_int, C_char, C_ptr + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*) :: id + integer (C_int), value :: style + integer (C_int) :: nrows, ncols + end subroutine lammps_actual_extract_fix_arraysize + end interface + + !! Functions/subroutines defined in library.h and library.cpp {{{1 + interface + subroutine lammps_actual_open_no_mpi (argc, argv, ptr) & + bind (C, name='lammps_open_no_mpi') + import :: C_int, C_ptr + integer (C_int), value :: argc + type (C_ptr), dimension(*) :: argv + type (C_ptr) :: ptr + end subroutine lammps_actual_open_no_mpi + + subroutine lammps_close (ptr) bind (C, name='lammps_close') + import :: C_ptr + type (C_ptr), value :: ptr + end subroutine lammps_close + + subroutine lammps_actual_file (ptr, str) bind (C, name='lammps_file') + import :: C_ptr, C_char + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*) :: str + end subroutine lammps_actual_file + + function lammps_actual_command (ptr, str) result (command) & + bind (C, name='lammps_command') + import :: C_ptr, C_char + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*) :: str + type (C_ptr) :: command + end function lammps_actual_command + + subroutine lammps_free (ptr) bind (C, name='lammps_free') + import :: C_ptr + type (C_ptr), value :: ptr + end subroutine lammps_free + + function lammps_actual_extract_global (ptr, name) & + bind (C, name='lammps_extract_global') result (global) + import :: C_ptr, C_char + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*) :: name + type (C_ptr) :: global + end function lammps_actual_extract_global + + function lammps_actual_extract_atom (ptr, name) & + bind (C, name='lammps_extract_atom') result (atom) + import :: C_ptr, C_char + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*) :: name + type (C_ptr) :: atom + end function lammps_actual_extract_atom + + function lammps_actual_extract_compute (ptr, id, style, type) & + result (compute) bind (C, name='lammps_extract_compute') + import :: C_ptr, C_char, C_int + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*) :: id + integer (C_int), value :: style, type + type (C_ptr) :: compute + end function lammps_actual_extract_compute + + function lammps_actual_extract_fix (ptr, id, style, type, i, j) & + result (fix) bind (C, name='lammps_extract_fix') + import :: C_ptr, C_char, C_int + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*) :: id + integer (C_int), value :: style, type, i, j + type (C_ptr) :: fix + end function lammps_actual_extract_fix + + function lammps_actual_extract_variable (ptr, name, group) & + result (variable) bind (C, name='lammps_extract_variable') + import :: C_ptr, C_char + type (C_ptr), value :: ptr + character (kind=C_char), dimension(*) :: name, group + type (C_ptr) :: variable + end function lammps_actual_extract_variable + + function lammps_get_natoms (ptr) result (natoms) & + bind (C, name='lammps_get_natoms') + import :: C_ptr, C_int + type (C_ptr), value :: ptr + integer (C_int) :: natoms + end function lammps_get_natoms + + subroutine lammps_actual_gather_atoms (ptr, name, type, count, data) & + bind (C, name='lammps_gather_atoms') + import :: C_ptr, C_int, C_char + type (C_ptr), value :: ptr, data + character (kind=C_char), dimension(*) :: name + integer (C_int), value :: type, count + end subroutine lammps_actual_gather_atoms + + subroutine lammps_actual_scatter_atoms (ptr, name, type, count, data) & + bind (C, name='lammps_scatter_atoms') + import :: C_ptr, C_int, C_char + type (C_ptr), value :: ptr, data + character (kind=C_char), dimension(*) :: name + integer (C_int), value :: type, count + end subroutine lammps_actual_scatter_atoms + end interface + + ! Generic functions for the wrappers below {{{1 + + ! Check the dimensions of the arrays these return; they are not always + ! easy to find. Note that I consider returning pointers to arbitrary + ! memory locations with no information as to array size/shape to be + ! extremely sloppy and error-prone. It would appear the Fortran standards + ! committee would agree, as they chose not to allow that sort of nonsense. + + interface lammps_extract_global + module procedure lammps_extract_global_i, lammps_extract_global_r, & + lammps_extract_global_dp + end interface lammps_extract_global + + interface lammps_extract_atom + module procedure lammps_extract_atom_ia, lammps_extract_atom_ra, & + lammps_extract_atom_dpa, lammps_extract_atom_dp2a, & + lammps_extract_atom_r2a + end interface lammps_extract_atom + + interface lammps_extract_compute + module procedure lammps_extract_compute_r, lammps_extract_compute_dp, & + lammps_extract_compute_ra, lammps_extract_compute_dpa, & + lammps_extract_compute_r2a, lammps_extract_compute_dp2a + end interface lammps_extract_compute + + interface lammps_extract_fix + module procedure lammps_extract_fix_r, lammps_extract_fix_dp, & + lammps_extract_fix_ra, lammps_extract_fix_dpa, & + lammps_extract_fix_r2a, lammps_extract_fix_dp2a + end interface lammps_extract_fix + + interface lammps_extract_variable + module procedure lammps_extract_variable_i, & + lammps_extract_variable_dp, & + lammps_extract_variable_r, & + lammps_extract_variable_ra, & + lammps_extract_variable_ia, & + lammps_extract_variable_dpa + end interface lammps_extract_variable + + interface lammps_gather_atoms + module procedure lammps_gather_atoms_ia, lammps_gather_atoms_dpa, & + lammps_gather_atoms_ra + end interface lammps_gather_atoms + + interface lammps_scatter_atoms + module procedure lammps_scatter_atoms_ia, lammps_scatter_atoms_dpa, & + lammps_scatter_atoms_ra + end interface lammps_scatter_atoms + +contains !! Wrapper functions local to this module {{{1 + + subroutine lammps_open (command_line, communicator, ptr) + character (len=*), intent(in) :: command_line + integer, intent(in) :: communicator + type (C_ptr) :: ptr + integer (C_int) :: argc + type (C_ptr), dimension(:), allocatable :: argv + character (kind=C_char), dimension(len_trim(command_line)+1), target :: & + c_command_line + c_command_line = string2Cstring (command_line) + call Cstring2argcargv (c_command_line, argc, argv) + call lammps_open_wrapper (argc, argv, communicator, ptr) + deallocate (argv) + end subroutine lammps_open + +!----------------------------------------------------------------------------- + + subroutine lammps_open_no_mpi (command_line, ptr) + character (len=*), intent(in) :: command_line + type (C_ptr) :: ptr + integer (C_int) :: argc + type (C_ptr), dimension(:), allocatable :: argv + character (kind=C_char), dimension(len_trim(command_line)+1), target :: & + c_command_line + c_command_line = string2Cstring (command_line) + call Cstring2argcargv (c_command_line, argc, argv) + call lammps_actual_open_no_mpi (argc, argv, ptr) + deallocate (argv) + end subroutine lammps_open_no_mpi + +!----------------------------------------------------------------------------- + + subroutine lammps_file (ptr, str) + type (C_ptr) :: ptr + character (len=*) :: str + character (kind=C_char), dimension(len_trim(str)+1) :: Cstr + Cstr = string2Cstring (str) + call lammps_actual_file (ptr, Cstr) + end subroutine lammps_file + +!----------------------------------------------------------------------------- + + subroutine lammps_command (ptr, str) + type (C_ptr) :: ptr + character (len=*) :: str + character (kind=C_char), dimension(len_trim(str)+1) :: Cstr + type (C_ptr) :: dummy + Cstr = string2Cstring (str) + dummy = lammps_actual_command (ptr, Cstr) + end subroutine lammps_command + +!----------------------------------------------------------------------------- + +! lammps_extract_global {{{2 + function lammps_extract_global_Cptr (ptr, name) result (global) + type (C_ptr) :: global + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + character (kind=C_char), dimension(len_trim(name)+1) :: Cname + Cname = string2Cstring (name) + global = lammps_actual_extract_global (ptr, Cname) + end function lammps_extract_global_Cptr + subroutine lammps_extract_global_i (global, ptr, name) + integer, intent(out) :: global + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + type (C_ptr) :: Cptr + integer (C_int), pointer :: Fptr + Cptr = lammps_extract_global_Cptr (ptr, name) + call C_F_pointer (Cptr, Fptr) + global = Fptr + nullify (Fptr) + end subroutine lammps_extract_global_i + subroutine lammps_extract_global_dp (global, ptr, name) + double precision, intent(out) :: global + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + type (C_ptr) :: Cptr + real (C_double), pointer :: Fptr + Cptr = lammps_extract_global_Cptr (ptr, name) + call C_F_pointer (Cptr, Fptr) + global = Fptr + nullify (Fptr) + end subroutine lammps_extract_global_dp + subroutine lammps_extract_global_r (global, ptr, name) + real :: global + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + type (C_ptr) :: Cptr + real (C_double), pointer :: Fptr + Cptr = lammps_extract_global_Cptr (ptr, name) + call C_F_pointer (Cptr, Fptr) + global = real (Fptr) + nullify (Fptr) + end subroutine lammps_extract_global_r + +!----------------------------------------------------------------------------- + +! lammps_extract_atom {{{2 + function lammps_extract_atom_Cptr (ptr, name) result (atom) + type (C_ptr) :: atom + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + character (kind=C_char), dimension(len_trim(name)+1) :: Cname + Cname = string2Cstring (name) + atom = lammps_actual_extract_atom (ptr, Cname) + end function lammps_extract_atom_Cptr + subroutine lammps_extract_atom_ia (atom, ptr, name) + integer, dimension(:), allocatable, intent(out) :: atom + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + type (C_ptr) :: Cptr + integer (C_int), pointer :: Fptr + integer :: natoms + natoms = lammps_get_natoms (ptr) + allocate (atom(natoms)) + Cptr = lammps_extract_atom_Cptr (ptr, name) + call C_F_pointer (Cptr, Fptr, (/natoms/)) + atom = Fptr + nullify (Fptr) + end subroutine lammps_extract_atom_ia + subroutine lammps_extract_atom_dpa (atom, ptr, name) + double precision, dimension(:), allocatable, intent(out) :: atom + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + type (C_ptr) :: Cptr + real (C_double), dimension(:), pointer :: Fptr + integer :: nelements + if ( name == 'mass' ) then + nelements = lammps_get_ntypes (ptr) + else if ( name == 'x' .or. name == 'v' .or. name == 'f' ) then + ! We should not be getting 'x' or 'v' or 'f' here! + call lammps_error_all (ptr, FLERR, 'You cannot extract those atom& + & data (x, v, or f) into a rank 1 array.') + return + else + ! Everything else we can get is probably nlocal units long + call lammps_extract_global_i (nelements, ptr, 'nlocal') + end if + allocate (atom(nelements)) + Cptr = lammps_extract_atom_Cptr (ptr, name) + if ( name == 'mass' ) then + call C_F_pointer (Cptr, Fptr, (/nelements + 1/)) + atom = Fptr(2:) ! LAMMPS starts numbering at 1 (C does not) + else + call C_F_pointer (Cptr, Fptr, (/nelements/)) + atom = Fptr + end if + nullify (Fptr) + end subroutine lammps_extract_atom_dpa + subroutine lammps_extract_atom_ra (atom, ptr, name) + real, dimension(:), allocatable, intent(out) :: atom + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + double precision, dimension(:), allocatable :: d_atom + call lammps_extract_atom_dpa (d_atom, ptr, name) + allocate (atom(size(d_atom))) + atom = real(d_atom) + deallocate (d_atom) + end subroutine lammps_extract_atom_ra + subroutine lammps_extract_atom_dp2a (atom, ptr, name) + double precision, dimension(:,:), allocatable, intent(out) :: atom + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + type (C_ptr) :: Cptr + integer :: nelements + if ( name /= 'x' .and. name /= 'v' .and. name /= 'f' ) then + call lammps_error_all (ptr, FLERR, 'You cannot extract ' // name // & + ' into a rank 2 array.') + return + end if + Cptr = lammps_extract_atom_Cptr (ptr, name) + nelements = lammps_get_natoms (ptr) + allocate (atom(nelements,3)) + atom = Cdoublestar_to_2darray (Cptr, nelements, 3) + end subroutine lammps_extract_atom_dp2a + subroutine lammps_extract_atom_r2a (atom, ptr, name) + real, dimension(:,:), allocatable, intent(out) :: atom + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + double precision, dimension(:,:), allocatable :: d_atom + call lammps_extract_atom_dp2a (d_atom, ptr, name) + if ( allocated (d_atom) ) then + allocate (atom(size(d_atom,1), size(d_atom,2))) + else + return + end if + atom = real(d_atom) + deallocate (d_atom) + end subroutine lammps_extract_atom_r2a + +!----------------------------------------------------------------------------- + +! lammps_extract_compute {{{2 + function lammps_extract_compute_Cptr (ptr, id, style, type) result (compute) + type (C_ptr) :: compute + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type + integer (kind=C_int) :: Cstyle, Ctype + character (kind=C_char), dimension(len_trim(id)+1) :: Cid + Cid = string2Cstring (id) + Cstyle = style + Ctype = type + compute = lammps_actual_extract_compute (ptr, Cid, Cstyle, Ctype) + end function lammps_extract_compute_Cptr + subroutine lammps_extract_compute_dp (compute, ptr, id, style, type) + double precision, intent(out) :: compute + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type + type (C_ptr) :: Cptr + real (C_double), pointer :: Fptr + ! The only valid values of (style,type) are (0,0) for scalar 'compute' + if ( style /= 0 ) then + call lammps_error_all (ptr, FLERR, 'You cannot pack per-atom/local& + & data into a scalar.') + return + end if + if ( type == 1 ) then + call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& + & vector (rank 1) into a scalar.') + return + else if ( type == 2 ) then + call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& + & array (rank 2) into a scalar.') + return + end if + Cptr = lammps_extract_compute_Cptr (ptr, id, style, type) + call C_F_pointer (Cptr, Fptr) + compute = Fptr + nullify (Fptr) + ! C pointer should not be freed! + end subroutine lammps_extract_compute_dp + subroutine lammps_extract_compute_r (compute, ptr, id, style, type) + real, intent(out) :: compute + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type + double precision :: d_compute + call lammps_extract_compute_dp (d_compute, ptr, id, style, type) + compute = real(d_compute) + end subroutine lammps_extract_compute_r + subroutine lammps_extract_compute_dpa (compute, ptr, id, style, type) + double precision, dimension(:), allocatable, intent(out) :: compute + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type + type (C_ptr) :: Cptr + real (C_double), dimension(:), pointer :: Fptr + integer :: nelements + ! Check for the correct dimensionality + if ( type == 0 ) then + call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& + & scalar (rank 0) into a rank 1 variable.') + return + else if ( type == 2 ) then + call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& + & array (rank 2) into a rank 1 variable.') + return + end if + nelements = lammps_extract_compute_vectorsize (ptr, id, style) + allocate (compute(nelements)) + Cptr = lammps_extract_compute_Cptr (ptr, id, style, type) + call C_F_pointer (Cptr, Fptr, (/nelements/)) + compute = Fptr + nullify (Fptr) + ! C pointer should not be freed + end subroutine lammps_extract_compute_dpa + subroutine lammps_extract_compute_ra (compute, ptr, id, style, type) + real, dimension(:), allocatable, intent(out) :: compute + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type + double precision, dimension(:), allocatable :: d_compute + call lammps_extract_compute_dpa (d_compute, ptr, id, style, type) + allocate (compute(size(d_compute))) + compute = real(d_compute) + deallocate (d_compute) + end subroutine lammps_extract_compute_ra + subroutine lammps_extract_compute_dp2a (compute, ptr, id, style, type) + double precision, dimension(:,:), allocatable, intent(out) :: compute + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type + type (C_ptr) :: Cptr + real (C_double), dimension(:,:), pointer :: Fptr + integer :: nr, nc + ! Check for the correct dimensionality + if ( type == 0 ) then + call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& + & scalar (rank 0) into a rank 2 variable.') + return + else if ( type == 1 ) then + call lammps_error_all (ptr, FLERR, 'You cannot extract a compute& + & array (rank 1) into a rank 2 variable.') + return + end if + call lammps_extract_compute_arraysize (ptr, id, style, nr, nc) + allocate (compute(nr, nc)) + Cptr = lammps_extract_compute_Cptr (ptr, id, style, type) + call C_F_pointer (Cptr, Fptr, (/nr, nc/)) + compute = Fptr + nullify (Fptr) + ! C pointer should not be freed + end subroutine lammps_extract_compute_dp2a + subroutine lammps_extract_compute_r2a (compute, ptr, id, style, type) + real, dimension(:,:), allocatable, intent(out) :: compute + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type + double precision, dimension(:,:), allocatable :: d_compute + call lammps_extract_compute_dp2a (d_compute, ptr, id, style, type) + allocate (compute(size(d_compute,1), size(d_compute,2))) + compute = real(d_compute) + deallocate (d_compute) + end subroutine lammps_extract_compute_r2a + +!----------------------------------------------------------------------------- + +! lammps_extract_fix {{{2 + function lammps_extract_fix_Cptr (ptr, id, style, type, i, j) & + result (fix) + type (C_ptr) :: fix + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type, i, j + character (kind=C_char), dimension(len_trim(id)+1) :: Cid + integer (kind=C_int) :: Cstyle, Ctype, Ci, Cj + Cid = string2Cstring (id) + Cstyle = style + Ctype = type + Ci = i - 1 ! This is for consistency with the values from f_ID[i], + Cj = j - 1 ! which is different from what library.cpp uses! + if ( (type >= 1 .and. Ci < 0) .or. & + (type == 2 .and. (Ci < 0 .or. Cj < 0) ) ) then + call lammps_error_all (ptr, FLERR, 'Index out of range in& + & lammps_extract_fix') + end if + fix = lammps_actual_extract_fix (ptr, Cid, Cstyle, Ctype, Ci, Cj) + end function lammps_extract_fix_Cptr + subroutine lammps_extract_fix_dp (fix, ptr, id, style, type, i, j) + double precision, intent(out) :: fix + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type, i, j + type (C_ptr) :: Cptr + real (C_double), pointer :: Fptr + ! Check for the correct dimensionality + if ( style /= 0 ) then + select case (type) + case (0) + call lammps_error_all (ptr, FLERR, 'There is no per-atom or local& + & scalar data available from fixes.') + case (1) + call lammps_error_all (ptr, FLERR, 'You cannot extract a fix''s & + &per-atom/local vector (rank 1) into a scalar.') + case (2) + call lammps_error_all (ptr, FLERR, 'You cannot extract a fix''s & + &per-atom/local array (rank 2) into a scalar.') + case default + call lammps_error_all (ptr, FLERR, 'Invalid extract_fix style& + & value.') + end select + return + end if + Cptr = lammps_extract_fix_Cptr (ptr, id, style, type, i, j) + call C_F_pointer (Cptr, Fptr) + fix = Fptr + nullify (Fptr) + ! Memory is only allocated for "global" fix variables + if ( style == 0 ) call lammps_free (Cptr) + end subroutine lammps_extract_fix_dp + subroutine lammps_extract_fix_r (fix, ptr, id, style, type, i, j) + real, intent(out) :: fix + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type, i, j + double precision :: d_fix + call lammps_extract_fix_dp (d_fix, ptr, id, style, type, i, j) + fix = real(d_fix) + end subroutine lammps_extract_fix_r + subroutine lammps_extract_fix_dpa (fix, ptr, id, style, type, i, j) + double precision, dimension(:), allocatable, intent(out) :: fix + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type, i, j + type (C_ptr) :: Cptr + real (C_double), dimension(:), pointer :: Fptr + integer :: fix_len + ! Check for the correct dimensionality + if ( style == 0 ) then + call lammps_error_all (ptr, FLERR, 'You can''t extract the& + & whole vector from global fix data') + return + else if ( type == 0 ) then + call lammps_error_all (ptr, FLERR, 'You can''t extract a fix& + & scalar into a rank 1 variable') + return + else if ( type == 2 ) then + call lammps_error_all (ptr, FLERR, 'You cannot extract a fix& + & array into a rank 1 variable.') + return + else if ( type /= 1 ) then + call lammps_error_all (ptr, FLERR, 'Invalid type for fix extraction.') + return + end if + fix_len = lammps_extract_fix_vectorsize (ptr, id, style) + allocate (fix(fix_len)) + Cptr = lammps_extract_fix_Cptr (ptr, id, style, type, i, j) + call C_F_pointer (Cptr, Fptr, (/fix_len/)) + fix = Fptr + nullify (Fptr) + ! Memory is only allocated for "global" fix variables + if ( style == 0 ) call lammps_free (Cptr) + end subroutine lammps_extract_fix_dpa + subroutine lammps_extract_fix_ra (fix, ptr, id, style, type, i, j) + real, dimension(:), allocatable, intent(out) :: fix + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type, i, j + double precision, dimension(:), allocatable :: d_fix + call lammps_extract_fix_dpa (d_fix, ptr, id, style, type, i, j) + allocate (fix(size(d_fix))) + fix = real(d_fix) + deallocate (d_fix) + end subroutine lammps_extract_fix_ra + subroutine lammps_extract_fix_dp2a (fix, ptr, id, style, type, i, j) + double precision, dimension(:,:), allocatable, intent(out) :: fix + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type, i, j + type (C_ptr) :: Cptr + real (C_double), dimension(:,:), pointer :: Fptr + integer :: nr, nc + ! Check for the correct dimensionality + if ( style == 0 ) then + call lammps_error_all (ptr, FLERR, 'It is not possible to extract the& + & entire array from global fix data.') + return + else if ( type == 0 ) then + call lammps_error_all (ptr, FLERR, 'You cannot extract a fix& + & scalar (rank 0) into a rank 2 variable.') + return + else if ( type == 1 ) then + call lammps_error_all (ptr, FLERR, 'You cannot extract a fix& + & vector (rank 1) into a rank 2 variable.') + return + end if + call lammps_extract_fix_arraysize (ptr, id, style, nr, nc) + allocate (fix(nr, nc)) + Cptr = lammps_extract_fix_Cptr (ptr, id, style, type, i, j) + call C_F_pointer (Cptr, Fptr, (/nr, nc/)) + fix = Fptr + nullify (Fptr) + ! C pointer should not be freed + end subroutine lammps_extract_fix_dp2a + subroutine lammps_extract_fix_r2a (fix, ptr, id, style, type, i, j) + real, dimension(:,:), allocatable, intent(out) :: fix + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style, type, i, j + double precision, dimension(:,:), allocatable :: d_fix + call lammps_extract_fix_dp2a (d_fix, ptr, id, style, type, i, j) + allocate (fix(size(d_fix,1), size(d_fix,2))) + fix = real(d_fix) + deallocate (d_fix) + end subroutine lammps_extract_fix_r2a + +!----------------------------------------------------------------------------- + +! lammps_extract_variable {{{2 + function lammps_extract_variable_Cptr (ptr, name, group) result (variable) + type (C_ptr) :: ptr, variable + character (len=*) :: name + character (len=*), optional :: group + character (kind=C_char), dimension(len_trim(name)+1) :: Cname + character (kind=C_char), dimension(:), allocatable :: Cgroup + Cname = string2Cstring (name) + if ( present(group) ) then + allocate (Cgroup(len_trim(group)+1)) + Cgroup = string2Cstring (group) + else + allocate (Cgroup(1)) + Cgroup(1) = C_NULL_CHAR + end if + variable = lammps_actual_extract_variable (ptr, Cname, Cgroup) + deallocate (Cgroup) + end function lammps_extract_variable_Cptr + subroutine lammps_extract_variable_i (variable, ptr, name, group) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + character (len=*), intent(in), optional :: group + integer, intent(out) :: variable + type (C_ptr) :: Cptr + integer (C_int), pointer :: Fptr + if ( present(group) ) then + Cptr = lammps_extract_variable_Cptr (ptr, name, group) + else + Cptr = lammps_extract_variable_Cptr (ptr, name) + end if + call C_F_pointer (Cptr, Fptr) + variable = Fptr + nullify (Fptr) + call lammps_free (Cptr) + end subroutine lammps_extract_variable_i + subroutine lammps_extract_variable_dp (variable, ptr, name, group) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + character (len=*), intent(in), optional :: group + double precision, intent(out) :: variable + type (C_ptr) :: Cptr + real (C_double), pointer :: Fptr + if ( present(group) ) then + Cptr = lammps_extract_variable_Cptr (ptr, name, group) + else + Cptr = lammps_extract_variable_Cptr (ptr, name) + end if + call C_F_pointer (Cptr, Fptr) + variable = Fptr + nullify (Fptr) + call lammps_free (Cptr) + end subroutine lammps_extract_variable_dp + subroutine lammps_extract_variable_r (variable, ptr, name, group) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + character (len=*), intent(in), optional :: group + real, intent(out) :: variable + double precision :: d_var + if ( present (group) ) then + call lammps_extract_variable_dp (d_var, ptr, name, group) + else + call lammps_extract_variable_dp (d_var, ptr, name) + end if + variable = real(d_var) + end subroutine lammps_extract_variable_r + + subroutine lammps_extract_variable_ia (variable, ptr, name, group) + integer, dimension(:), allocatable, intent(out) :: variable + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + character (len=*), intent(in), optional :: group + type (C_ptr) :: Cptr + integer (C_int), dimension(:), pointer :: Fptr + integer :: natoms + nullify (Fptr) + if ( present(group) ) then + Cptr = lammps_extract_variable_Cptr (ptr, name, group) + else + Cptr = lammps_extract_variable_Cptr (ptr, name) + end if + natoms = lammps_get_natoms (ptr) + allocate (variable(natoms)) + call C_F_pointer (Cptr, Fptr, (/natoms/)) + variable = Fptr + nullify (Fptr) + call lammps_free (Cptr) + end subroutine lammps_extract_variable_ia + subroutine lammps_extract_variable_dpa (variable, ptr, name, group) + double precision, dimension(:), allocatable, intent(out) :: variable + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + character (len=*), intent(in), optional :: group + type (C_ptr) :: Cptr + real (C_double), dimension(:), pointer :: Fptr + integer :: natoms + if ( present(group) ) then + Cptr = lammps_extract_variable_Cptr (ptr, name, group) + else + Cptr = lammps_extract_variable_Cptr (ptr, name) + end if + natoms = lammps_get_natoms (ptr) + allocate (variable(natoms)) + call C_F_pointer (Cptr, Fptr, (/natoms/)) + variable = Fptr + nullify (Fptr) + call lammps_free (Cptr) + end subroutine lammps_extract_variable_dpa + subroutine lammps_extract_variable_ra (variable, ptr, name, group) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + character (len=*), intent(in), optional :: group + real, dimension(:), allocatable, intent(out) :: variable + double precision, dimension(:), allocatable :: d_var + if ( present (group) ) then + call lammps_extract_variable_dpa (d_var, ptr, name, group) + else + call lammps_extract_variable_dpa (d_var, ptr, name) + end if + allocate (variable(size(d_var))) + variable = real(d_var) + deallocate (d_var) + end subroutine lammps_extract_variable_ra + +!-------------------------------------------------------------------------2}}} + + subroutine lammps_gather_atoms_ia (ptr, name, count, data) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + integer, intent(in) :: count + integer, dimension(:), allocatable, intent(out) :: data + type (C_ptr) :: Cdata + integer (C_int), dimension(:), pointer :: Fdata + integer (C_int) :: natoms + character (kind=C_char), dimension(len_trim(name)) :: Cname + integer (C_int), parameter :: Ctype = 0 + integer (C_int) :: Ccount + natoms = lammps_get_natoms (ptr) + Cname = string2Cstring (name) + if ( count /= 1 .and. count /= 3 ) then + call lammps_error_all (ptr, FLERR, 'lammps_gather_atoms requires& + & count to be either 1 or 3') + else + Ccount = count + end if + allocate ( Fdata(count*natoms) ) + allocate ( data(count*natoms) ) + Cdata = C_loc (Fdata(1)) + call lammps_actual_gather_atoms (ptr, Cname, Ctype, Ccount, Cdata) + data = Fdata + deallocate (Fdata) + end subroutine lammps_gather_atoms_ia + subroutine lammps_gather_atoms_dpa (ptr, name, count, data) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + integer, intent(in) :: count + double precision, dimension(:), allocatable, intent(out) :: data + type (C_ptr) :: Cdata + real (C_double), dimension(:), pointer :: Fdata + integer (C_int) :: natoms + character (kind=C_char), dimension(len_trim(name)) :: Cname + integer (C_int), parameter :: Ctype = 1 + integer (C_int) :: Ccount + natoms = lammps_get_natoms (ptr) + Cname = string2Cstring (name) + if ( count /= 1 .and. count /= 3 ) then + call lammps_error_all (ptr, FLERR, 'lammps_gather_atoms requires& + & count to be either 1 or 3') + else + Ccount = count + end if + allocate ( Fdata(count*natoms) ) + allocate ( data(count*natoms) ) + Cdata = C_loc (Fdata(1)) + call lammps_actual_gather_atoms (ptr, Cname, Ctype, Ccount, Cdata) + data = Fdata(:) + deallocate (Fdata) + end subroutine lammps_gather_atoms_dpa + subroutine lammps_gather_atoms_ra (ptr, name, count, data) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + integer, intent(in) :: count + real, dimension(:), allocatable, intent(out) :: data + double precision, dimension(:), allocatable :: d_data + call lammps_gather_atoms_dpa (ptr, name, count, d_data) + allocate (data(size(d_data))) + data = d_data + deallocate (d_data) + end subroutine lammps_gather_atoms_ra + +!----------------------------------------------------------------------------- + + subroutine lammps_scatter_atoms_ia (ptr, name, data) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + integer, dimension(:), intent(in) :: data + integer (kind=C_int) :: natoms, Ccount + integer (kind=C_int), parameter :: Ctype = 0 + character (kind=C_char), dimension(len_trim(name)) :: Cname + integer, dimension(size(data)), target :: Fdata + type (C_ptr) :: Cdata + natoms = lammps_get_natoms (ptr) + Cname = string2Cstring (name) + Ccount = size(data) / natoms + if ( Ccount /= 1 .and. Ccount /= 3 ) & + call lammps_error_all (ptr, FLERR, 'lammps_gather_atoms requires& + & count to be either 1 or 3') + Fdata = data + Cdata = C_loc (Fdata(1)) + call lammps_actual_scatter_atoms (ptr, Cname, Ctype, Ccount, Cdata) + end subroutine lammps_scatter_atoms_ia + subroutine lammps_scatter_atoms_dpa (ptr, name, data) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + double precision, dimension(:), intent(in) :: data + integer (kind=C_int) :: natoms, Ccount + integer (kind=C_int), parameter :: Ctype = 0 + character (kind=C_char), dimension(len_trim(name)) :: Cname + double precision, dimension(size(data)), target :: Fdata + type (C_ptr) :: Cdata + natoms = lammps_get_natoms (ptr) + Cname = string2Cstring (name) + Ccount = size(data) / natoms + if ( Ccount /= 1 .and. Ccount /= 3 ) & + call lammps_error_all (ptr, FLERR, 'lammps_gather_atoms requires& + & count to be either 1 or 3') + Fdata = data + Cdata = C_loc (Fdata(1)) + call lammps_actual_scatter_atoms (ptr, Cname, Ctype, Ccount, Cdata) + end subroutine lammps_scatter_atoms_dpa + subroutine lammps_scatter_atoms_ra (ptr, name, data) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: name + real, dimension(:), intent(out) :: data + double precision, dimension(size(data)) :: d_data + d_data = real (data, kind(d_data)) + call lammps_scatter_atoms_dpa (ptr, name, d_data) + end subroutine lammps_scatter_atoms_ra + +!----------------------------------------------------------------------------- + +! subroutine lammps_get_coords (ptr, coords) +! type (C_ptr) :: ptr +! double precision, dimension(:), allocatable, intent(out) :: coords +! real (C_double), dimension(:), allocatable, target :: C_coords +! integer :: natoms +! natoms = lammps_get_natoms (ptr) +! allocate (coords(3*natoms)) +! allocate (C_coords(3*natoms)) +! call lammps_actual_get_coords (ptr, C_loc(C_coords)) +! coords = C_coords +! deallocate (C_coords) +! end subroutine lammps_get_coords +! +!!----------------------------------------------------------------------------- +! +! subroutine lammps_put_coords (ptr, coords) +! type (C_ptr) :: ptr +! double precision, dimension(:) :: coords +! real (C_double), dimension(size(coords)) :: C_coords +! C_coords = coords +! call lammps_actual_put_coords (ptr, C_coords) +! end subroutine lammps_put_coords +! +!!----------------------------------------------------------------------------- + + function lammps_extract_compute_vectorsize (ptr, id, style) & + result (vectorsize) + integer :: vectorsize + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style + integer (C_int) :: Cvectorsize, Cstyle + character (kind=C_char), dimension(len_trim(id)+1) :: Cid + Cid = string2Cstring (id) + Cstyle = int(style, C_int) + Cvectorsize = lammps_actual_extract_compute_vectorsize (ptr, Cid, Cstyle) + vectorsize = int(Cvectorsize, kind(vectorsize)) + end function lammps_extract_compute_vectorsize + +!----------------------------------------------------------------------------- + + function lammps_extract_fix_vectorsize (ptr, id, style) & + result (vectorsize) + integer :: vectorsize + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style + integer (C_int) :: Cvectorsize, Cstyle + character (kind=C_char), dimension(len_trim(id)+1) :: Cid + Cid = string2Cstring (id) + Cstyle = int(style, C_int) + Cvectorsize = lammps_actual_extract_fix_vectorsize (ptr, Cid, Cstyle) + vectorsize = int(Cvectorsize, kind(vectorsize)) + end function lammps_extract_fix_vectorsize + +!----------------------------------------------------------------------------- + + subroutine lammps_extract_compute_arraysize (ptr, id, style, nrows, ncols) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style + integer, intent(out) :: nrows, ncols + integer (C_int) :: Cstyle, Cnrows, Cncols + character (kind=C_char), dimension(len_trim(id)+1) :: Cid + Cid = string2Cstring (id) + Cstyle = int (style, C_int) + call lammps_actual_extract_compute_arraysize (ptr, Cid, Cstyle, & + Cnrows, Cncols) + nrows = int (Cnrows, kind(nrows)) + ncols = int (Cncols, kind(ncols)) + end subroutine lammps_extract_compute_arraysize + +!----------------------------------------------------------------------------- + + subroutine lammps_extract_fix_arraysize (ptr, id, style, nrows, ncols) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: id + integer, intent(in) :: style + integer, intent(out) :: nrows, ncols + integer (C_int) :: Cstyle, Cnrows, Cncols + character (kind=C_char), dimension(len_trim(id)+1) :: Cid + Cid = string2Cstring (id) + Cstyle = int (style, kind(Cstyle)) + call lammps_actual_extract_fix_arraysize (ptr, Cid, Cstyle, & + Cnrows, Cncols) + nrows = int (Cnrows, kind(nrows)) + ncols = int (Cncols, kind(ncols)) + end subroutine lammps_extract_fix_arraysize + +!----------------------------------------------------------------------------- + + subroutine lammps_error_all (ptr, file, line, str) + type (C_ptr), intent(in) :: ptr + character (len=*), intent(in) :: file, str + integer, intent(in) :: line + character (kind=C_char), dimension(len_trim(file)+1) :: Cfile + character (kind=C_char), dimension(len_trim(str)+1) :: Cstr + integer (C_int) :: Cline + Cline = int(line, kind(Cline)) + Cfile = string2Cstring (file) + Cstr = string2Cstring (str) + call lammps_actual_error_all (ptr, Cfile, Cline, Cstr) + end subroutine lammps_error_all + +!----------------------------------------------------------------------------- + +! Locally defined helper functions {{{1 + + pure function string2Cstring (string) result (C_string) + use, intrinsic :: ISO_C_binding, only : C_char, C_NULL_CHAR + character (len=*), intent(in) :: string + character (len=1, kind=C_char) :: C_string (len_trim(string)+1) + integer :: i, n + n = len_trim (string) + forall (i = 1:n) + C_string(i) = string(i:i) + end forall + C_string(n+1) = C_NULL_CHAR + end function string2Cstring + +!----------------------------------------------------------------------------- + + subroutine Cstring2argcargv (Cstring, argc, argv) + !! Converts a C-style string to argc and argv, that is, words in Cstring + !! become C-style strings in argv. IMPORTANT: Cstring is modified by + !! this routine! I would make Cstring local TO this routine and accept + !! a Fortran-style string instead, but we run into scoping and + !! allocation problems that way. This routine assumes the string is + !! null-terminated, as all C-style strings must be. + + character (kind=C_char), dimension(*), target, intent(inout) :: Cstring + integer (C_int), intent(out) :: argc + type (C_ptr), dimension(:), allocatable, intent(out) :: argv + + integer :: StringStart, SpaceIndex, strlen, argnum + + argc = 1_C_int + + ! Find the length of the string + strlen = 1 + do while ( Cstring(strlen) /= C_NULL_CHAR ) + strlen = strlen + 1 + end do + + ! Find the number of non-escaped spaces + SpaceIndex = 2 + do while ( SpaceIndex < strlen ) + if ( Cstring(SpaceIndex) == ' ' .and. & + Cstring(SpaceIndex-1) /= '\' ) then + argc = argc + 1_C_int + ! Find the next non-space character + do while ( Cstring(SpaceIndex+1) == ' ') + SpaceIndex = SpaceIndex + 1 + end do + end if + SpaceIndex = SpaceIndex + 1 + end do + + ! Now allocate memory for argv + allocate (argv(argc)) + + ! Now find the string starting and ending locations + StringStart = 1 + SpaceIndex = 2 + argnum = 1 + do while ( SpaceIndex < strlen ) + if ( Cstring(SpaceIndex) == ' ' .and. & + Cstring(SpaceIndex-1) /= '\' ) then + ! Found a real space => split strings and store this one + Cstring(Spaceindex) = C_NULL_CHAR ! Replaces space with NULL + argv(argnum) = C_loc(Cstring(StringStart)) + argnum = argnum + 1 + ! Find the next non-space character + do while ( Cstring(SpaceIndex+1) == ' ') + SpaceIndex = SpaceIndex + 1 + end do + StringStart = SpaceIndex + 1 + else if ( Cstring(SpaceIndex) == ' ' .and. & + Cstring(SpaceIndex-1) == '\' ) then + ! Escaped space => remove backslash and move rest of array + Cstring(SpaceIndex-1:strlen-1) = Cstring(SpaceIndex:strlen) + strlen = strlen - 1 ! Last character is still C_NULL_CHAR + end if + SpaceIndex = SpaceIndex + 1 + end do + ! Now handle the last argument + argv(argnum) = C_loc(Cstring(StringStart)) + + end subroutine Cstring2argcargv + +!----------------------------------------------------------------------------- + + function Cdoublestar_to_2darray (Carray, nrows, ncolumns) result (Farray) + + ! Take a C/C++ array of pointers to pointers to doubles (sort of like a + ! two-dimensional array, and handled the same way from the programmer's + ! perspective) into a Fortran-style array. Note that columns in C still + ! correspond to columns in Fortran here and the same for rows. + + type (C_ptr), intent(in) :: Carray + integer, intent(in) :: nrows, ncolumns + double precision, dimension(nrows, ncolumns) :: Farray + type (C_ptr), dimension(:), pointer :: C_rows + real (C_double), dimension(:), pointer :: F_row + integer :: i + + ! Convert each "C row pointer" into an array of rows + call C_F_pointer (Carray, C_rows, (/nrows/)) + do i = 1, nrows + ! Convert each C pointer (an entire row) into a Fortran pointer + call C_F_pointer (C_rows(i), F_row, (/ncolumns/)) + Farray (i,:) = real(F_row, kind(0.0D0)) + end do + + end function Cdoublestar_to_2darray +! 1}}} + +end module LAMMPS + +! vim: foldmethod=marker ts=3 sts=3 expandtab diff --git a/examples/COUPLE/fortran2/README b/examples/COUPLE/fortran2/README index 4b14eefa93..03c76fb3ca 100644 --- a/examples/COUPLE/fortran2/README +++ b/examples/COUPLE/fortran2/README @@ -12,7 +12,7 @@ questions: Karl D. Hammond University of Tennessee, Knoxville karlh at ugcs.caltech.edu -karlh atutk.edu +karlh at utk.edu ------------------------------------- @@ -27,7 +27,7 @@ compile. The following steps will work to compile this module (replace ${LAMMPS_SRC} with the path to your LAMMPS source directory): (1) Compile LAMMPS as a static library. Call the resulting file ${LAMMPS_LIB}, - which will have an actual name lake liblammps_openmpi.a. If compiling + which will have an actual name lake liblmp_openmpi.a. If compiling using the MPI stubs in ${LAMMPS_SRC}/STUBS, you will need to know where libmpi.a is as well (I'll call it ${MPI_STUBS} hereafter) (2) Copy said library to your Fortran program's source directory or include @@ -61,7 +61,7 @@ with the path to your LAMMPS source directory): need to have the .mod file from part (3). It is also possible to add LAMMPS.o and LAMMPS-wrapper.o into the - LAMMPS library (e.g., liblammps_openmpi.a) instead of creating a separate + LAMMPS library (e.g., liblmp_openmpi.a) instead of creating a separate library, like so: ar rs ${LAMMPS_LIB} LAMMPS.o LAMMPS-wrapper.o In this case, you can now use the Fortran wrapper functions as if they diff --git a/examples/COUPLE/fortran2/makefile b/examples/COUPLE/fortran2/makefile index 3d13c4428e..92065d23a8 100644 --- a/examples/COUPLE/fortran2/makefile +++ b/examples/COUPLE/fortran2/makefile @@ -1,7 +1,7 @@ SHELL = /bin/sh # Path to LAMMPS extraction directory -LAMMPS_ROOT = ../svn-dist +LAMMPS_ROOT = ../../.. LAMMPS_SRC = $(LAMMPS_ROOT)/src # Remove the line below if using mpicxx/mpic++ as your C++ compiler From 448637286853f7bed49f123e150f38b036cccc26 Mon Sep 17 00:00:00 2001 From: sjplimp Date: Wed, 15 Aug 2012 14:34:23 +0000 Subject: [PATCH 02/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8670 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- python/install.py | 67 +++++++++++++++++++++++++++++------------------ 1 file changed, 42 insertions(+), 25 deletions(-) diff --git a/python/install.py b/python/install.py index 3bf2739cbc..c1e62fc853 100644 --- a/python/install.py +++ b/python/install.py @@ -1,35 +1,52 @@ -#!/usr/local/bin/python +#!/usr/bin/env python -# copy LAMMPS shared library src/liblammps.so and lammps.py to system dirs -# Syntax: python install.py [libdir] [pydir] -# libdir = target dir for src/liblammps.so, default = /usr/local/lib -# pydir = target dir for lammps.py, default = Python site-packages dir +instructions = """copy LAMMPS shared library src/liblammps.so and lammps.py to system dirs +Syntax: python install.py [libdir] [pydir] + libdir = target dir for src/liblammps.so, default = /usr/local/lib, or the first + item in LD_LIBRARY_PATH if it doesn't exist. + pydir = target dir for lammps.py, default = Python site-packages, via distutils.""" -import sys,commands +import sys, shutil, os if len(sys.argv) > 3: - print "Syntax: python install.py [libdir] [pydir]" + print instructions sys.exit() -if len(sys.argv) >= 2: libdir = sys.argv[1] -else: libdir = "/usr/local/lib" +# verify that our user-specified path is in LD_LIBRARY_PATH +# since if not, the install won't work + +libdir = "/usr/local/lib" +libpaths = os.environ['LD_LIBRARY_PATH'].split(':') +if not libdir in libpaths: + libdir = libpaths[0] -if len(sys.argv) == 3: pydir = sys.argv[2] -else: - paths = sys.path - for i,path in enumerate(paths): - index = path.rfind("site-packages") - if index < 0: continue - if index == len(path) - len("site-packages"): break - pydir = paths[i] +pydir = False +try: + libdir = sys.argv[1] + pydir = sys.argv[2] +except IndexError: + pass -str = "cp ../src/liblammps.so %s" % libdir -print str -outstr = commands.getoutput(str) -if len(outstr.strip()): print outstr +# copy the C library into place -str = "cp ../python/lammps.py %s" % pydir -print str -outstr = commands.getoutput(str) -if len(outstr.strip()): print outstr +shutil.copy('../src/liblammps.so', libdir) +# if user-specified, copy lammps.py into directory +# else invoke setup from Distutils to add to site-packages + +if pydir: + shutil.copy('../python/lammps.py', pydir) + sys.exit() + +from distutils.core import setup + +os.chdir('../python') + +setup(name = "lammps", + version = "15Aug12", + author = "Steve Plimpton", + author_email = "sjplimp@sandia.gov", + url = "http://lammps.sandia.gov", + description = """LAMMPS molecular dynamics library""", + py_modules = ["lammps"] +) From 8af673c69d5f7b9faa7c3bb69806874dacc2fecd Mon Sep 17 00:00:00 2001 From: sjplimp Date: Wed, 15 Aug 2012 14:43:41 +0000 Subject: [PATCH 03/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8671 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- src/library.cpp | 23 ++++++++++++++++++----- 1 file changed, 18 insertions(+), 5 deletions(-) diff --git a/src/library.cpp b/src/library.cpp index 6aecc44805..da6836dc13 100644 --- a/src/library.cpp +++ b/src/library.cpp @@ -30,7 +30,9 @@ #include "modify.h" #include "compute.h" #include "fix.h" +#include "comm.h" #include "memory.h" +#include "error.h" using namespace LAMMPS_NS; @@ -383,8 +385,13 @@ void lammps_gather_atoms(void *ptr, char *name, // error if tags are not defined or not consecutive - if (lmp->atom->tag_enable == 0 || lmp->atom->tag_consecutive() == 0) return; - if (lmp->atom->natoms > MAXSMALLINT) return; + int flag = 0; + if (lmp->atom->tag_enable == 0 || lmp->atom->tag_consecutive() == 0) flag = 1; + if (lmp->atom->natoms > MAXSMALLINT) flag = 1; + if (flag && lmp->comm->me == 0) { + lmp->error->warning(FLERR,"Library error in lammps_gather_atoms"); + return; + } int natoms = static_cast (lmp->atom->natoms); @@ -464,10 +471,16 @@ void lammps_scatter_atoms(void *ptr, char *name, { LAMMPS *lmp = (LAMMPS *) ptr; - // error if tags are not defined or not consecutive + // error if tags are not defined or not consecutive or no atom map - if (lmp->atom->tag_enable == 0 || lmp->atom->tag_consecutive() == 0) return; - if (lmp->atom->natoms > MAXSMALLINT) return; + int flag = 0; + if (lmp->atom->tag_enable == 0 || lmp->atom->tag_consecutive() == 0) flag = 1; + if (lmp->atom->natoms > MAXSMALLINT) flag = 1; + if (lmp->atom->map_style == 0) flag = 1; + if (flag && lmp->comm->me == 0) { + lmp->error->warning(FLERR,"Library error in lammps_scatter_atoms"); + return; + } int natoms = static_cast (lmp->atom->natoms); From 2e7bd3367f6b09ba03d2e8836da00c7314e264a0 Mon Sep 17 00:00:00 2001 From: sjplimp Date: Wed, 15 Aug 2012 19:49:01 +0000 Subject: [PATCH 04/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8672 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- python/install.py | 89 +++++++++++++++++++++++++++-------------------- 1 file changed, 52 insertions(+), 37 deletions(-) diff --git a/python/install.py b/python/install.py index c1e62fc853..e1fa4612b4 100644 --- a/python/install.py +++ b/python/install.py @@ -1,52 +1,67 @@ -#!/usr/bin/env python +#!/usr/local/bin/python -instructions = """copy LAMMPS shared library src/liblammps.so and lammps.py to system dirs -Syntax: python install.py [libdir] [pydir] - libdir = target dir for src/liblammps.so, default = /usr/local/lib, or the first - item in LD_LIBRARY_PATH if it doesn't exist. - pydir = target dir for lammps.py, default = Python site-packages, via distutils.""" +# copy LAMMPS src/liblammps.so and lammps.py to system dirs -import sys, shutil, os +instructions = """ +Syntax: python install.py [-h] [libdir] [pydir] + libdir = target dir for src/liblammps.so, default = /usr/local/lib + pydir = target dir for lammps.py, default = Python site-packages dir +""" -if len(sys.argv) > 3: +import sys,os,commands + +if (len(sys.argv) > 1 and sys.argv[1] == "-h") or len(sys.argv) > 3: print instructions sys.exit() -# verify that our user-specified path is in LD_LIBRARY_PATH -# since if not, the install won't work +if len(sys.argv) >= 2: libdir = sys.argv[1] +else: libdir = "/usr/local/lib" + +if len(sys.argv) == 3: pydir = sys.argv[2] +else: pydir = "" + +# copy C lib to libdir if it exists +# warn if not in LD_LIBRARY_PATH or LD_LIBRARY_PATH is undefined + +if not os.path.isdir(libdir): + print "ERROR: libdir %s does not exist" % libdir + sys.exit() -libdir = "/usr/local/lib" -libpaths = os.environ['LD_LIBRARY_PATH'].split(':') -if not libdir in libpaths: - libdir = libpaths[0] +if "LD_LIBRARY_PATH" not in os.environ: + print "WARNING: LD_LIBRARY_PATH undefined, cannot check libdir %s" % libdir +else: + libpaths = os.environ['LD_LIBRARY_PATH'].split(':') + if libdir not in libpaths: + print "WARNING: libdir %s not in LD_LIBRARY_PATH" % libdir -pydir = False -try: - libdir = sys.argv[1] - pydir = sys.argv[2] -except IndexError: - pass +str = "cp ../src/liblammps.so %s" % libdir +print str +outstr = commands.getoutput(str) +if len(outstr.strip()): print outstr -# copy the C library into place - -shutil.copy('../src/liblammps.so', libdir) - -# if user-specified, copy lammps.py into directory -# else invoke setup from Distutils to add to site-packages +# copy lammps.py to pydir if it exists +# if pydir not specified, install in site-packages via distutils setup() if pydir: - shutil.copy('../python/lammps.py', pydir) + if not os.path.isdir(pydir): + print "ERROR: pydir %s does not exist" % pydir sys.exit() + str = "cp ../python/lammps.py %s" % pydir + print str + outstr = commands.getoutput(str) + if len(outstr.strip()): print outstr + sys.exit() + +print "installing lammps.py in Python site-packages dir" + +os.chdir('../python') # in case invoked via make in src dir from distutils.core import setup - -os.chdir('../python') - +sys.argv = ["setup.py","install"] # as if had run "python setup.py install" setup(name = "lammps", - version = "15Aug12", - author = "Steve Plimpton", - author_email = "sjplimp@sandia.gov", - url = "http://lammps.sandia.gov", - description = """LAMMPS molecular dynamics library""", - py_modules = ["lammps"] -) + version = "15Aug12", + author = "Steve Plimpton", + author_email = "sjplimp@sandia.gov", + url = "http://lammps.sandia.gov", + description = "LAMMPS molecular dynamics library", + py_modules = ["lammps"]) From 5c58881400ad73fff5f6db5c2c771933fe9e28d5 Mon Sep 17 00:00:00 2001 From: sjplimp Date: Wed, 15 Aug 2012 22:59:37 +0000 Subject: [PATCH 05/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8673 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- doc/Section_python.html | 23 ++++++++++++----------- doc/Section_python.txt | 23 ++++++++++++----------- doc/Section_start.html | 2 +- doc/Section_start.txt | 2 +- 4 files changed, 26 insertions(+), 24 deletions(-) diff --git a/doc/Section_python.html b/doc/Section_python.html index 46c4ab9783..9b97533af1 100644 --- a/doc/Section_python.html +++ b/doc/Section_python.html @@ -58,12 +58,13 @@ operations within LAMMPS, such as running a simulation for a reasonable number of timesteps, then the overhead cost of invoking LAMMPS thru Python will be negligible.

-

Before using LAMMPS from a Python script, you have to do two things. -You need to set two environment variables. And you need to build -LAMMPS as a dynamic shared library, so it can be loaded by Python. -Both these steps are discussed below. If you wish to run LAMMPS in -parallel from Python, you also need to extend your Python with MPI. -This is also discussed below. +

Before using LAMMPS from a Python script, you need to do two things. +You need to build LAMMPS as a dynamic shared library, so it can be +loaded by Python. And you need to tell Python how to find the library +and the Python wrapper file python/lammps.py. Both these steps are +discussed below. If you wish to run LAMMPS in parallel from Python, +you also need to extend your Python with MPI. This is also discussed +below.

The Python wrapper for LAMMPS uses the amazing and magical (to me) "ctypes" package in Python, which auto-generates the interface code @@ -131,7 +132,7 @@ python/lammps.py file.

You can invoke install.py from the python directory as

-
% python install.py libdir pydir 
+
% python install.py [libdir] [pydir] 
 

The optional libdir is where to copy the LAMMPS shared library to; the default is /usr/local/lib. The optional pydir is where to copy the @@ -146,12 +147,12 @@ non-standard locations, such as within your own user space, you will need to set your PYTHONPATH and LD_LIBRARY_PATH environment variables accordingly, as above.

-

If the instally.py script does not allow you to copy files into system +

If the install.py script does not allow you to copy files into system directories, prefix the python command with "sudo". If you do this, make sure that the Python that root runs is the same as the Python you run. E.g. you may need to do something like

-
% sudo /usr/local/bin/python install.py libdir pydir 
+
% sudo /usr/local/bin/python install.py [libdir] [pydir] 
 

You can also invoke install.py from the make command in the src directory as @@ -275,8 +276,8 @@ If the load fails, the most common error to see is

OSError: Could not load LAMMPS dynamic library 
 

which means Python was unable to load the LAMMPS shared library. This -typically occurs if the system can't find the LAMMMPS shared library -or one of the auxiliary shared libraries it depends on. +typically occurs if the system can't find the LAMMPS shared library or +one of the auxiliary shared libraries it depends on.

Python (actually the operating system) isn't verbose about telling you why the load failed, so carefully go through the steps above regarding diff --git a/doc/Section_python.txt b/doc/Section_python.txt index 3c29fe6fe6..47e53fc8a8 100644 --- a/doc/Section_python.txt +++ b/doc/Section_python.txt @@ -55,12 +55,13 @@ operations within LAMMPS, such as running a simulation for a reasonable number of timesteps, then the overhead cost of invoking LAMMPS thru Python will be negligible. -Before using LAMMPS from a Python script, you have to do two things. -You need to set two environment variables. And you need to build -LAMMPS as a dynamic shared library, so it can be loaded by Python. -Both these steps are discussed below. If you wish to run LAMMPS in -parallel from Python, you also need to extend your Python with MPI. -This is also discussed below. +Before using LAMMPS from a Python script, you need to do two things. +You need to build LAMMPS as a dynamic shared library, so it can be +loaded by Python. And you need to tell Python how to find the library +and the Python wrapper file python/lammps.py. Both these steps are +discussed below. If you wish to run LAMMPS in parallel from Python, +you also need to extend your Python with MPI. This is also discussed +below. The Python wrapper for LAMMPS uses the amazing and magical (to me) "ctypes" package in Python, which auto-generates the interface code @@ -127,7 +128,7 @@ python/lammps.py file. You can invoke install.py from the python directory as -% python install.py [libdir] [pydir] :pre +% python install.py \[libdir\] \[pydir\] :pre The optional libdir is where to copy the LAMMPS shared library to; the default is /usr/local/lib. The optional pydir is where to copy the @@ -142,12 +143,12 @@ non-standard locations, such as within your own user space, you will need to set your PYTHONPATH and LD_LIBRARY_PATH environment variables accordingly, as above. -If the instally.py script does not allow you to copy files into system +If the install.py script does not allow you to copy files into system directories, prefix the python command with "sudo". If you do this, make sure that the Python that root runs is the same as the Python you run. E.g. you may need to do something like -% sudo /usr/local/bin/python install.py [libdir] [pydir] :pre +% sudo /usr/local/bin/python install.py \[libdir\] \[pydir\] :pre You can also invoke install.py from the make command in the src directory as @@ -271,8 +272,8 @@ If the load fails, the most common error to see is OSError: Could not load LAMMPS dynamic library :pre which means Python was unable to load the LAMMPS shared library. This -typically occurs if the system can't find the LAMMMPS shared library -or one of the auxiliary shared libraries it depends on. +typically occurs if the system can't find the LAMMPS shared library or +one of the auxiliary shared libraries it depends on. Python (actually the operating system) isn't verbose about telling you why the load failed, so carefully go through the steps above regarding diff --git a/doc/Section_start.html b/doc/Section_start.html index e225c3394a..2951ab5096 100644 --- a/doc/Section_start.html +++ b/doc/Section_start.html @@ -850,7 +850,7 @@ should be the file /usr/local/lib/libmpich.so. the environment variable LD_LIBRARY_PATH. So you may wish to copy the file src/liblammps.so or src/liblammps_g++.so (for example) to a place the system can find it by default, such as /usr/local/lib, or you may -wish to add the lammps src directory to LD_LIBRARY_PATH, so that the +wish to add the LAMMPS src directory to LD_LIBRARY_PATH, so that the current version of the shared library is always available to programs that use it.

diff --git a/doc/Section_start.txt b/doc/Section_start.txt index 5712e91236..7551850b9f 100644 --- a/doc/Section_start.txt +++ b/doc/Section_start.txt @@ -844,7 +844,7 @@ The operating system finds shared libraries to load at run-time using the environment variable LD_LIBRARY_PATH. So you may wish to copy the file src/liblammps.so or src/liblammps_g++.so (for example) to a place the system can find it by default, such as /usr/local/lib, or you may -wish to add the lammps src directory to LD_LIBRARY_PATH, so that the +wish to add the LAMMPS src directory to LD_LIBRARY_PATH, so that the current version of the shared library is always available to programs that use it. From 0df7e3716903f7fa12fe438401d78478dbcc3e45 Mon Sep 17 00:00:00 2001 From: sjplimp Date: Thu, 16 Aug 2012 14:20:20 +0000 Subject: [PATCH 06/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8674 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- src/MAKE/Makefile.g++ | 3 --- src/Make.sh | 4 +++- src/Makefile | 2 +- src/Makefile.lib | 3 --- src/Makefile.list | 3 --- src/Makefile.shlib | 2 +- src/USER-CUDA/cuda.cpp | 2 ++ 7 files changed, 7 insertions(+), 12 deletions(-) diff --git a/src/MAKE/Makefile.g++ b/src/MAKE/Makefile.g++ index 486742e87d..a884c91fd7 100755 --- a/src/MAKE/Makefile.g++ +++ b/src/MAKE/Makefile.g++ @@ -85,9 +85,6 @@ $(EXE): $(OBJ) lib: $(OBJ) $(ARCHIVE) $(ARFLAGS) $(EXE) $(OBJ) -#shlib: $(OBJ) -# $(ARCHIVE) $(ARFLAGS) $(EXE) $(OBJ) - shlib: $(OBJ) $(CC) $(CCFLAGS) $(SHFLAGS) $(SHLIBFLAGS) $(EXTRA_PATH) -o $(EXE) \ $(OBJ) $(EXTRA_LIB) $(LIB) diff --git a/src/Make.sh b/src/Make.sh index 7144bf37a3..e554ba6353 100644 --- a/src/Make.sh +++ b/src/Make.sh @@ -1,6 +1,8 @@ -# Make.sh = update Makefile.lib or Makefile.list or style_*.h files +# Make.sh = update Makefile.lib, Makefile.shlib, Makefile.list +# or style_*.h files # Syntax: sh Make.sh style # sh Make.sh Makefile.lib +# sh Make.sh Makefile.shlib # sh Make.sh Makefile.list # function to create one style_*.h file diff --git a/src/Makefile b/src/Makefile index 5ad4251822..b0cf43b46b 100755 --- a/src/Makefile +++ b/src/Makefile @@ -130,7 +130,7 @@ makelist: @$(SHELL) Make.sh style @$(SHELL) Make.sh Makefile.list -# install LAMMPS shared lib and Python wrapper in Python +# install LAMMPS shared lib and Python wrapper for Python usage install-python: @python ../python/install.py diff --git a/src/Makefile.lib b/src/Makefile.lib index 3c7504c9e8..7e27fef24d 100644 --- a/src/Makefile.lib +++ b/src/Makefile.lib @@ -21,9 +21,6 @@ help: @files="`ls MAKE/Makefile.*`"; \ for file in $$files; do head -1 $$file; done -clean: - rm -rf Obj_* - .DEFAULT: @test -f MAKE/Makefile.$@ @if [ ! -d Obj_$@ ]; then mkdir Obj_$@; fi diff --git a/src/Makefile.list b/src/Makefile.list index 5f755f6ecd..65bbebca09 100644 --- a/src/Makefile.list +++ b/src/Makefile.list @@ -21,9 +21,6 @@ help: @files="`ls MAKE/Makefile.*`"; \ for file in $$files; do head -1 $$file; done -clean: - rm -rf Obj_* - .DEFAULT: @test -f MAKE/Makefile.$@ @if [ ! -d Obj_$@ ]; then mkdir Obj_$@; fi diff --git a/src/Makefile.shlib b/src/Makefile.shlib index 8ce14d8d58..a331230b73 100644 --- a/src/Makefile.shlib +++ b/src/Makefile.shlib @@ -22,7 +22,7 @@ help: for file in $$files; do head -1 $$file; done clean: - rm -rf Obj_* + rm -rf Obj_shlib_* .DEFAULT: @test -f MAKE/Makefile.$@ diff --git a/src/USER-CUDA/cuda.cpp b/src/USER-CUDA/cuda.cpp index 22dd2ceaed..e3f4d47d81 100644 --- a/src/USER-CUDA/cuda.cpp +++ b/src/USER-CUDA/cuda.cpp @@ -410,6 +410,8 @@ void Cuda::setDomainParams() cu_domain->boxlo_lamda[i] = domain->boxlo_lamda[i]; cu_domain->boxhi_lamda[i] = domain->boxhi_lamda[i]; cu_domain->prd_lamda[i] = domain->prd_lamda[i]; + cu_domain->sublo[i] = domain->sublo_lamda[i]; + cu_domain->subhi[i] = domain->subhi_lamda[i]; } cu_domain->xy = domain->xy; From d4215d8844022fee7754f4a30b7010f3af8cd615 Mon Sep 17 00:00:00 2001 From: sjplimp Date: Thu, 16 Aug 2012 21:16:03 +0000 Subject: [PATCH 07/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8675 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- python/lammps.py | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/python/lammps.py b/python/lammps.py index f8c5063606..4485bb6b6d 100644 --- a/python/lammps.py +++ b/python/lammps.py @@ -13,7 +13,7 @@ # Python wrapper on LAMMPS library via ctypes -import types +import sys,traceback,types from ctypes import * class lammps: @@ -26,6 +26,8 @@ class lammps: if not name: self.lib = CDLL("liblammps.so") else: self.lib = CDLL("liblammps_%s.so" % name) except: + type,value,tb = sys.exc_info() + traceback.print_exception(type,value,tb) raise OSError,"Could not load LAMMPS dynamic library" # create an instance of LAMMPS From d510654bc36074d9e0c14e1707bdf61e851aea6e Mon Sep 17 00:00:00 2001 From: sjplimp Date: Thu, 16 Aug 2012 21:20:03 +0000 Subject: [PATCH 08/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8676 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- doc/Section_python.html | 16 ++++++++++------ doc/Section_python.txt | 16 ++++++++++------ 2 files changed, 20 insertions(+), 12 deletions(-) diff --git a/doc/Section_python.html b/doc/Section_python.html index 9b97533af1..e4d48975b6 100644 --- a/doc/Section_python.html +++ b/doc/Section_python.html @@ -277,13 +277,17 @@ If the load fails, the most common error to see is

which means Python was unable to load the LAMMPS shared library. This typically occurs if the system can't find the LAMMPS shared library or -one of the auxiliary shared libraries it depends on. +one of the auxiliary shared libraries it depends on. The error +message should give you some indication of what went wrong.

-

Python (actually the operating system) isn't verbose about telling you -why the load failed, so carefully go through the steps above regarding -environment variables, and the instructions in Section_start -5 about building a shared library and -about setting the LD_LIBRARY_PATH envirornment variable. +

You can also test the load directly in Python as follows +

+
>>> from ctypes import CDLL
+>>> CDLL("liblammps.so") 
+
+

If an error occurs, carefully go thru the steps above and in +Section_start 5 about building a shared +library and about insuring Python can find the necessary 2 files.

Test LAMMPS and Python in serial:
diff --git a/doc/Section_python.txt b/doc/Section_python.txt index 47e53fc8a8..e21ff33ce8 100644 --- a/doc/Section_python.txt +++ b/doc/Section_python.txt @@ -273,13 +273,17 @@ OSError: Could not load LAMMPS dynamic library :pre which means Python was unable to load the LAMMPS shared library. This typically occurs if the system can't find the LAMMPS shared library or -one of the auxiliary shared libraries it depends on. +one of the auxiliary shared libraries it depends on. The error +message should give you some indication of what went wrong. -Python (actually the operating system) isn't verbose about telling you -why the load failed, so carefully go through the steps above regarding -environment variables, and the instructions in "Section_start -5"_Section_start.html#start_5 about building a shared library and -about setting the LD_LIBRARY_PATH envirornment variable. +You can also test the load directly in Python as follows + +>>> from ctypes import CDLL +>>> CDLL("liblammps.so") :pre + +If an error occurs, carefully go thru the steps above and in +"Section_start 5"_Section_start.html#start_5 about building a shared +library and about insuring Python can find the necessary 2 files. [Test LAMMPS and Python in serial:] :h5 From 53bb7e981d3d0d3eb3d9fd9f1463146bcb8f63f7 Mon Sep 17 00:00:00 2001 From: sjplimp Date: Thu, 16 Aug 2012 22:58:42 +0000 Subject: [PATCH 09/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8677 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- src/KSPACE/pppm.cpp | 1 - 1 file changed, 1 deletion(-) diff --git a/src/KSPACE/pppm.cpp b/src/KSPACE/pppm.cpp index 2bea3fadee..bea8eb2938 100644 --- a/src/KSPACE/pppm.cpp +++ b/src/KSPACE/pppm.cpp @@ -100,7 +100,6 @@ PPPM::PPPM(LAMMPS *lmp, int narg, char **arg) : KSpace(lmp, narg, arg) // see JCP 109, pg 7698 for derivation of coefficients // higher order coefficients may be computed if needed - memory->destroy(acons); memory->create(acons,8,7,"pppm:acons"); acons[1][0] = 2.0 / 3.0; acons[2][0] = 1.0 / 50.0; From d29dd35c45542e057e57e2bfeffea7917a751080 Mon Sep 17 00:00:00 2001 From: sjplimp Date: Fri, 17 Aug 2012 13:16:52 +0000 Subject: [PATCH 10/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8678 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- src/Makefile.shlib | 4 ++-- src/USER-OMP/pair_lj_expand_omp.h | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Makefile.shlib b/src/Makefile.shlib index a331230b73..71483a1c87 100644 --- a/src/Makefile.shlib +++ b/src/Makefile.shlib @@ -7,9 +7,9 @@ SHELL = /bin/sh ROOT = lammps EXE = lib$(ROOT)_$@.so -SRC = angle.cpp angle_charmm.cpp angle_class2.cpp angle_cosine.cpp angle_cosine_delta.cpp angle_cosine_periodic.cpp angle_cosine_squared.cpp angle_harmonic.cpp angle_hybrid.cpp angle_table.cpp atom.cpp atom_map.cpp atom_vec.cpp atom_vec_angle.cpp atom_vec_atomic.cpp atom_vec_bond.cpp atom_vec_charge.cpp atom_vec_dipole.cpp atom_vec_ellipsoid.cpp atom_vec_full.cpp atom_vec_hybrid.cpp atom_vec_line.cpp atom_vec_molecular.cpp atom_vec_peri.cpp atom_vec_sphere.cpp atom_vec_tri.cpp balance.cpp bond.cpp bond_class2.cpp bond_fene.cpp bond_fene_expand.cpp bond_harmonic.cpp bond_hybrid.cpp bond_morse.cpp bond_nonlinear.cpp bond_quartic.cpp bond_table.cpp change_box.cpp comm.cpp compute.cpp compute_angle_local.cpp compute_atom_molecule.cpp compute_bond_local.cpp compute_centro_atom.cpp compute_cluster_atom.cpp compute_cna_atom.cpp compute_com.cpp compute_com_molecule.cpp compute_contact_atom.cpp compute_coord_atom.cpp compute_damage_atom.cpp compute_dihedral_local.cpp compute_displace_atom.cpp compute_erotate_asphere.cpp compute_erotate_sphere.cpp compute_erotate_sphere_atom.cpp compute_event_displace.cpp compute_group_group.cpp compute_gyration.cpp compute_gyration_molecule.cpp compute_heat_flux.cpp compute_improper_local.cpp compute_ke.cpp compute_ke_atom.cpp compute_msd.cpp compute_msd_molecule.cpp compute_pair.cpp compute_pair_local.cpp compute_pe.cpp compute_pe_atom.cpp compute_pressure.cpp compute_property_atom.cpp compute_property_local.cpp compute_property_molecule.cpp compute_rdf.cpp compute_reduce.cpp compute_reduce_region.cpp compute_slice.cpp compute_stress_atom.cpp compute_temp.cpp compute_temp_asphere.cpp compute_temp_com.cpp compute_temp_deform.cpp compute_temp_partial.cpp compute_temp_profile.cpp compute_temp_ramp.cpp compute_temp_region.cpp compute_temp_sphere.cpp compute_ti.cpp create_atoms.cpp create_box.cpp delete_atoms.cpp delete_bonds.cpp dihedral.cpp dihedral_charmm.cpp dihedral_class2.cpp dihedral_harmonic.cpp dihedral_helix.cpp dihedral_hybrid.cpp dihedral_multi_harmonic.cpp dihedral_opls.cpp displace_atoms.cpp domain.cpp dump.cpp dump_atom.cpp dump_cfg.cpp dump_custom.cpp dump_dcd.cpp dump_image.cpp dump_local.cpp dump_xtc.cpp dump_xyz.cpp error.cpp finish.cpp fix.cpp fix_adapt.cpp fix_addforce.cpp fix_append_atoms.cpp fix_ave_atom.cpp fix_ave_correlate.cpp fix_ave_histo.cpp fix_ave_spatial.cpp fix_ave_time.cpp fix_aveforce.cpp fix_balance.cpp fix_bond_break.cpp fix_bond_create.cpp fix_bond_swap.cpp fix_box_relax.cpp fix_deform.cpp fix_deposit.cpp fix_drag.cpp fix_dt_reset.cpp fix_efield.cpp fix_enforce2d.cpp fix_evaporate.cpp fix_event.cpp fix_event_prd.cpp fix_event_tad.cpp fix_external.cpp fix_freeze.cpp fix_gcmc.cpp fix_gravity.cpp fix_heat.cpp fix_indent.cpp fix_langevin.cpp fix_lineforce.cpp fix_minimize.cpp fix_momentum.cpp fix_move.cpp fix_msst.cpp fix_neb.cpp fix_nh.cpp fix_nh_asphere.cpp fix_nh_sphere.cpp fix_nph.cpp fix_nph_asphere.cpp fix_nph_sphere.cpp fix_nphug.cpp fix_npt.cpp fix_npt_asphere.cpp fix_npt_sphere.cpp fix_nve.cpp fix_nve_asphere.cpp fix_nve_asphere_noforce.cpp fix_nve_limit.cpp fix_nve_line.cpp fix_nve_noforce.cpp fix_nve_sphere.cpp fix_nve_tri.cpp fix_nvt.cpp fix_nvt_asphere.cpp fix_nvt_sllod.cpp fix_nvt_sphere.cpp fix_orient_fcc.cpp fix_peri_neigh.cpp fix_planeforce.cpp fix_pour.cpp fix_press_berendsen.cpp fix_print.cpp fix_qeq_comb.cpp fix_read_restart.cpp fix_recenter.cpp fix_respa.cpp fix_restrain.cpp fix_rigid.cpp fix_rigid_nve.cpp fix_rigid_nvt.cpp fix_setforce.cpp fix_shake.cpp fix_shear_history.cpp fix_spring.cpp fix_spring_rg.cpp fix_spring_self.cpp fix_srd.cpp fix_store_force.cpp fix_store_state.cpp fix_temp_berendsen.cpp fix_temp_rescale.cpp fix_thermal_conductivity.cpp fix_tmd.cpp fix_ttm.cpp fix_viscosity.cpp fix_viscous.cpp fix_wall.cpp fix_wall_colloid.cpp fix_wall_gran.cpp fix_wall_harmonic.cpp fix_wall_lj126.cpp fix_wall_lj93.cpp fix_wall_piston.cpp fix_wall_reflect.cpp fix_wall_region.cpp fix_wall_srd.cpp force.cpp group.cpp image.cpp improper.cpp improper_class2.cpp improper_cvff.cpp improper_harmonic.cpp improper_hybrid.cpp improper_umbrella.cpp input.cpp integrate.cpp irregular.cpp kspace.cpp lammps.cpp lattice.cpp library.cpp math_extra.cpp memory.cpp min.cpp min_cg.cpp min_fire.cpp min_hftn.cpp min_linesearch.cpp min_quickmin.cpp min_sd.cpp minimize.cpp modify.cpp neb.cpp neigh_bond.cpp neigh_derive.cpp neigh_full.cpp neigh_gran.cpp neigh_half_bin.cpp neigh_half_multi.cpp neigh_half_nsq.cpp neigh_list.cpp neigh_request.cpp neigh_respa.cpp neigh_stencil.cpp neighbor.cpp output.cpp pair.cpp pair_adp.cpp pair_airebo.cpp pair_beck.cpp pair_bop.cpp pair_born.cpp pair_born_coul_wolf.cpp pair_brownian.cpp pair_brownian_poly.cpp pair_buck.cpp pair_buck_coul_cut.cpp pair_colloid.cpp pair_comb.cpp pair_coul_cut.cpp pair_coul_debye.cpp pair_coul_wolf.cpp pair_dipole_cut.cpp pair_dpd.cpp pair_dpd_tstat.cpp pair_dsmc.cpp pair_eam.cpp pair_eam_alloy.cpp pair_eam_alloy_opt.cpp pair_eam_fs.cpp pair_eam_fs_opt.cpp pair_eam_opt.cpp pair_eim.cpp pair_gauss.cpp pair_gayberne.cpp pair_gran_hertz_history.cpp pair_gran_hooke.cpp pair_gran_hooke_history.cpp pair_hbond_dreiding_lj.cpp pair_hbond_dreiding_morse.cpp pair_hybrid.cpp pair_hybrid_overlay.cpp pair_lcbop.cpp pair_line_lj.cpp pair_lj96_cut.cpp pair_lj_charmm_coul_charmm.cpp pair_lj_charmm_coul_charmm_implicit.cpp pair_lj_class2.cpp pair_lj_class2_coul_cut.cpp pair_lj_class2_coul_long.cpp pair_lj_cubic.cpp pair_lj_cut.cpp pair_lj_cut_coul_cut.cpp pair_lj_cut_coul_debye.cpp pair_lj_cut_opt.cpp pair_lj_expand.cpp pair_lj_gromacs.cpp pair_lj_gromacs_coul_gromacs.cpp pair_lj_smooth.cpp pair_lj_smooth_linear.cpp pair_lubricate.cpp pair_lubricateU.cpp pair_lubricateU_poly.cpp pair_lubricate_poly.cpp pair_morse.cpp pair_morse_opt.cpp pair_peri_lps.cpp pair_peri_pmb.cpp pair_rebo.cpp pair_resquared.cpp pair_soft.cpp pair_sw.cpp pair_table.cpp pair_tersoff.cpp pair_tersoff_zbl.cpp pair_tri_lj.cpp pair_yukawa.cpp pair_yukawa_colloid.cpp prd.cpp procmap.cpp random_mars.cpp random_park.cpp read_data.cpp read_dump.cpp read_restart.cpp reader.cpp reader_native.cpp reader_xyz.cpp region.cpp region_block.cpp region_cone.cpp region_cylinder.cpp region_intersect.cpp region_plane.cpp region_prism.cpp region_sphere.cpp region_union.cpp replicate.cpp rerun.cpp respa.cpp run.cpp set.cpp special.cpp tad.cpp temper.cpp thermo.cpp timer.cpp universe.cpp update.cpp variable.cpp velocity.cpp verlet.cpp verlet_split.cpp write_restart.cpp xdr_compat.cpp +SRC = angle.cpp angle_charmm.cpp angle_class2.cpp angle_cosine.cpp angle_cosine_delta.cpp angle_cosine_periodic.cpp angle_cosine_squared.cpp angle_harmonic.cpp angle_hybrid.cpp angle_table.cpp atom.cpp atom_map.cpp atom_vec.cpp atom_vec_angle.cpp atom_vec_atomic.cpp atom_vec_bond.cpp atom_vec_charge.cpp atom_vec_dipole.cpp atom_vec_ellipsoid.cpp atom_vec_full.cpp atom_vec_hybrid.cpp atom_vec_line.cpp atom_vec_molecular.cpp atom_vec_peri.cpp atom_vec_sphere.cpp atom_vec_tri.cpp balance.cpp bond.cpp bond_class2.cpp bond_fene.cpp bond_fene_expand.cpp bond_harmonic.cpp bond_hybrid.cpp bond_morse.cpp bond_nonlinear.cpp bond_quartic.cpp bond_table.cpp change_box.cpp comm.cpp compute.cpp compute_angle_local.cpp compute_atom_molecule.cpp compute_bond_local.cpp compute_centro_atom.cpp compute_cluster_atom.cpp compute_cna_atom.cpp compute_com.cpp compute_com_molecule.cpp compute_contact_atom.cpp compute_coord_atom.cpp compute_damage_atom.cpp compute_dihedral_local.cpp compute_displace_atom.cpp compute_erotate_asphere.cpp compute_erotate_sphere.cpp compute_erotate_sphere_atom.cpp compute_event_displace.cpp compute_group_group.cpp compute_gyration.cpp compute_gyration_molecule.cpp compute_heat_flux.cpp compute_improper_local.cpp compute_ke.cpp compute_ke_atom.cpp compute_msd.cpp compute_msd_molecule.cpp compute_pair.cpp compute_pair_local.cpp compute_pe.cpp compute_pe_atom.cpp compute_pressure.cpp compute_property_atom.cpp compute_property_local.cpp compute_property_molecule.cpp compute_rdf.cpp compute_reduce.cpp compute_reduce_region.cpp compute_slice.cpp compute_stress_atom.cpp compute_temp.cpp compute_temp_asphere.cpp compute_temp_com.cpp compute_temp_deform.cpp compute_temp_partial.cpp compute_temp_profile.cpp compute_temp_ramp.cpp compute_temp_region.cpp compute_temp_sphere.cpp compute_ti.cpp create_atoms.cpp create_box.cpp delete_atoms.cpp delete_bonds.cpp dihedral.cpp dihedral_charmm.cpp dihedral_class2.cpp dihedral_harmonic.cpp dihedral_helix.cpp dihedral_hybrid.cpp dihedral_multi_harmonic.cpp dihedral_opls.cpp displace_atoms.cpp domain.cpp dump.cpp dump_atom.cpp dump_cfg.cpp dump_custom.cpp dump_dcd.cpp dump_image.cpp dump_local.cpp dump_xtc.cpp dump_xyz.cpp error.cpp ewald.cpp fft3d.cpp fft3d_wrap.cpp finish.cpp fix.cpp fix_adapt.cpp fix_addforce.cpp fix_append_atoms.cpp fix_ave_atom.cpp fix_ave_correlate.cpp fix_ave_histo.cpp fix_ave_spatial.cpp fix_ave_time.cpp fix_aveforce.cpp fix_balance.cpp fix_bond_break.cpp fix_bond_create.cpp fix_bond_swap.cpp fix_box_relax.cpp fix_deform.cpp fix_deposit.cpp fix_drag.cpp fix_dt_reset.cpp fix_efield.cpp fix_enforce2d.cpp fix_evaporate.cpp fix_event.cpp fix_event_prd.cpp fix_event_tad.cpp fix_external.cpp fix_freeze.cpp fix_gcmc.cpp fix_gravity.cpp fix_heat.cpp fix_indent.cpp fix_langevin.cpp fix_lineforce.cpp fix_minimize.cpp fix_momentum.cpp fix_move.cpp fix_msst.cpp fix_neb.cpp fix_nh.cpp fix_nh_asphere.cpp fix_nh_sphere.cpp fix_nph.cpp fix_nph_asphere.cpp fix_nph_sphere.cpp fix_nphug.cpp fix_npt.cpp fix_npt_asphere.cpp fix_npt_sphere.cpp fix_nve.cpp fix_nve_asphere.cpp fix_nve_asphere_noforce.cpp fix_nve_limit.cpp fix_nve_line.cpp fix_nve_noforce.cpp fix_nve_sphere.cpp fix_nve_tri.cpp fix_nvt.cpp fix_nvt_asphere.cpp fix_nvt_sllod.cpp fix_nvt_sphere.cpp fix_orient_fcc.cpp fix_peri_neigh.cpp fix_planeforce.cpp fix_pour.cpp fix_press_berendsen.cpp fix_print.cpp fix_qeq_comb.cpp fix_read_restart.cpp fix_recenter.cpp fix_respa.cpp fix_restrain.cpp fix_rigid.cpp fix_rigid_nve.cpp fix_rigid_nvt.cpp fix_setforce.cpp fix_shake.cpp fix_shear_history.cpp fix_spring.cpp fix_spring_rg.cpp fix_spring_self.cpp fix_srd.cpp fix_store_force.cpp fix_store_state.cpp fix_temp_berendsen.cpp fix_temp_rescale.cpp fix_thermal_conductivity.cpp fix_tmd.cpp fix_ttm.cpp fix_viscosity.cpp fix_viscous.cpp fix_wall.cpp fix_wall_colloid.cpp fix_wall_gran.cpp fix_wall_harmonic.cpp fix_wall_lj126.cpp fix_wall_lj93.cpp fix_wall_piston.cpp fix_wall_reflect.cpp fix_wall_region.cpp fix_wall_srd.cpp force.cpp group.cpp image.cpp improper.cpp improper_class2.cpp improper_cvff.cpp improper_harmonic.cpp improper_hybrid.cpp improper_umbrella.cpp input.cpp integrate.cpp irregular.cpp kspace.cpp lammps.cpp lattice.cpp library.cpp math_extra.cpp memory.cpp min.cpp min_cg.cpp min_fire.cpp min_hftn.cpp min_linesearch.cpp min_quickmin.cpp min_sd.cpp minimize.cpp modify.cpp neb.cpp neigh_bond.cpp neigh_derive.cpp neigh_full.cpp neigh_gran.cpp neigh_half_bin.cpp neigh_half_multi.cpp neigh_half_nsq.cpp neigh_list.cpp neigh_request.cpp neigh_respa.cpp neigh_stencil.cpp neighbor.cpp output.cpp pair.cpp pair_adp.cpp pair_airebo.cpp pair_beck.cpp pair_bop.cpp pair_born.cpp pair_born_coul_long.cpp pair_born_coul_wolf.cpp pair_brownian.cpp pair_brownian_poly.cpp pair_buck.cpp pair_buck_coul_cut.cpp pair_buck_coul_long.cpp pair_colloid.cpp pair_comb.cpp pair_coul_cut.cpp pair_coul_debye.cpp pair_coul_long.cpp pair_coul_wolf.cpp pair_dipole_cut.cpp pair_dpd.cpp pair_dpd_tstat.cpp pair_dsmc.cpp pair_eam.cpp pair_eam_alloy.cpp pair_eam_alloy_opt.cpp pair_eam_fs.cpp pair_eam_fs_opt.cpp pair_eam_opt.cpp pair_eim.cpp pair_gauss.cpp pair_gayberne.cpp pair_gran_hertz_history.cpp pair_gran_hooke.cpp pair_gran_hooke_history.cpp pair_hbond_dreiding_lj.cpp pair_hbond_dreiding_morse.cpp pair_hybrid.cpp pair_hybrid_overlay.cpp pair_lcbop.cpp pair_line_lj.cpp pair_lj96_cut.cpp pair_lj_charmm_coul_charmm.cpp pair_lj_charmm_coul_charmm_implicit.cpp pair_lj_charmm_coul_long.cpp pair_lj_charmm_coul_long_opt.cpp pair_lj_class2.cpp pair_lj_class2_coul_cut.cpp pair_lj_class2_coul_long.cpp pair_lj_cubic.cpp pair_lj_cut.cpp pair_lj_cut_coul_cut.cpp pair_lj_cut_coul_debye.cpp pair_lj_cut_coul_long.cpp pair_lj_cut_coul_long_opt.cpp pair_lj_cut_coul_long_tip4p.cpp pair_lj_cut_coul_long_tip4p_opt.cpp pair_lj_cut_opt.cpp pair_lj_expand.cpp pair_lj_gromacs.cpp pair_lj_gromacs_coul_gromacs.cpp pair_lj_smooth.cpp pair_lj_smooth_linear.cpp pair_lubricate.cpp pair_lubricateU.cpp pair_lubricateU_poly.cpp pair_lubricate_poly.cpp pair_morse.cpp pair_morse_opt.cpp pair_peri_lps.cpp pair_peri_pmb.cpp pair_rebo.cpp pair_resquared.cpp pair_soft.cpp pair_sw.cpp pair_table.cpp pair_tersoff.cpp pair_tersoff_zbl.cpp pair_tri_lj.cpp pair_yukawa.cpp pair_yukawa_colloid.cpp pppm.cpp pppm_cg.cpp pppm_old.cpp pppm_tip4p.cpp prd.cpp procmap.cpp random_mars.cpp random_park.cpp read_data.cpp read_dump.cpp read_restart.cpp reader.cpp reader_native.cpp reader_xyz.cpp region.cpp region_block.cpp region_cone.cpp region_cylinder.cpp region_intersect.cpp region_plane.cpp region_prism.cpp region_sphere.cpp region_union.cpp remap.cpp remap_wrap.cpp replicate.cpp rerun.cpp respa.cpp run.cpp set.cpp special.cpp tad.cpp temper.cpp thermo.cpp timer.cpp universe.cpp update.cpp variable.cpp velocity.cpp verlet.cpp verlet_split.cpp write_restart.cpp xdr_compat.cpp -INC = accelerator_cuda.h accelerator_omp.h angle.h angle_charmm.h angle_class2.h angle_cosine.h angle_cosine_delta.h angle_cosine_periodic.h angle_cosine_squared.h angle_harmonic.h angle_hybrid.h angle_table.h atom.h atom_map.h atom_vec.h atom_vec_angle.h atom_vec_atomic.h atom_vec_bond.h atom_vec_charge.h atom_vec_dipole.h atom_vec_ellipsoid.h atom_vec_full.h atom_vec_hybrid.h atom_vec_line.h atom_vec_molecular.h atom_vec_peri.h atom_vec_sphere.h atom_vec_tri.h balance.h bond.h bond_class2.h bond_fene.h bond_fene_expand.h bond_harmonic.h bond_hybrid.h bond_morse.h bond_nonlinear.h bond_quartic.h bond_table.h change_box.h comm.h compute.h compute_angle_local.h compute_atom_molecule.h compute_bond_local.h compute_centro_atom.h compute_cluster_atom.h compute_cna_atom.h compute_com.h compute_com_molecule.h compute_contact_atom.h compute_coord_atom.h compute_damage_atom.h compute_dihedral_local.h compute_displace_atom.h compute_erotate_asphere.h compute_erotate_sphere.h compute_erotate_sphere_atom.h compute_event_displace.h compute_group_group.h compute_gyration.h compute_gyration_molecule.h compute_heat_flux.h compute_improper_local.h compute_ke.h compute_ke_atom.h compute_msd.h compute_msd_molecule.h compute_pair.h compute_pair_local.h compute_pe.h compute_pe_atom.h compute_pressure.h compute_property_atom.h compute_property_local.h compute_property_molecule.h compute_rdf.h compute_reduce.h compute_reduce_region.h compute_slice.h compute_stress_atom.h compute_temp.h compute_temp_asphere.h compute_temp_com.h compute_temp_deform.h compute_temp_partial.h compute_temp_profile.h compute_temp_ramp.h compute_temp_region.h compute_temp_sphere.h compute_ti.h create_atoms.h create_box.h delete_atoms.h delete_bonds.h dihedral.h dihedral_charmm.h dihedral_class2.h dihedral_harmonic.h dihedral_helix.h dihedral_hybrid.h dihedral_multi_harmonic.h dihedral_opls.h displace_atoms.h domain.h dump.h dump_atom.h dump_cfg.h dump_custom.h dump_dcd.h dump_image.h dump_local.h dump_xtc.h dump_xyz.h error.h finish.h fix.h fix_adapt.h fix_addforce.h fix_append_atoms.h fix_ave_atom.h fix_ave_correlate.h fix_ave_histo.h fix_ave_spatial.h fix_ave_time.h fix_aveforce.h fix_balance.h fix_bond_break.h fix_bond_create.h fix_bond_swap.h fix_box_relax.h fix_deform.h fix_deposit.h fix_drag.h fix_dt_reset.h fix_efield.h fix_enforce2d.h fix_evaporate.h fix_event.h fix_event_prd.h fix_event_tad.h fix_external.h fix_freeze.h fix_gcmc.h fix_gravity.h fix_heat.h fix_indent.h fix_langevin.h fix_lineforce.h fix_minimize.h fix_momentum.h fix_move.h fix_msst.h fix_neb.h fix_nh.h fix_nh_asphere.h fix_nh_sphere.h fix_nph.h fix_nph_asphere.h fix_nph_sphere.h fix_nphug.h fix_npt.h fix_npt_asphere.h fix_npt_sphere.h fix_nve.h fix_nve_asphere.h fix_nve_asphere_noforce.h fix_nve_limit.h fix_nve_line.h fix_nve_noforce.h fix_nve_sphere.h fix_nve_tri.h fix_nvt.h fix_nvt_asphere.h fix_nvt_sllod.h fix_nvt_sphere.h fix_orient_fcc.h fix_peri_neigh.h fix_planeforce.h fix_pour.h fix_press_berendsen.h fix_print.h fix_qeq_comb.h fix_read_restart.h fix_recenter.h fix_respa.h fix_restrain.h fix_rigid.h fix_rigid_nve.h fix_rigid_nvt.h fix_setforce.h fix_shake.h fix_shear_history.h fix_spring.h fix_spring_rg.h fix_spring_self.h fix_srd.h fix_store_force.h fix_store_state.h fix_temp_berendsen.h fix_temp_rescale.h fix_thermal_conductivity.h fix_tmd.h fix_ttm.h fix_viscosity.h fix_viscous.h fix_wall.h fix_wall_colloid.h fix_wall_gran.h fix_wall_harmonic.h fix_wall_lj126.h fix_wall_lj93.h fix_wall_piston.h fix_wall_reflect.h fix_wall_region.h fix_wall_srd.h force.h group.h image.h improper.h improper_class2.h improper_cvff.h improper_harmonic.h improper_hybrid.h improper_umbrella.h input.h integrate.h irregular.h kspace.h lammps.h lattice.h library.h lmptype.h lmpwindows.h math_const.h math_extra.h memory.h min.h min_cg.h min_fire.h min_hftn.h min_linesearch.h min_quickmin.h min_sd.h minimize.h modify.h neb.h neigh_bond.h neigh_derive.h neigh_full.h neigh_gran.h neigh_half_bin.h neigh_half_multi.h neigh_half_nsq.h neigh_list.h neigh_request.h neigh_respa.h neighbor.h output.h pack.h pair.h pair_adp.h pair_airebo.h pair_beck.h pair_bop.h pair_born.h pair_born_coul_wolf.h pair_brownian.h pair_brownian_poly.h pair_buck.h pair_buck_coul_cut.h pair_colloid.h pair_comb.h pair_coul_cut.h pair_coul_debye.h pair_coul_wolf.h pair_dipole_cut.h pair_dpd.h pair_dpd_tstat.h pair_dsmc.h pair_eam.h pair_eam_alloy.h pair_eam_alloy_opt.h pair_eam_fs.h pair_eam_fs_opt.h pair_eam_opt.h pair_eim.h pair_gauss.h pair_gayberne.h pair_gran_hertz_history.h pair_gran_hooke.h pair_gran_hooke_history.h pair_hbond_dreiding_lj.h pair_hbond_dreiding_morse.h pair_hybrid.h pair_hybrid_overlay.h pair_lcbop.h pair_line_lj.h pair_lj96_cut.h pair_lj_charmm_coul_charmm.h pair_lj_charmm_coul_charmm_implicit.h pair_lj_class2.h pair_lj_class2_coul_cut.h pair_lj_class2_coul_long.h pair_lj_cubic.h pair_lj_cut.h pair_lj_cut_coul_cut.h pair_lj_cut_coul_debye.h pair_lj_cut_opt.h pair_lj_expand.h pair_lj_gromacs.h pair_lj_gromacs_coul_gromacs.h pair_lj_smooth.h pair_lj_smooth_linear.h pair_lubricate.h pair_lubricateU.h pair_lubricateU_poly.h pair_lubricate_poly.h pair_morse.h pair_morse_opt.h pair_peri_lps.h pair_peri_pmb.h pair_rebo.h pair_resquared.h pair_soft.h pair_sw.h pair_table.h pair_tersoff.h pair_tersoff_zbl.h pair_tri_lj.h pair_yukawa.h pair_yukawa_colloid.h pointers.h prd.h procmap.h random_mars.h random_park.h read_data.h read_dump.h read_restart.h reader.h reader_native.h reader_xyz.h region.h region_block.h region_cone.h region_cylinder.h region_intersect.h region_plane.h region_prism.h region_sphere.h region_union.h replicate.h rerun.h respa.h run.h set.h special.h style_angle.h style_atom.h style_bond.h style_command.h style_compute.h style_dihedral.h style_dump.h style_fix.h style_improper.h style_integrate.h style_kspace.h style_minimize.h style_pair.h style_reader.h style_region.h suffix.h tad.h temper.h thermo.h timer.h universe.h update.h variable.h velocity.h verlet.h verlet_split.h version.h write_restart.h xdr_compat.h +INC = accelerator_cuda.h accelerator_omp.h angle.h angle_charmm.h angle_class2.h angle_cosine.h angle_cosine_delta.h angle_cosine_periodic.h angle_cosine_squared.h angle_harmonic.h angle_hybrid.h angle_table.h atom.h atom_map.h atom_vec.h atom_vec_angle.h atom_vec_atomic.h atom_vec_bond.h atom_vec_charge.h atom_vec_dipole.h atom_vec_ellipsoid.h atom_vec_full.h atom_vec_hybrid.h atom_vec_line.h atom_vec_molecular.h atom_vec_peri.h atom_vec_sphere.h atom_vec_tri.h balance.h bond.h bond_class2.h bond_fene.h bond_fene_expand.h bond_harmonic.h bond_hybrid.h bond_morse.h bond_nonlinear.h bond_quartic.h bond_table.h change_box.h comm.h compute.h compute_angle_local.h compute_atom_molecule.h compute_bond_local.h compute_centro_atom.h compute_cluster_atom.h compute_cna_atom.h compute_com.h compute_com_molecule.h compute_contact_atom.h compute_coord_atom.h compute_damage_atom.h compute_dihedral_local.h compute_displace_atom.h compute_erotate_asphere.h compute_erotate_sphere.h compute_erotate_sphere_atom.h compute_event_displace.h compute_group_group.h compute_gyration.h compute_gyration_molecule.h compute_heat_flux.h compute_improper_local.h compute_ke.h compute_ke_atom.h compute_msd.h compute_msd_molecule.h compute_pair.h compute_pair_local.h compute_pe.h compute_pe_atom.h compute_pressure.h compute_property_atom.h compute_property_local.h compute_property_molecule.h compute_rdf.h compute_reduce.h compute_reduce_region.h compute_slice.h compute_stress_atom.h compute_temp.h compute_temp_asphere.h compute_temp_com.h compute_temp_deform.h compute_temp_partial.h compute_temp_profile.h compute_temp_ramp.h compute_temp_region.h compute_temp_sphere.h compute_ti.h create_atoms.h create_box.h delete_atoms.h delete_bonds.h dihedral.h dihedral_charmm.h dihedral_class2.h dihedral_harmonic.h dihedral_helix.h dihedral_hybrid.h dihedral_multi_harmonic.h dihedral_opls.h displace_atoms.h domain.h dump.h dump_atom.h dump_cfg.h dump_custom.h dump_dcd.h dump_image.h dump_local.h dump_xtc.h dump_xyz.h error.h ewald.h fft3d.h fft3d_wrap.h finish.h fix.h fix_adapt.h fix_addforce.h fix_append_atoms.h fix_ave_atom.h fix_ave_correlate.h fix_ave_histo.h fix_ave_spatial.h fix_ave_time.h fix_aveforce.h fix_balance.h fix_bond_break.h fix_bond_create.h fix_bond_swap.h fix_box_relax.h fix_deform.h fix_deposit.h fix_drag.h fix_dt_reset.h fix_efield.h fix_enforce2d.h fix_evaporate.h fix_event.h fix_event_prd.h fix_event_tad.h fix_external.h fix_freeze.h fix_gcmc.h fix_gravity.h fix_heat.h fix_indent.h fix_langevin.h fix_lineforce.h fix_minimize.h fix_momentum.h fix_move.h fix_msst.h fix_neb.h fix_nh.h fix_nh_asphere.h fix_nh_sphere.h fix_nph.h fix_nph_asphere.h fix_nph_sphere.h fix_nphug.h fix_npt.h fix_npt_asphere.h fix_npt_sphere.h fix_nve.h fix_nve_asphere.h fix_nve_asphere_noforce.h fix_nve_limit.h fix_nve_line.h fix_nve_noforce.h fix_nve_sphere.h fix_nve_tri.h fix_nvt.h fix_nvt_asphere.h fix_nvt_sllod.h fix_nvt_sphere.h fix_orient_fcc.h fix_peri_neigh.h fix_planeforce.h fix_pour.h fix_press_berendsen.h fix_print.h fix_qeq_comb.h fix_read_restart.h fix_recenter.h fix_respa.h fix_restrain.h fix_rigid.h fix_rigid_nve.h fix_rigid_nvt.h fix_setforce.h fix_shake.h fix_shear_history.h fix_spring.h fix_spring_rg.h fix_spring_self.h fix_srd.h fix_store_force.h fix_store_state.h fix_temp_berendsen.h fix_temp_rescale.h fix_thermal_conductivity.h fix_tmd.h fix_ttm.h fix_viscosity.h fix_viscous.h fix_wall.h fix_wall_colloid.h fix_wall_gran.h fix_wall_harmonic.h fix_wall_lj126.h fix_wall_lj93.h fix_wall_piston.h fix_wall_reflect.h fix_wall_region.h fix_wall_srd.h force.h group.h image.h improper.h improper_class2.h improper_cvff.h improper_harmonic.h improper_hybrid.h improper_umbrella.h input.h integrate.h irregular.h kissfft.h kspace.h lammps.h lattice.h library.h lmptype.h lmpwindows.h math_const.h math_extra.h memory.h min.h min_cg.h min_fire.h min_hftn.h min_linesearch.h min_quickmin.h min_sd.h minimize.h modify.h neb.h neigh_bond.h neigh_derive.h neigh_full.h neigh_gran.h neigh_half_bin.h neigh_half_multi.h neigh_half_nsq.h neigh_list.h neigh_request.h neigh_respa.h neighbor.h output.h pack.h pair.h pair_adp.h pair_airebo.h pair_beck.h pair_bop.h pair_born.h pair_born_coul_long.h pair_born_coul_wolf.h pair_brownian.h pair_brownian_poly.h pair_buck.h pair_buck_coul_cut.h pair_buck_coul_long.h pair_colloid.h pair_comb.h pair_coul_cut.h pair_coul_debye.h pair_coul_long.h pair_coul_wolf.h pair_dipole_cut.h pair_dpd.h pair_dpd_tstat.h pair_dsmc.h pair_eam.h pair_eam_alloy.h pair_eam_alloy_opt.h pair_eam_fs.h pair_eam_fs_opt.h pair_eam_opt.h pair_eim.h pair_gauss.h pair_gayberne.h pair_gran_hertz_history.h pair_gran_hooke.h pair_gran_hooke_history.h pair_hbond_dreiding_lj.h pair_hbond_dreiding_morse.h pair_hybrid.h pair_hybrid_overlay.h pair_lcbop.h pair_line_lj.h pair_lj96_cut.h pair_lj_charmm_coul_charmm.h pair_lj_charmm_coul_charmm_implicit.h pair_lj_charmm_coul_long.h pair_lj_charmm_coul_long_opt.h pair_lj_class2.h pair_lj_class2_coul_cut.h pair_lj_class2_coul_long.h pair_lj_cubic.h pair_lj_cut.h pair_lj_cut_coul_cut.h pair_lj_cut_coul_debye.h pair_lj_cut_coul_long.h pair_lj_cut_coul_long_opt.h pair_lj_cut_coul_long_tip4p.h pair_lj_cut_coul_long_tip4p_opt.h pair_lj_cut_opt.h pair_lj_expand.h pair_lj_gromacs.h pair_lj_gromacs_coul_gromacs.h pair_lj_smooth.h pair_lj_smooth_linear.h pair_lubricate.h pair_lubricateU.h pair_lubricateU_poly.h pair_lubricate_poly.h pair_morse.h pair_morse_opt.h pair_peri_lps.h pair_peri_pmb.h pair_rebo.h pair_resquared.h pair_soft.h pair_sw.h pair_table.h pair_tersoff.h pair_tersoff_zbl.h pair_tri_lj.h pair_yukawa.h pair_yukawa_colloid.h pointers.h pppm.h pppm_cg.h pppm_old.h pppm_tip4p.h prd.h procmap.h random_mars.h random_park.h read_data.h read_dump.h read_restart.h reader.h reader_native.h reader_xyz.h region.h region_block.h region_cone.h region_cylinder.h region_intersect.h region_plane.h region_prism.h region_sphere.h region_union.h remap.h remap_wrap.h replicate.h rerun.h respa.h run.h set.h special.h style_angle.h style_atom.h style_bond.h style_command.h style_compute.h style_dihedral.h style_dump.h style_fix.h style_improper.h style_integrate.h style_kspace.h style_minimize.h style_pair.h style_reader.h style_region.h suffix.h tad.h temper.h thermo.h timer.h universe.h update.h variable.h velocity.h verlet.h verlet_split.h version.h write_restart.h xdr_compat.h OBJ = $(SRC:.cpp=.o) diff --git a/src/USER-OMP/pair_lj_expand_omp.h b/src/USER-OMP/pair_lj_expand_omp.h index 53728ead6d..8ca3bd41b0 100644 --- a/src/USER-OMP/pair_lj_expand_omp.h +++ b/src/USER-OMP/pair_lj_expand_omp.h @@ -17,7 +17,7 @@ #ifdef PAIR_CLASS -PairStyle(lj/cut/omp,PairLJExpandOMP) +PairStyle(lj/expand/omp,PairLJExpandOMP) #else From 02b9a79d38506587c9a11caa41827fd52a17fc18 Mon Sep 17 00:00:00 2001 From: sjplimp Date: Fri, 17 Aug 2012 13:26:41 +0000 Subject: [PATCH 11/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8679 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- src/KSPACE/fft3d_wrap.h | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/KSPACE/fft3d_wrap.h b/src/KSPACE/fft3d_wrap.h index bf1cdca8e9..d324eb31c3 100644 --- a/src/KSPACE/fft3d_wrap.h +++ b/src/KSPACE/fft3d_wrap.h @@ -39,6 +39,8 @@ class FFT3d : protected Pointers { E: Could not create 3d FFT plan -The FFT setup in pppm failed. +The FFT setup for the PPPM solver failed, typically due +to lack of memory. This is an unusual error. Check the +size of the FFT grid you are requesting. */ From 4cb989a2d3a671c8d49bfc9c94027f4996a72f50 Mon Sep 17 00:00:00 2001 From: sjplimp Date: Fri, 17 Aug 2012 14:51:11 +0000 Subject: [PATCH 12/12] git-svn-id: svn://svn.icms.temple.edu/lammps-ro/trunk@8680 f3b2605a-c512-4ea7-a41b-209d697bcdaa --- doc/Section_python.html | 19 +++++++++++-------- doc/Section_python.txt | 19 +++++++++++-------- 2 files changed, 22 insertions(+), 16 deletions(-) diff --git a/doc/Section_python.html b/doc/Section_python.html index e4d48975b6..64889c3d53 100644 --- a/doc/Section_python.html +++ b/doc/Section_python.html @@ -270,24 +270,27 @@ and type:
>>> from lammps import lammps
 >>> lmp = lammps() 
 
-

If you get no errors, you're ready to use LAMMPS from Python. -If the load fails, the most common error to see is +

If you get no errors, you're ready to use LAMMPS from Python. If the +2nd command fails, the most common error to see is

OSError: Could not load LAMMPS dynamic library 
 

which means Python was unable to load the LAMMPS shared library. This typically occurs if the system can't find the LAMMPS shared library or -one of the auxiliary shared libraries it depends on. The error -message should give you some indication of what went wrong. +one of the auxiliary shared libraries it depends on, or if something +about the library is incompatible with your Python. The error message +should give you an indication of what went wrong.

-

You can also test the load directly in Python as follows +

You can also test the load directly in Python as follows, without +first importing from the lammps.py file:

>>> from ctypes import CDLL
 >>> CDLL("liblammps.so") 
 
-

If an error occurs, carefully go thru the steps above and in -Section_start 5 about building a shared -library and about insuring Python can find the necessary 2 files. +

If an error occurs, carefully go thru the steps in Section_start +5 and above about building a shared +library and about insuring Python can find the necessary two files +it needs.

Test LAMMPS and Python in serial:
diff --git a/doc/Section_python.txt b/doc/Section_python.txt index e21ff33ce8..38fad3451f 100644 --- a/doc/Section_python.txt +++ b/doc/Section_python.txt @@ -266,24 +266,27 @@ and type: >>> from lammps import lammps >>> lmp = lammps() :pre -If you get no errors, you're ready to use LAMMPS from Python. -If the load fails, the most common error to see is +If you get no errors, you're ready to use LAMMPS from Python. If the +2nd command fails, the most common error to see is OSError: Could not load LAMMPS dynamic library :pre which means Python was unable to load the LAMMPS shared library. This typically occurs if the system can't find the LAMMPS shared library or -one of the auxiliary shared libraries it depends on. The error -message should give you some indication of what went wrong. +one of the auxiliary shared libraries it depends on, or if something +about the library is incompatible with your Python. The error message +should give you an indication of what went wrong. -You can also test the load directly in Python as follows +You can also test the load directly in Python as follows, without +first importing from the lammps.py file: >>> from ctypes import CDLL >>> CDLL("liblammps.so") :pre -If an error occurs, carefully go thru the steps above and in -"Section_start 5"_Section_start.html#start_5 about building a shared -library and about insuring Python can find the necessary 2 files. +If an error occurs, carefully go thru the steps in "Section_start +5"_Section_start.html#start_5 and above about building a shared +library and about insuring Python can find the necessary two files +it needs. [Test LAMMPS and Python in serial:] :h5