products/sources/formale Sprachen/Fortran/f90gl-1.2.15/examples image not shown  

Quellcode-Bibliothek

© Kompilation durch diese Firma

[Weder Korrektheit noch Funktionsfähigkeit der Software werden zugesichert.]

Datei: Feedback.dfm   Sprache: Fortran

Untersuchung f90gl©

!  blender renders two spinning icosahedrons (red and green).
!  The blending factors for the two icosahedrons vary sinusoidally
!  and slightly out of phase.  blender also renders two lines of
!  text in a stroke font: one line antialiased, the other not.

module blender_data

! with use here, we don't need them in each routine
use opengl_gl
use opengl_glu
use opengl_glut

real(glfloat) :: light0_ambient(4) = (/0.2, 0.2, 0.2, 1.0/)
real(glfloat) :: light0_diffuse(4) = (/0.0, 0.0, 0.0, 1.0/)
real(glfloat) :: light1_diffuse(4) = (/1.0, 0.0, 0.0, 1.0/)
real(glfloat) :: light1_position(4) = (/1.0, 1.0, 1.0, 0.0/)
real(glfloat) :: light2_diffuse(4) = (/0.0, 1.0, 0.0, 1.0/)
real(glfloat) :: light2_position(4) = (/-1.0, -1.0, 1.0, 0.0/)
real :: s = 0.0
real(glfloat) :: angle1 = 0.0, angle2 = 0.0

end module blender_data

subroutine output(x, y, text)
use blender_data
real(glfloat) x,y
character(len=*) text
integer(glcint) p

  call glPushMatrix()
  call glTranslatef(x, y, 0.0_glfloat)
  do i=1,len(text)
    p = ichar(text(i:i))
    call glutStrokeCharacter(GLUT_STROKE_ROMAN, p)
  end do
  call glPopMatrix()
end subroutine output

subroutine display()
use blender_data

  real(glfloat), save :: amb(4) = (/0.4, 0.4, 0.4, 0.0/)
  real(glfloat), save :: dif(4) = (/1.0, 1.0, 1.0, 0.0/)

  call glClear(ior(GL_COLOR_BUFFER_BIT,GL_DEPTH_BUFFER_BIT))
  call glEnable(GL_LIGHT1)
  call glDisable(GL_LIGHT2)
  dif(4) = cos(s) / 2.0 + 0.5
  amb(4) = dif(4)
  call glMaterialfv(GL_FRONT, GL_AMBIENT, amb)
  call glMaterialfv(GL_FRONT, GL_DIFFUSE, dif)

  call glPushMatrix()
! let's take a chance that the default integer is the same kind as
! glint, and not bother with the _glint on constants
  call glTranslatef(-0.3, -0.3, 0.0)
  call glRotatef(angle1, 1.0, 5.0, 0.0)
  call glCallList(1)        ! render ico display list
  call glPopMatrix()

  call glClear(GL_DEPTH_BUFFER_BIT)
  call glEnable(GL_LIGHT2)
  call glDisable(GL_LIGHT1)
  dif(4) = 0.5 - cos(s * .95) / 2.0
  amb(4) = dif(4)
  call glMaterialfv(GL_FRONT, GL_AMBIENT, amb)
  call glMaterialfv(GL_FRONT, GL_DIFFUSE, dif)

  call glPushMatrix()
  call glTranslatef(0.3, 0.3, 0.0)
  call glRotatef(angle2, 1.0, 0.0, 5.0)
  call glCallList(1)        ! render ico display list
  call glPopMatrix()

  call glPushAttrib(GL_ENABLE_BIT)
  call glDisable(GL_DEPTH_TEST)
  call glDisable(GL_LIGHTING)
  call glMatrixMode(GL_PROJECTION)
  call glPushMatrix()
  call glLoadIdentity()
  call gluOrtho2D(0.0_gldouble, 1500.0_gldouble, 0.0_gldouble, 1500.0_gldouble)
  call glMatrixMode(GL_MODELVIEW)
  call glPushMatrix()
  call glLoadIdentity()
