fortran66のブログ

fortran について書きます。

Windows窓絵もOOPで。

やっつけで。

Win32窓用のコールバックルーチン等への変数の受け渡し方がきれいにかけてません。
intel fortran の問題だと思いますが、構造体の要素として構造体を持つ場合の生成子でコンパイラのエラーが出ます。

Win32で実行時に表示されるwindowの図。

ファイルとして出力される図。
HTML5 (canvas)

PS (EPS) (座標系の向きが逆転しているので逆さになっているw)


メインルーチンで、基底classにそれぞれの派生形を割り付けることで出力を制御しています。それ以外は共通の命令を用いることができます。この手の問題がOOP向きなのではないかと思います。

program oop
  use m_plot
  implicit none
  class(t_device), allocatable :: fig
  type(t_rgb) :: rgb_black = t_rgb(0, 0, 0)
  
  allocate(fig, source = t_win32('test', 640, 480, 1, rgb_black ))
  call fig%on()
  call fig%moveTo(0, 0)
  call fig%lineTo(500, 200)
  call fig%pen(1, t_rgb(0, 0, 255))
  call fig%moveTo(500, 200)
  call fig%lineTo(100, 200)
  call fig%pen(2, t_rgb(0, 255, 255))
  call fig%moveTo(100, 200)
  call fig%lineTo(100, 480)
  call fig%off()
  deallocate(fig)

  allocate(fig, source = t_html('test', 640, 480, 1, rgb_black ))
  call fig%on()
  call fig%moveTo(0, 0)
  call fig%lineTo(500, 200)
  call fig%pen(1, t_rgb(0, 0, 255))
  call fig%moveTo(500, 200)
  call fig%lineTo(100, 200)
  call fig%pen(2, t_rgb(0, 255, 255))
  call fig%moveTo(100, 200)
  call fig%lineTo(100, 480)
  call fig%off()
  deallocate(fig)
  
  allocate(fig, source = t_ps('test', 640, 480, 1, rgb_black ))
  call fig%on()
  call fig%moveTo(0, 0)
  call fig%lineTo(500, 200)
  call fig%pen(1, t_rgb(0, 0, 255))
  call fig%moveTo(500, 200)
  call fig%lineTo(100, 200)
  call fig%pen(2, t_rgb(0, 255, 255))
  call fig%moveTo(100, 200)
  call fig%lineTo(100, 480)
  call fig%off()
  deallocate(fig)
  
  stop  
end program oop

ソース

module m_oop
  implicit none

  type :: t_rgb
    integer :: ir, ig, ib
  end type t_rgb
  
  type, abstract :: t_device
    character(len = 80) :: title = 'Plotter'
    integer :: nsize_x = 640, nsize_y = 480
    integer :: line_width = 1
    type (t_rgb) :: rgb = t_rgb(0, 0, 0)
  contains
    procedure (device_on), deferred, pass :: on
    procedure (device_off), deferred, pass :: off
    procedure (device_show), deferred, pass :: show
    procedure (device_pen), deferred, pass :: pen
    procedure (device_lineTo), deferred, pass :: lineTo
    procedure (device_moveTo), deferred, pass :: moveTo
  end type t_device 

  abstract interface 
    subroutine device_on(self)
      import :: t_device
      class(t_device), intent(in out) :: self
    end subroutine device_on
  
    subroutine device_off(self)
      import :: t_device
      class(t_device), intent(in) :: self
    end subroutine device_off

    subroutine device_show(self)
      import :: t_device
      class(t_device), intent(in) :: self
    end subroutine device_show
    
    subroutine device_pen(self, line_width, rgb)
      import :: t_device, t_rgb
      class(t_device), intent(in out) :: self
      integer, intent(in), optional :: line_width
      type (t_rgb), intent(in), optional :: rgb
    end subroutine device_pen

    subroutine device_lineTo(self, ix, iy)
      import :: t_device
      class(t_device), intent(in) :: self
      integer, intent(in) :: ix, iy
    end subroutine device_lineTo
  
    subroutine device_moveTo(self, ix, iy)
      import :: t_device
      class(t_device), intent(in) :: self
      integer, intent(in) :: ix, iy
    end subroutine device_moveTo
  end interface

