Genetic_base/src/model/data_transform.f90

41 lines
1.2 KiB
Fortran

! <subroutine for manipulating the input Data before the Fit
subroutine data_transform(q,x1,x2,y,wt,p,npar,p_act)
use dim_parameter,only : nstat,pst,ntot,qn,numdatpt,ndiab
use ctrans_mod, only: ctrans
use data_matrix
! use david_ctrans_mod, only: ctrans_d
implicit none
! IN: variables
integer npar
double precision q(qn,numdatpt),x1(qn,numdatpt),x2(qn,numdatpt)
double precision y(ntot,numdatpt),wt(ntot,numdatpt)
double precision p(npar),mat_x(ndiab,ndiab),mat_y(ndiab,ndiab)
double precision v(ndiab,ndiab),E(nstat)
integer p_act(npar), pt
logical dbg
parameter (dbg=.false.)
integer TYPES,BLK ! TYPE OF THE CALCULATION AND THE BLOCK IF TYEPE IS 3
double precision U(ndiab,ndiab), U_ref(ndiab,ndiab) ! Transformation matrix
! get the ref transformation matrix
!call eval_surface(E,V,U_ref,q(1:qn,1),p)
do pt=1,numdatpt
call ctrans(q(1:qn,pt),x1(:,pt),x2(:,pt))! ctrans the dipole cooordinate.
!call ctrans_pes(q(1:qn,pt),x1(:,pt),x2(:,pt))
write(7,'(6f18.8)') x1(1:6,pt)
y(11:ntot,pt)=-y(11:ntot,pt)
enddo
call weight(wt,y)
end subroutine