Skip to content
Snippets Groups Projects
visualise_matrix.f90 4.5 KiB
Newer Older
  • Learn to ignore specific revisions
  • !------------------------------------------------------------------------------|
    !------------------------------------------------------------------------------|
    !                                                                              |
    !              ||===\\                                                         | 
    !              ||    \\                                                        |
    !              ||     ||   //==\\   ||  ||   //==||  ||/==\\                   |
    !              ||     ||  ||    ||  ||  ||  ||   ||  ||    ||                  |
    !              ||    //   ||    ||  ||  ||  ||   ||  ||                        |
    !              ||===//     \\==//    \\==\\  \\==\\  ||                        |
    !                                                                              |
    !------------------------------------------------------------------------------|
    !------------------------------------------------------------------------------|
    !                                                                              |
    !              VISUALISE_MATRIX    Apr. 2008                                   |
    !                                                                              |
    !------------------------------------------------------------------------------|
    !------------------------------------------------------------------------------|
    
    subroutine visualise_matrix (nz,irn,jcn,n,istep,iter,ndof)
    
    
    implicit none
    
    
    !------------------------------------------------------------------------------|
    !(((((((((((((((( Purpose of the routine  ))))))))))))))))))))))))))))))))))))))
    !------------------------------------------------------------------------------|
    ! this routine uses the (irn,jcn) coordinates of the non-zero terms of the 
    ! matrix to build a visual representation of it.
    
    !------------------------------------------------------------------------------|
    !((((((((((((((((  declaration of the subroutine arguments  ))))))))))))))))))))
    !------------------------------------------------------------------------------|
    integer nz,n,istep,iter,ndof
    integer irn(nz),jcn(nz)
    
    !------------------------------------------------------------------------------|
    !(((((((((((((((( declaration of the subroutine internal variables )))))))))))))
    !------------------------------------------------------------------------------|
    integer ierr,iproc,nproc,inz,ncolours,pgopen,istat
    double precision dxyz,alpha,beta,alpha_offset,beta_offset
    double precision ratio,colour,ps_scale
    logical flag_colour
    character(len=3) :: colormap
    character(len=4) :: cistep,citer
    character(len=10) :: cn,cnz
    
    !-------------------------------------------------------------------------------
    !-------------------------------------------------------------------------------
    
    call mpi_comm_size (mpi_comm_world,nproc,ierr)
    call mpi_comm_rank (mpi_comm_world,iproc,ierr)
    
    if (iproc.eq.0) then
    
       call int_to_char(cistep,4,istep)
       call int_to_char(citer,4,iter)
    
    
       if (ndof==3) then
          istat=pgopen('./DEBUG/MATRIX/visual_matrix3_'//cistep//'_'//citer//'.ps/VCPS')
       else
          istat=pgopen('./DEBUG/MATRIX/visual_matrix1_'//cistep//'.ps/VCPS')
       end if
       if (istat .le.0) stop 'pb snapshot visualise matrix'
    
       CALL PGBBUF                       ! begin batch of output
       CALL PGSAVE                       ! save pgplot attributes
       CALL PGSCH(0.5)                   ! set character height
       CALL PGPAGE                       ! advance to new page
       CALL PGSFS (2)                    ! set fill style : outline
       CALL PGENV(-0.1,1.1,-.1,1.1,1,-1) ! set window and viewport
       CALL PGRECT(0.,1.,0.,1.)          ! draw unit square
       CALL PGSLW (1)                    ! set line width
      
       !=====[plotting the nz terms as dots]===== 
       CALL PGPT (nz, real(jcn)/real(n), 1.0-real(irn)/real(n),  -1)
    
       !=====[writing information on graph]=====
       CALL PGSCI (1) ! use colour number 1
       CALL PGSCH (0.75) ! set character height
       if (ndof==3) then
          CALL PGPTXT (0.0,1.01,0.0,0.0,'3 dofs per node')
       else
          CALL PGPTXT (0.0,1.01,0.0,0.0,'1 dof per node')
       end if
       CALL PGPTXT (0.5,1.01,0.0,0.0,'istep='//cistep//' iter='//citer)
       call int_to_char(cn, 10,n)
       call int_to_char(cnz,10,nz)
       CALL PGPTXT (0.0,-0.05,0.0,0.0,'n='//cn)
       CALL PGPTXT (0.4,-0.05,0.0,0.0,'nz='//cnz)
    
       CALL PGUNSA
       CALL PGEBUF
       CALL PGCLOS
    
    end if
    
    return
    end subroutine visualise_matrix
    
    !-------------------------------------------------------------------------------
    !-------------------------------------------------------------------------------