!  Rotate text slightly to help show jaggies.
  call glRotatef(4.0, 0.0, 0.0, 1.0)
  call output(200., 225., "This is antialiased.")
  call glscalef(.5,.5,.5)
  call glDisable(GL_LINE_SMOOTH)
  call glDisable(GL_BLEND)
  call output(160., 100., "This text is not.")
  call glPopMatrix()
  call glMatrixMode(GL_PROJECTION)
  call glPopMatrix()
  call glPopAttrib()
  call glMatrixMode(GL_MODELVIEW)

  call glutSwapBuffers()
end subroutine display

subroutine idle()
use blender_data

  angle1 = mod(angle1 + 0.8, 360.0)
  angle2 = mod(angle2 + 1.1, 360.0)
  s = s + 0.05
  call glutPostRedisplay()
end subroutine idle

subroutine visible(vis)
use blender_data
integerintent(inout) :: vis
interface
  subroutine idle()
  end subroutine idle
end interface

  if (vis == GLUT_VISIBLE) then
    call glutIdleFunc(idle)
  else
    call glutIdleFunc(glutnullfunc)
  endif
end subroutine visible

program main
use blender_data
use opengl_glut
integer(glcint) i
interface
  subroutine display()
  end subroutine display

  subroutine visible(vis)
  integerintent(inout) :: vis
  end subroutine visible
end interface

  call glutInit()
  call glutInitDisplayMode(ior(ior(GLUT_DOUBLE,GLUT_RGB),GLUT_DEPTH))
  i = glutCreateWindow("blender")
  call glutDisplayFunc(display)
  call glutVisibilityFunc(visible)

  call glNewList(1, GL_COMPILE)  ! create ico display list
  call glutSolidIcosahedron()
  call glEndList()

  call glEnable(GL_LIGHTING)
  call glEnable(GL_LIGHT0)
  call glLightfv(GL_LIGHT0, GL_AMBIENT, light0_ambient)
  call glLightfv(GL_LIGHT0, GL_DIFFUSE, light0_diffuse)
  call glLightfv(GL_LIGHT1, GL_DIFFUSE, light1_diffuse)
  call glLightfv(GL_LIGHT1, GL_POSITION, light1_position)
  call glLightfv(GL_LIGHT2, GL_DIFFUSE, light2_diffuse)
  call glLightfv(GL_LIGHT2, GL_POSITION, light2_position)
  call glEnable(GL_DEPTH_TEST)
  call glEnable(GL_CULL_FACE)
  call glEnable(GL_BLEND)
  call glBlendFunc(GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA)
  call glEnable(GL_LINE_SMOOTH)
  call glLineWidth(2.0)

  call glMatrixMode(GL_PROJECTION)
  call gluPerspective( 40.0_gldouble, & ! field of view in degree
                           1.0_gldouble, & ! aspect ratio
                           1.0_gldouble, & ! Z near
                          10.0_gldouble)   ! Z far
  call glMatrixMode(GL_MODELVIEW)
  call gluLookAt( &
     0.0_gldouble, 0.0_gldouble, 5.0_gldouble, & ! eye is at (0,0,5)
     0.0_gldouble, 0.0_gldouble, 0.0_gldouble, & ! center is at (0,0,0)
     0.0_gldouble, 1.0_gldouble, 0.0_gldouble)    ! up is in positive Y direction
  call glTranslatef(0.0, 0.6, -1.0)

  call glutMainLoop()
end program main

¤ Diese beiden folgenden Angebotsgruppen bietet das Unternehmen0.21Angebot  Wie Sie bei der Firma Beratungs- und Dienstleistungen beauftragen können  ¤





Begriffe der Konzeptbildung
Was zu einem Entwurf gehört
Druckansicht
Hier finden Sie eine Liste der Produkte des Unternehmens

Mittel




Lebenszyklus

Die hierunter aufgelisteten Ziele sind für diese Firma wichtig


Ziele

Entwicklung einer Software für die statische Quellcodeanalyse


Bot Zugriff