Path: blob/devel/elmerice/Tests/InvMeth_AdjRobin/PROG/GradientValidation.f90
3206 views
! Compare the total derivative of the cost function computed as:1! (1) dJ=P.G where P is a perturbation vector of the variable of interest2! G is the gradient of the cost function computed by an inverse method3! (2) [J(V+hP)-J(V)]/h : forward finite difference computation of the derivative4! V is the variable of interest5! h is the step size6!7!8! Compute (1) from at the first iteration and update V=Vini+hP, h=19! Compute (2) for all the other iteration with h^i+1=h^i/210!11! Serial/parallel 2D/3D12!13! Keyword in Solver section of the .sif:14! Cost Variable Name15! Optimized Variable Name16! Perturbed Variable Name17! Gradient Variable Name18! Result File19!20! Output: in result File: h , abs((1)-(2))/(1) , (1), (2)21!22!23! *****************************************************************************24SUBROUTINE GradientValidation ( Model,Solver,dt,TransientSimulation )25!------------------------------------------------------------------------------26!******************************************************************************27USE DefUtils28IMPLICIT NONE29!------------------------------------------------------------------------------30TYPE(Solver_t) :: Solver31TYPE(Model_t) :: Model3233REAL(KIND=dp) :: dt34LOGICAL :: TransientSimulation35!36CHARACTER(LEN=MAX_NAME_LEN) :: SolverName37TYPE(Element_t),POINTER :: Element38TYPE(ValueList_t), POINTER :: SolverParams39TYPE(Variable_t), POINTER :: Var,PVar,CostVar,GradVar40REAL(KIND=dp), POINTER :: Values(:),PValues(:),CostValues(:),GradValues(:)41INTEGER, POINTER :: Perm(:),PPerm(:),GradPerm(:)42INTEGER, POINTER :: NodeIndexes(:)4344REAL(KIND=dp),allocatable :: x(:),xp(:),g(:)45REAL(KIND=dp) :: J,J0,h,dJ,dJd4647integer :: i,t,n,NMAX,NActiveNodes48integer :: ierr49integer,allocatable :: ActiveNodes(:)50integer,allocatable :: NewNode(:)51integer,parameter :: io=2052integer :: MyPe=-15354Logical :: FirstVisit=.true.,Found, UnFoundFatal55Logical :: Parallel56logical,allocatable :: VisitedNode(:)5758CHARACTER(LEN=MAX_NAME_LEN) :: CostSolName,VarSolName,GradSolName,PSolName,ResultFile59CHARACTER*10 :: date,temps6061!62save FirstVisit63save SolverName64save CostSolName,VarSolName,GradSolName,ResultFile65save ActiveNodes,NActiveNodes66save x,xp67save J0,h,dJ68save MyPe69save Parallel707172! Read Constant from sif solver section73IF(FirstVisit) Then7475WRITE(SolverName, '(A)') 'GradientValidation'7677! Check we have a parallel run78Parallel = .FALSE.79IF(ASSOCIATED(Solver % Matrix % ParMatrix)) Then80IF ( Solver % Matrix % ParMatrix % ParEnv % PEs > 1 ) Parallel =.True.81MyPe=ParEnv % MyPe82End if838485SolverParams => GetSolverParams()8687!!!!!!!!!!!!find active nodes88NMAX=Solver % Mesh % NumberOfNodes89allocate(VisitedNode(NMAX),NewNode(NMAX))90VisitedNode=.false.91NewNode=-19293NActiveNodes=094DO t=1,Solver % NumberOfActiveElements95Element => GetActiveElement(t)96n = GetElementNOFNodes()97NodeIndexes => Element % NodeIndexes98Do i=1,n99if (VisitedNode(NodeIndexes(i))) then100cycle101else102VisitedNode(NodeIndexes(i))=.true.103NActiveNodes=NActiveNodes+1104NewNode(NActiveNodes)=NodeIndexes(i)105endif106End do107End do108109if (NActiveNodes.eq.0) THEN110WRITE(Message,'(A)') 'NActiveNodes = 0 !!!'111CALL FATAL(SolverName,Message)112End if113114allocate(ActiveNodes(NActiveNodes),x(NActiveNodes),xp(NActiveNodes),g(NActiveNodes))115ActiveNodes(1:NActiveNodes)=NewNode(1:NActiveNodes)116117deallocate(VisitedNode,NewNode)118119!!!!!!! Solver Params120121CostSolName = GetString( SolverParams,'Cost Variable Name', Found)122IF(.NOT.Found) THEN123CALL WARN(SolverName,'Keyword >Cost Variable Name< not found in section >Solver<')124CALL WARN(SolverName,'Taking default value >CostValue<')125WRITE(CostSolName,'(A)') 'CostValue'126END IF127VarSolName = GetString( SolverParams,'Optimized Variable Name', Found)128IF(.NOT.Found) THEN129CALL WARN(SolverName,'Keyword >Optimized Variable Name< not found in section >Solver<')130CALL WARN(SolverName,'Taking default value >Beta<')131WRITE(VarSolName,'(A)') 'Beta'132END IF133PSolName = GetString( SolverParams,'Perturbed Variable Name', Found)134IF(.NOT.Found) THEN135CALL WARN(SolverName,'Keyword >Perturbed Variable Name< not found in section >Solver<')136CALL WARN(SolverName,'Taking default value >BetaP<')137WRITE(VarSolName,'(A)') 'BetaP'138END IF139GradSolName = GetString( SolverParams,'Gradient Variable Name', Found)140IF(.NOT.Found) THEN141CALL WARN(SolverName,'Keyword >Gradient Variable Name< not found in section >Solver<')142CALL WARN(SolverName,'Taking default value >DJDB<')143WRITE(GradSolName,'(A)') 'DJDB'144END IF145ResultFile=GetString( SolverParams,'Result File',Found)146IF(Found) Then147IF ((Parallel.AND.(MyPe.EQ.0)).OR.(.NOT.Parallel)) Then148open(io,file=trim(ResultFile))149CALL DATE_AND_TIME(date,temps)150write(io,'(a1,a2,a1,a2,a1,a4,5x,a2,a1,a2,a1,a2)')'#',date(5:6),'/',date(7:8),'/',date(1:4), &151temps(1:2),':',temps(3:4),':',temps(5:6)152write(io,'(A)') '# step size, relative error, Adjoint total der., FD total der.'153close(io)154ENDIF155ELSE156CALL FATAL(SolverName,'Keyword <Result File> Not Found')157ENDIF158159!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!160CostVar => VariableGet( Solver % Mesh % Variables, CostSolName,UnFoundFatal=UnFoundFatal)161CostValues => CostVar % Values162163Var => VariableGet( Solver % Mesh % Variables, VarSolName,UnFoundFatal=UnFoundFatal)164Values => Var % Values165Perm => Var % Perm166167PVar => VariableGet( Solver % Mesh % Variables, PSolName,UnFoundFatal=UnFoundFatal)168PValues => PVar % Values169PPerm => PVar % Perm170171GradVar => VariableGet( Solver % Mesh % Variables, GradSolName,UnFoundFatal=UnFoundFatal)172GradValues => GradVar % Values173GradPerm => GradVar % Perm174175x(1:NActiveNodes)=Values(Perm(ActiveNodes(1:NActiveNodes)))176g(1:NActiveNodes)=GradValues(GradPerm(ActiveNodes(1:NActiveNodes)))177xp(1:NActiveNodes)=PValues(PPerm(ActiveNodes(1:NActiveNodes)))178179!!!!!! On calcul la dervivee totale à partir de la valeur du180!gradient181dJ=0._dp182Do i=1,NActiveNodes183dJ=dJ+xp(i)*g(i)184End do185deallocate(g)186187IF (Parallel) THEN188CALL MPI_ALLREDUCE(dJ,dJ,1,&189MPI_DOUBLE_PRECISION,MPI_SUM,MPI_COMM_WORLD,ierr)190ENDIF191192193!!!!! On sauve la valeur de J0 pour le calcul diffrence fini.194J0=CostValues(1)195196!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!197h=1.0_dp198Do i=1,NActiveNodes199Values(Perm(ActiveNodes(i)))=x(i)+h*xp(i)200End do201202203FirstVisit=.FALSE.204Return205End if206!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!207208CostVar => VariableGet( Solver % Mesh % Variables, CostSolName,UnFoundFatal=UnFoundFatal)209CostValues => CostVar % Values210211Var => VariableGet( Solver % Mesh % Variables, VarSolName,UnFoundFatal=UnFoundFatal)212Values => Var % Values213Perm => Var % Perm214215216J=CostValues(1)217218dJd=(J-J0)/h219220IF (Parallel) MyPe=ParEnv % MyPe221IF ((Parallel.AND.(MyPe.EQ.0)).OR.(.NOT.Parallel)) Then222open(io,file=trim(ResultFile),position='append')223write(io,'(4(e15.8,2x))') h,abs(dJ-dJd)/abs(dJ),dJ,dJd224close(io)225ENDIF226227h=h/2.0_dp228Do i=1,NActiveNodes229Values(Perm(ActiveNodes(i)))=x(i)+h*xp(i)230End Do231232Return233!------------------------------------------------------------------------------234END SUBROUTINE GradientValidation235!------------------------------------------------------------------------------236237238239240