save_fe_field Subroutine

public subroutine save_fe_field(fe_f, file_name, code, nodal)

Arguments

Type IntentOptional AttributesName
type(FE_FILM), intent(in) :: fe_f
character(len=*), intent(in) :: file_name
integer(kind=I4), intent(in) :: code
logical(kind=I4), intent(in) :: nodal

if false : cell value, if true : nodal value


Calls

proc~~save_fe_field~~CallsGraph proc~save_fe_field save_fe_field proc~write_surf write_surf proc~save_fe_field->proc~write_surf proc~empty empty proc~save_fe_field->proc~empty proc~init_scal init_scal proc~save_fe_field->proc~init_scal proc~lower lower proc~write_surf->proc~lower proc~scal2surf scal2surf proc~write_surf->proc~scal2surf proc~surf2scal surf2scal proc~write_surf->proc~surf2scal proc~get_unit get_unit proc~write_surf->proc~get_unit proc~init_scal->proc~empty proc~c_f_string c_f_string proc~surf2scal->proc~c_f_string proc~c_f_string->proc~empty

Called by

proc~~save_fe_field~~CalledByGraph proc~save_fe_field save_fe_field proc~solve_fe_prob solve_fe_prob proc~solve_fe_prob->proc~save_fe_field proc~test_rough_fe test_rough_fe proc~test_rough_fe->proc~solve_fe_prob proc~test_bearing_x_fe test_bearing_x_fe proc~test_bearing_x_fe->proc~solve_fe_prob proc~test_slider_fe test_slider_fe proc~test_slider_fe->proc~solve_fe_prob proc~test_pocket_fe test_pocket_fe proc~test_pocket_fe->proc~solve_fe_prob proc~test_bearing_y_fe test_bearing_y_fe proc~test_bearing_y_fe->proc~solve_fe_prob proc~run_test run_test proc~run_test->proc~test_rough_fe proc~run_test->proc~test_bearing_x_fe proc~run_test->proc~test_slider_fe proc~run_test->proc~test_pocket_fe proc~run_test->proc~test_bearing_y_fe program~main main program~main->proc~run_test

Contents

Source Code


Source Code

   subroutine save_fe_field(fe_f, file_name, code, nodal)
   implicit none
   type(FE_FILM),    intent(in) :: fe_f
   character(len=*), intent(in) :: file_name
   integer(kind=I4), intent(in) :: code
   logical(kind=I4), intent(in) :: nodal !! if false : cell value, if true : nodal value

      integer(kind=I4) :: nx, ny
      integer(kind=I4), dimension(1) :: i1, i2
      real(kind=R8), allocatable, dimension(:,:) :: tab_s
      real(kind=R8) :: lx, ly
      character(len=8) :: unit_z

      nx = fe_f%m%nx
      ny = fe_f%m%ny
      lx = fe_f%m%lx
      ly = fe_f%m%ly

      call empty(unit_z)

      if (.not.nodal) then
         nx = nx -1
         ny = ny -1
      endif

      allocate( tab_s(1:nx, 1:ny) ) ; tab_s = -1.

      if (nodal) then
         tab_s = reshape( fe_f%vn(:, code), (/nx, ny/) )
         i1 = index(fe_f%vn_name(code), '(') +1
         i2 = index(fe_f%vn_name(code), ')') -1
         unit_z = fe_f%vn_name(code)(i1(1):i2(1))
      else
         tab_s = reshape( fe_f%vc(:, code), (/nx, ny/) )
         i1 = index(fe_f%vc_name(code), '(') +1
         i2 = index(fe_f%vc_name(code), ')') -1
         unit_z = fe_f%vc_name(code)(i1(1):i2(1))
      endif

      call init_scal(scal = scal_tmp, & !
                       nx = nx,       & !
                       ny = ny,       & !
                       lx = lx,       & ! default unit : m
                       ly = ly,       & !
                   unit_z = unit_z    ) !

      call write_surf(nom_fic = file_name,  & !
                        tab_s = tab_s,      & !
                         scal = scal_tmp    )

      deallocate(tab_s)
   return
   endsubroutine save_fe_field