end module m_oop


module m_win32
  use ifwina
  use ifwinty
  use ifmt, only : RTL_CRITICAL_SECTION
  use m_oop
  implicit none

  type, extends(t_device) :: t_win32
  contains 
    procedure, pass :: on => gr_on
    procedure, pass :: off => gr_off
    procedure, pass :: show => gr_show
    procedure, pass :: pen => gr_pen
    procedure, pass :: lineTo => gr_lineTo
    procedure, pass :: moveTo => gr_moveTo
  end type t_win32

  type :: t_wnd
    integer (HANDLE) :: hWnd    
    integer (HANDLE) :: hDC       
    integer (LPINT)  :: hThread  
    integer (LPDWORD):: id      
    integer (HANDLE) :: hPen     
  end type t_wnd      

  type (t_wnd) :: wnd
  type (RTL_CRITICAL_SECTION) :: lpCriticalSection
  
contains
  !--------------------------------------------------------------------------------
  integer(4) function WinMain( hInstance, nCmdShow, w_win32 )
    implicit none
    integer (HANDLE), intent(in) :: hInstance 
    integer (SINT)  , intent(in) :: nCmdShow
    type (t_win32), intent(in) :: w_win32
    type (T_WNDCLASS) :: wc
    type (T_MSG)      :: mesg
    integer (HANDLE)  :: hWndMain
    integer (BOOL)    :: iretb
    character (LEN = 256) :: ClassName = 'Fortran'//char(0)
    integer :: iwindow_frame_x, iwindow_frame_y 
    ! Init Main window
    iwindow_frame_x = 2 * GetSystemMetrics(SM_CXFIXEDFRAME) !side line = 6, title bar = 25
    iwindow_frame_y = 2 * GetSystemMetrics(SM_CYFIXEDFRAME) + GetSystemMetrics(SM_CYCAPTION)
    !
    WinMain = -1 ! Error code 
    wc%lpszClassName =  loc(ClassName)     ! non-standard Fortran :: LOC(xxx) = TRANSFER(C_LOC(xxx), iii)
    wc%lpfnWndProc   =  loc(MainWndProc)   ! CALLBACK procedure name
    wc%style        = ior(CS_VREDRAW , CS_HREDRAW)
    wc%hInstance     = hInstance
    wc%hIcon        = NULL   
    wc%hCursor      = LoadCursor( NULL, IDC_ARROW )
    wc%hbrBackground = ( COLOR_WINDOW + 1 )
    if ( RegisterClass(wc) == 0 ) return    ! initialize window
    ! Init instance
    WinMain = -2 ! Error code 
    hWndMain = CreateWindowEx(  0, ClassName,                        &
                                trim(w_win32%title)//char(0),           &
                                int(ior(WS_OVERLAPPED, WS_SYSMENU)), &
                                CW_USEDEFAULT, CW_USEDEFAULT,       &
                                w_win32%nsize_x + iwindow_frame_x,      &
                                w_win32%nsize_y + iwindow_frame_y,      &
                                0, 0,                            &
                                hInstance,                        &
                                NULL                           ) 
    if (hWndMain == 0) return
    iretb = ShowWindow( hWndMain, nCmdShow )
    iretb = UpdateWindow( hWndMain )
    ! Message Loop
    do while ( GetMessage (mesg, NULL, 0, 0) ) 
      iretb = TranslateMessage( mesg ) 
      iretb = DispatchMessage(  mesg )
    end do
    WinMain = mesg%wParam
    return
  end function WinMain
  !-------------------------------------------------------------------------------------
  integer (LRESULT) function MainWndProc( hWnd, mesg, wParam, lParam ) 
  !DEC$ ATTRIBUTES STDcall, DECORATE, ALIAS : 'MainWndProc' :: MainWndProc
    integer (HANDLE) , intent(in) :: hWnd
    integer (UINT)   , intent(in) :: mesg
    integer (fwParam), intent(in) :: wParam
    integer (flParam), intent(in) :: lParam
    !
    integer (HANDLE) :: hDC, hBmp
    integer (BOOL)   :: iretb
    type (T_PAINTSTRUCT) :: ps
    type (T_RECT)       :: rc
    !
    MainWndProc = 0
    select case ( mesg )
      case (WM_CREATE)
        wnd%hWnd = hWnd
        hDC      = GetDC(hWnd)
        wnd%hDC  = CreateCompatibleDC(hDC)
        iretb    = GetClientRect(hWnd, rc)
        hBmp     = CreateCompatibleBitmap(hDC, rc%right - rc%left, rc%bottom - rc%top)
        iretb    = SelectObject(wnd%hDC, hBmp)
        iretb    = PatBlt(wnd%hDC, 0, 0, rc%right - rc%left, rc%bottom - rc%top, WHITENESS)
        iretb    = ReleaseDC(hWnd, hDC)
        iretb    = DeleteObject(hBmp)
      case (WM_DESTROY)
        iretb = DeleteObject( wnd%hDC )
        call PostQuitMessage( 0 )
      case (WM_PAINT)
        call EnterCriticalSection( loc(lpCriticalSection) )
        hDC    = BeginPaint(    wnd%hWnd, ps )
        iretb  = GetClientRect( wnd%hWnd, rc )
        iretb  = BitBlt(hDC, 0, 0, rc%right - rc%left, rc%bottom - rc%top, wnd%hDC, 0, 0, SRCCOPY)
        iretb  = endPaint( wnd%hWnd, ps )
        call LeaveCriticalSection( loc(lpCriticalSection) )
      case (WM_RBUTTONUP)
        iretb = DeleteObject( wnd%hDC )
        call PostQuitMessage( 0 )
      case default
        MainWndProc = DefWindowProc( hWnd, mesg, wParam, lParam )
    end select 
    return
  end function MainWndProc
  !-------------------------------------------------------------------------------------
  subroutine gr_on(self)
    use IFMT, only : CreateThread ! multithread module
    class(t_win32), intent(in out) :: self
    integer (BOOL)    :: iretb
    integer (HANDLE)  :: hBmp
    type (T_RECT)    :: rc
    call InitializeCriticalSection( loc(lpCriticalSection) ) ! non-standard Fortran :: LOC
    wnd%hThread = CreateThread(NULL, 0, Thread_Proc, NULL, CREATE_SUSPENDED, wnd%id) 
    iretb      = SetThreadPriority(wnd%hThread, THREAD_PRIORITY_BELOW_NORMAL)
    iretb      = ResumeThread(wnd%hThread)
    call sleep(100) ! wait for Window initialization 
    iretb = GetClientRect(wnd%hWnd, rc)
    hBmp  = CreateCompatibleBitmap(wnd%hDC, rc%right - rc%left, rc%bottom - rc%top)
    iretb = SelectObject(wnd%hDC, hBmp)
    iretb = DeleteObject(hBmp)
    iretb = PatBlt(wnd%hDC, 0, 0, rc%right - rc%left, rc%bottom - rc%top, WHITENESS)
    wnd%hPen = CreatePen(PS_SOLID, 1, 0)
    return
  contains 

    integer (LONG) function Thread_Proc(lp_ThreadParameter)
    !DEC$ ATTRIBUTES STDcall, ALIAS:"_thread_proc" :: Thread_Proc
      integer (LPINT), intent(in) :: lp_ThreadParameter
      integer :: hInst
      hInst      = GetModuleHandle(NULL)
      Thread_Proc = WinMain(hInst, SW_SHOWNORMAL, self)
      return
    end function Thread_Proc
    
  end subroutine gr_on
  !-------------------------------------------------------------------------------------
  subroutine gr_off(self)
    class(t_win32), intent(in) :: self
    integer (BOOL)  :: iretb
    integer (DWORD) :: iwait
    iwait = INFINITE
    call gr_show(self) 
    iretb = DeleteObject(wnd%hPen) 
    iretb = WaitForSingleObject(wnd%hThread, iwait)
    iretb = CloseHandle(wnd%hThread)
    iretb = PostMessage(wnd%hWnd, WM_DESTROY, NULL, NULL)
    wnd%hThread = NULL
    call DeleteCriticalSection( loc(lpCriticalSection) ) ! non-standard Fortran :: LOC
    return
  end subroutine gr_off
  !-------------------------------------------------------------------------------------
  subroutine gr_show(self)
    class(t_win32), intent(in) :: self
    integer (BOOL):: iretb
    call EnterCriticalSection( loc(lpCriticalSection) ) ! non-standard Fortran :: LOC
    iretb = InvalidateRect(wnd%hWnd, NULL, FALSE)
    call LeaveCriticalSection( loc(lpCriticalSection) ) ! non-standard Fortran :: LOC
    return
  end subroutine gr_show
  !-------------------------------------------------------------------------------------
  subroutine gr_pen(self, line_width, rgb)
    class(t_win32), intent(in out) :: self
    integer, intent(in), optional :: line_width
    type (t_rgb), intent(in), optional :: rgb
    integer (BOOL) :: iretb
    associate( rgb_ => self%rgb, line_width_ => self%line_width )
      if ( present(rgb) ) rgb_ = rgb
      if ( present(line_width) ) line_width_ = line_width
      call EnterCriticalSection( loc(lpCriticalSection) ) ! non-standard Fortran :: LOC  
      iretb    = DeleteObject(wnd%hPen) 
      wnd%hPen = CreatePen(PS_SOLID, line_width_, irgb(rgb_))
      iretb    = SelectObject(wnd%hDC, wnd%hPen)
      iretb    = MoveToEx(wnd%hDC, 0, 0, NULL)
      call LeaveCriticalSection( loc(lpCriticalSection) ) ! non-standard Fortran :: LOC
    end associate
    return
  contains 
    integer function irgb(rgb)
      type(t_rgb), intent(in) :: rgb
      irgb = rgb%ir + (rgb%ig + (rgb%ib * 256)) * 256
      return
    end function irgb
  end subroutine gr_pen
  !----------------------------------------------------------------
  subroutine gr_moveTo(self, ix, iy)
    class(t_win32), intent(in) :: self
    integer, intent(in) :: ix, iy
    integer (BOOL):: iretb
    call EnterCriticalSection( loc(lpCriticalSection) ) ! non-standard Fortran :: LOC
    iretb = MoveToEx(wnd%hDC, ix, iy, NULL)
    call LeaveCriticalSection( loc(lpCriticalSection) ) ! non-standard Fortran :: LOC
  return
  end subroutine gr_moveTo
  !----------------------------------------------------------------
  subroutine gr_lineTo(self, ix, iy)
    class(t_win32), intent(in) :: self
    integer, intent(in) :: ix, iy
    integer (BOOL):: iretb
    call EnterCriticalSection( loc(lpCriticalSection) ) ! non-standard Fortran :: LOC
    iretb = LineTo(wnd%hDC, ix, iy)
    call LeaveCriticalSection( loc(lpCriticalSection) ) ! non-standard Fortran :: LOC
    return
  end subroutine gr_lineTo
  !----------------------------------------------------------------
 end module m_win32
 


 module m_html
  use m_oop
  implicit none
  private
  public :: t_html
  type, extends(t_device) :: t_html
    integer :: iw = 9
  contains 
    procedure, pass :: on => html_on
    procedure, pass :: off => html_off
    procedure, pass :: show => html_show
    procedure, pass :: pen => html_pen
    procedure, pass :: lineTo => html_lineTo
    procedure, pass :: moveTo => html_moveTo
  end type t_html
contains
  !----------------------------------------------------------------
  subroutine html_on(self)
    class(t_html), intent(in out) :: self
    associate (iw => self%iw, title => self%title)
      open(iw, file = trim(title) // '.html')
      write(iw, '(a)') '<!DOCTYPE html>'
      write(iw, '(a)') '<html>'
      write(iw, '(a)') '<head>'
      write(iw, '(a)') '<meta charset="Shift_JIS">'
      write(iw, '(3a)') '<title>', trim(title), '</title>'
      write(iw, '(a)')  '<script type="text/javascript">'
      write(iw, '(a)') '<!--'
      write(iw, '(a)') 'function plotter() {'
      write(iw, '(3a)') "var canvas = document.getElementById('", trim(title), "');"
      write(iw, '(a)') "var context = canvas.getContext('2d');"
      write(iw, '(a)') '//'
      write(iw, '(a)') 'context.scale(1, 1);'
      write(iw, '(a)') 'context.lineWidth = 1;'               ! pen default
      write(iw, '(a)') "context.strokeStyle = 'rgb(0, 0, 0)';"  ! pen default
      write(iw, '(a)') 'context.lineCap = "butt";'
      write(iw, '(a)') 'context.beginPath();'
    end associate
    return
  end subroutine html_on
  !----------------------------------------------------------------
  subroutine html_off(self)
    class(t_html), intent(in) :: self
    associate (iw => self%iw, title => self%title, nx => self%nsize_x, ny => self%nsize_y)
      write(iw, '(a)') 'context.stroke();'
      write(iw, '(a)') '}'
      write(iw, '(a)') '//-->'
      write(iw, '(a)') '</script>'
      write(iw, '(a)') '</head>'
      write(iw, '(a)') '<body onLoad="plotter()">'
      write(iw, '(3a, i6, a, i6, a)') '<canvas id="', trim(title) , '" width="', nx, '" height="', ny, '">'
      write(iw, '(a)') '</canvas>'
      write(iw, '(a)') '</body>'
      write(iw, '(a)') '</html>' 
    end associate
    return
  end subroutine html_off
  !----------------------------------------------------------------
  subroutine html_show(self)
    class(t_html), intent(in) :: self
    write(self%iw, '(a)') 'context.stroke();'
    write(self%iw, '(a)') 'context.beginPath();'
    return
  end subroutine html_show
  !----------------------------------------------------------------
  subroutine html_pen(self, line_width, rgb)
    class(t_html), intent(in out) :: self
    integer, intent(in), optional :: line_width
    type (t_rgb), intent(in), optional :: rgb
    associate (iw => self%iw, rgb_ => self%rgb, line_width_ => self%line_width)
      if ( present(line_width) ) line_width_ = line_width
      if ( present(rgb) ) rgb_ = rgb
      write(iw, '(a)') 'context.stroke();'
      write(iw, '(a, 3(i3, a))') "context.strokeStyle = 'rgb(", rgb_%ir, ',', rgb_%ig, ',', rgb_%ib, ")';"
      write(iw, '(a,  i5, a)') 'context.lineWidth =', line_width_, ';'
      write(iw, '(a)') 'context.beginPath();'
      write(iw, '(a, i7, a, i7, a)') 'context.moveTo( 0, 0);'
    end associate
    return
  end subroutine html_pen
  !----------------------------------------------------------------
  subroutine html_lineTo(self, ix, iy)
    class(t_html), intent(in) :: self
    integer, intent(in) :: ix, iy
    write(self%iw, '(a, i7, a, i7, a)') 'context.lineTo(', ix, ',', iy, ');'
    return
  end subroutine html_lineTo
  !----------------------------------------------------------------
  subroutine html_moveTo(self, ix, iy)
    class(t_html), intent(in) :: self
    integer, intent(in) :: ix, iy
    write(self%iw, '(a, i7, a, i7, a)') 'context.moveTo(', ix, ',', iy, ');'
    return
  end subroutine html_moveTo  
end module m_html



module m_PS
use m_oop
  implicit none
  private
  public :: t_PS
  type, extends(t_device) :: t_PS
    integer :: iw = 9
  contains 
    procedure, pass :: on => ps_on
    procedure, pass :: off => ps_off
    procedure, pass :: show => ps_show
    procedure, pass :: pen => ps_pen
    procedure, pass :: lineTo => ps_lineTo
    procedure, pass :: moveTo => ps_moveTo
  end type t_PS
contains
  !----------------------------------------------------------------
  subroutine ps_on(self)
    class(t_ps), intent(in out) :: self
    associate (iw => self%iw, title => self%title)
      open(iw, file = trim(title) // '.ps')
      write(iw, '(a)') '%!PS-Adobe-3.0 EPSF-3.0'
      write(iw, '(a, 2i8)') '%%BoundingBox: 0 0 ', self%nsize_x, self%nsize_y
      write(iw, '(2a)') '%%Title: ', trim(self%title)
      write(iw, '(a)') '%%EndComments'
      write(iw, '(a)') 'gsave'
      write(iw, '(a)') '1 1 scale'
      write(iw, '(a)') '1 setlinewidth'
      write(iw, '(a)') '0.0 0.0 0.0 setrgbcolor'
      write(iw, '(a)') '2 setlinejoin'
      write(iw, '(a)') 'newpath'
    end associate
    return
  end subroutine ps_on
  !-------------------------------------------------------------------------------------
  subroutine ps_off(self)
    class(t_ps), intent(in) :: self
    write(self%iw, '(a)') 'stroke'
    write(self%iw, '(a)') 'showpage'
    write(self%iw, '(a)') 'grestore'
    write(self%iw, '(a)') '%%EOF'
    return
  end subroutine ps_off
  !-------------------------------------------------------------------------------------
  subroutine ps_show(self)
    class(t_ps), intent(in) :: self
    write(self%iw, '(a)') 'stroke'
    write(self%iw, '(a)') 'newpath'
    return
  end subroutine ps_show
  !-------------------------------------------------------------------------------------
  subroutine ps_pen(self, line_width, rgb)
    class(t_ps), intent(in out) :: self
    integer, intent(in), optional :: line_width
    type (t_rgb), intent(in), optional :: rgb
    associate (iw => self%iw, rgb_ => self%rgb, line_width_ => self%line_width)
      if ( present(rgb) ) rgb_ = rgb
      if ( present(line_width) ) line_width_ = line_width
      write(iw, '(a)') 'stroke'
      write(iw, '(3f7.3, a)') rgb_%ir / 255.0, rgb_%ig / 255.0, rgb_%ib / 255.0, " setrgbcolor"
      write(iw, '(i5, a)') line_width_, ' setlinewidth'
      write(iw, '(a)') 'newpath'
      write(iw, '(a)') ' 0 0 moveto'
    end associate
    return
  end subroutine ps_pen
  !-------------------------------------------------------------------------------------
  subroutine ps_moveTo(self, ix, iy)
    class(t_ps), intent(in) :: self
    integer, intent(in) :: ix, iy
    write(self%iw, '(2i7, a)') ix, iy, ' moveto'
    return
  end subroutine ps_moveTo
  !----------------------------------------------------------------
  subroutine ps_lineTo(self, ix, iy)
    class(t_ps), intent(in) :: self
    integer, intent(in) :: ix, iy
    write(self%iw, '(2i7, a)') ix, iy, ' lineto'
    return
  end subroutine ps_lineTo
end module m_PS


module m_plot
  use m_oop
  use m_html
  use m_PS
  use m_win32
  implicit none
  private
  public :: t_rgb, t_device, t_html, t_PS, t_win32
end module m_plot


program oop
  use m_plot
  implicit none
  class(t_device), allocatable :: fig
  type(t_rgb) :: rgb_black = t_rgb(0, 0, 0)
  
  allocate(fig, source = t_win32('test', 640, 480, 1, rgb_black ))
  call fig%on()
  call fig%moveTo(0, 0)
  call fig%lineTo(500, 200)
  call fig%pen(1, t_rgb(0, 0, 255))
  call fig%moveTo(500, 200)
  call fig%lineTo(100, 200)
  call fig%pen(2, t_rgb(0, 255, 255))
  call fig%moveTo(100, 200)
  call fig%lineTo(100, 480)
  call fig%off()
  deallocate(fig)

  allocate(fig, source = t_html('test', 640, 480, 1, rgb_black ))
  call fig%on()
  call fig%moveTo(0, 0)
  call fig%lineTo(500, 200)
  call fig%pen(1, t_rgb(0, 0, 255))
  call fig%moveTo(500, 200)
  call fig%lineTo(100, 200)
  call fig%pen(2, t_rgb(0, 255, 255))
  call fig%moveTo(100, 200)
  call fig%lineTo(100, 480)
  call fig%off()
  deallocate(fig)
  
  allocate(fig, source = t_ps('test', 640, 480, 1, rgb_black ))
  call fig%on()
  call fig%moveTo(0, 0)
  call fig%lineTo(500, 200)
  call fig%pen(1, t_rgb(0, 0, 255))
  call fig%moveTo(500, 200)
  call fig%lineTo(100, 200)
  call fig%pen(2, t_rgb(0, 255, 255))
  call fig%moveTo(100, 200)
  call fig%lineTo(100, 480)
  call fig%off()
  deallocate(fig)
  
  stop  
end program oop