- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hello!
I put together thecode quoted below(to save my OpenGL graphics to a BMP) after reading several messages on this forum.I can now set the resolution of the BMP higher then the resolution of the screen but the smoothness of the saved image is still delimited by the screen resolutionfor StrechBlt only increases and copyes the screen pixels. Does anyone have any idea how to save an OpenGL graphics with a resolution higher than that of the screen so as to the lines would look like lines even encreasing the saved picture. I'm not very experienced in this field so if anyone has a subroutine plese send me...
Integer*4 Function Save_Bmp(hdc, hwnd)
INTEGER*4 hdc, hBitmap, hmemDC, holdBitmap, cClrBits, nColorTable
INTEGER*4hwnd, rval, iSt, BMPhight, BMPwidth
INTEGER, PARAMETER :: RGBQUAD_SIZE = 4
INTEGER(1), ALLOCATABLE:: bmBits(:), bmInfo(:)
INTEGER*4 hdc, hBitmap, hmemDC, holdBitmap, cClrBits, nColorTable
INTEGER*4hwnd, rval, iSt, BMPhight, BMPwidth
INTEGER, PARAMETER :: RGBQUAD_SIZE = 4
INTEGER(1), ALLOCATABLE:: bmBits(:), bmInfo(:)
TYPE(T_BITMAP) BMP
TYPE(T_BITMAPINFO) BI; POINTER(pBI, BI)
TYPE(T_BITMAPFILEHEADER) bfh
TYPE(T_BITMAPINFO) BI; POINTER(pBI, BI)
TYPE(T_BITMAPFILEHEADER) bfh
BMPwidth = 2*glnWidth
BMPhight = 2*glnHeight
hBitmap = CreateCompatibleBitmap (hDC, BMPwidth, BMPhight)
hmemDC = CreateCompatibleDC (hDC)
hOldBitmap = SelectObject (hmemDC, hBitmap)
BMPhight = 2*glnHeight
hBitmap = CreateCompatibleBitmap (hDC, BMPwidth, BMPhight)
hmemDC = CreateCompatibleDC (hDC)
hOldBitmap = SelectObject (hmemDC, hBitmap)
rval = SetStretchBltMode(hmemDC, HALFTONE)
rval = StretchBlt(hmemDC, 0, 0, BMPwidth, BMPhight, hdc, 0, 0, GlnWidth, GlnHeight, SRCCOPY)
rval = GetObject (hBitmap, SIZEOF(BMP), LOC(BMP))
cClrBits = 24
ALLOCATE(bmInfo(SIZEOF(BI%bmiHeader))); bmInfo = 0_1 !Allocate memory for the BITMAPINFO structure
pBI = LOC(bmInfo)
nColorTable = 0
ALLOCATE(bmInfo(SIZEOF(BI%bmiHeader))); bmInfo = 0_1 !Allocate memory for the BITMAPINFO structure
pBI = LOC(bmInfo)
nColorTable = 0
BI%bmiHeader%biSize = SIZEOF(BI%bmiHeader)
BI%bmiHeader%biWidth = BMP%bmWidth
BI%bmiHeader%biHeight = BMP%bmHeight
BI%bmiHeader%biPlanes = 1
BI%bmiHeader%biBitCount = cClrBits
BI%bmiHeader%biCompression = BI_RGB
BI%bmiHeader%biSizeImage = ((BI%bmiHeader%biWidth * cClrBits + 31) /8) * BI%bmiHeader%biHeight
BI%bmiHeader%biXPelsPerMeter = 0! 96*100/2.54+1
BI%bmiHeader%biYPelsPerMeter = 0! 96*100/2.54+1
BI%bmiHeader%biClrUsed = nColorTable
BI%bmiHeader%biClrImportant = 0
BI%bmiHeader%biWidth = BMP%bmWidth
BI%bmiHeader%biHeight = BMP%bmHeight
BI%bmiHeader%biPlanes = 1
BI%bmiHeader%biBitCount = cClrBits
BI%bmiHeader%biCompression = BI_RGB
BI%bmiHeader%biSizeImage = ((BI%bmiHeader%biWidth * cClrBits + 31) /8) * BI%bmiHeader%biHeight
BI%bmiHeader%biXPelsPerMeter = 0! 96*100/2.54+1
BI%bmiHeader%biYPelsPerMeter = 0! 96*100/2.54+1
BI%bmiHeader%biClrUsed = nColorTable
BI%bmiHeader%biClrImportant = 0
hOldBmp = SelectObject(hmemDC, hBitmap)
ALLOCATE(bmBits(BI%bmiHeader%biSizeImage))
!DEC$IF (_DF_VERSION_.LT.650 .OR. .NOT.DEFINED(XLITE))
iSt = GetDIBits(hmemDC, hBitmap, 0, BI%bmiHeader%biHeight, LOC(bmBits), BI, DIB_RGB_COLORS)
!DEC$ELSE
iSt = GetDIBits(hmemDC, hBitmap, 0, BI%bmiHeader%biHeight, LOC(bmBits), LOC(BI), DIB_RGB_COLORS)
!DEC$ENDIF
iSt = GetDIBits(hmemDC, hBitmap, 0, BI%bmiHeader%biHeight, LOC(bmBits), BI, DIB_RGB_COLORS)
!DEC$ELSE
iSt = GetDIBits(hmemDC, hBitmap, 0, BI%bmiHeader%biHeight, LOC(bmBits), LOC(BI), DIB_RGB_COLORS)
!DEC$ENDIF
iSt = DeleteDC(hmemDC)
iSt = SelectObject(hmemDC, hOldBmp)
iSt = SelectObject(hmemDC, hOldBmp)
bfh%bfType = 'BM' !'BM' = Z'4d42'
bfh%bfSize = SIZEOF(bfh) + BI%bmiHeader%biSize + nColorTable * RGBQUAD_SIZE + BI%bmiHeader%biSizeImage
bfh%bfReserved1 = 0
bfh%bfReserved2 = 0
bfh%bfOffBits = SIZEOF(hdr) + BI%bmiHeader%biSize + nColorTable * RGBQUAD_SIZE
bfh%bfSize = SIZEOF(bfh) + BI%bmiHeader%biSize + nColorTable * RGBQUAD_SIZE + BI%bmiHeader%biSizeImage
bfh%bfReserved1 = 0
bfh%bfReserved2 = 0
bfh%bfOffBits = SIZEOF(hdr) + BI%bmiHeader%biSize + nColorTable * RGBQUAD_SIZE
bmpfile = bmpfile(1:lt(bmpfile))//'.bmp'
OPEN(bmpfunit, file = bmpfile, ACTION = 'WRITE', ACCESS = 'SEQUENTIAL', STATUS = 'UNKNOWN', FORM = 'BINARY', IOSTAT = iErr)
IF (iErr.NE.0) RETURN
WRITE(bmpfunit, IOSTAT = iErr) bfh, bmInfo(1: SIZEOF(BI%bmiHeader)+ nColorTable*RGBQUAD_SIZE), bmBits
CLOSE(bmpfunit)
OPEN(bmpfunit, file = bmpfile, ACTION = 'WRITE', ACCESS = 'SEQUENTIAL', STATUS = 'UNKNOWN', FORM = 'BINARY', IOSTAT = iErr)
IF (iErr.NE.0) RETURN
WRITE(bmpfunit, IOSTAT = iErr) bfh, bmInfo(1: SIZEOF(BI%bmiHeader)+ nColorTable*RGBQUAD_SIZE), bmBits
CLOSE(bmpfunit)
Save_Bmp = 1
End Function Save_Bmp
End Function Save_Bmp
Link Copied
8 Replies
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I imagine what you are doing is creating a scene bydrawing lines of a given minimumthickness (say 1 pixel wide) on a 100 by 100 (say) background grid of pixels and then doubling the pixels to 200 by 200 say (by dividing each row and column into two). Well, your scene remains the same size and your lines will be the same width as before but now they will be twice the width of the 'new' pixel size, so you cannot expect increased resolution, This will only come when you rescale your scene to cover 200 by 200 pixels and redraw the whole scene with your 1-pixel wide pen (effectively using a 1/2/ pixel wide pen on your original 100X100 background. So having obtained the handle to the new device context, hMemDC, you should send it to your drawing routine to have the scene redrawn onto it.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thank's for your answere. Theoretically I know that this is what a would have to do but I don't know how to. Unfortunatelly I have no much experience in this field. I've tried replacing
rval = SetStretchBltMode(hmemDC, HALFTONE)
rval = StretchBlt(hmemDC, 0, 0, BMPwidth, BMPhight, hdc, 0, 0, GlnWidth, GlnHeight, SRCCOPY)
rval = StretchBlt(hmemDC, 0, 0, BMPwidth, BMPhight, hdc, 0, 0, GlnWidth, GlnHeight, SRCCOPY)
with
! call SetGLPixelFormat(hmemDC)
hrc = fwglCreateContext(hmemDC)
bret = fwglMakeCurrent(hmemDC, hrc)
bret = InvalidateRect (hwnd, NULL_RECT, .FALSE.)
Call DrawScene (hmemDC, angleX,angleY,angleZ,transX,transY,transZ)
hrc = fwglCreateContext(hmemDC)
bret = fwglMakeCurrent(hmemDC, hrc)
bret = InvalidateRect (hwnd, NULL_RECT, .FALSE.)
Call DrawScene (hmemDC, angleX,angleY,angleZ,transX,transY,transZ)
but then the saved BMP is an empty BMP.
Coud you by any chance give me some mor details.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Why not try what you had but add the 'draw scene' command...
Code:
BMPwidth = 2*glnWidth BMPhight = 2*glnHeight hBitmap = CreateCompatibleBitmap (hDC, BMPwidth, BMPhight) ! create a memory device context compatible with the display device context hDC ! It will contain only a 1X1 place-holding bitmap... hmemDC = CreateCompatibleDC (hDC) ! select the desired size bitmap, handle hBitmap, into the compatible device context... ! taking the place of the 1X1 bitmap
hOldBitmap = SelectObject (hmemDC, hBitmap) ! Draw on the bitmap by sending the device context handle to the scene drawing routine.. Call DrawScene (hmemDC, angleX,angleY,angleZ,transX,transY,transZ)
then follow it with your code for saving the bitmap.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
This is the first thing I had tried beforepostingmy letter to the forum. There may be a problem with my DrawScene routine!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I see you are using OpenGL, with which I am not familiar. What I suggested will work with GDI calls. A litle reading of the OpenGL help shows that your code creating a renderingcontext and creating the correct bitmap format having front and back buffers is the way to go.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I have solved the problem now. It may be useful for others. Here's the code:
Integer*4 Function Save_Bmp(hdc, hwnd, hrc)
INTEGER*4 hdc, hBitmap, hmemDC, holdBitmap, cClrBits, nColorTable, hrc, hrc1
INTEGER*4hwnd, rval, iSt, BMPhight, BMPwidth
INTEGER, PARAMETER :: RGBQUAD_SIZE = 4
INTEGER(1), ALLOCATABLE:: bmBits(:), bmInfo(:)
INTEGER*4 hdc, hBitmap, hmemDC, holdBitmap, cClrBits, nColorTable, hrc, hrc1
INTEGER*4hwnd, rval, iSt, BMPhight, BMPwidth
INTEGER, PARAMETER :: RGBQUAD_SIZE = 4
INTEGER(1), ALLOCATABLE:: bmBits(:), bmInfo(:)
TYPE(T_BITMAP) BMP
TYPE(T_BITMAPINFO) BI
TYPE(T_BITMAPFILEHEADER) bfh
TYPE(T_BITMAPINFO) BI
TYPE(T_BITMAPFILEHEADER) bfh
BMPwidth = 4*glnWidth
BMPhight = 4*glnHeight
cClrBits = 24
nColorTable = 0
BMPhight = 4*glnHeight
cClrBits = 24
nColorTable = 0
BI%bmiHeader%biSize = SIZEOF(BI%bmiHeader)
BI%bmiHeader%biWidth = BMPwidth
BI%bmiHeader%biHeight = BMPhight
BI%bmiHeader%biPlanes = 1
BI%bmiHeader%biBitCount = cClrBits
BI%bmiHeader%biCompression = BI_RGB
BI%bmiHeader%biSizeImage = ((BI%bmiHeader%biWidth * cClrBits + 31) /8) * BI%bmiHeader%biHeight
BI%bmiHeader%biXPelsPerMeter = 0! 96*100/2.54+1
BI%bmiHeader%biYPelsPerMeter = 0! 96*100/2.54+1
BI%bmiHeader%biClrUsed = nColorTable
BI%bmiHeader%biClrImportant = 0
BI%bmiHeader%biWidth = BMPwidth
BI%bmiHeader%biHeight = BMPhight
BI%bmiHeader%biPlanes = 1
BI%bmiHeader%biBitCount = cClrBits
BI%bmiHeader%biCompression = BI_RGB
BI%bmiHeader%biSizeImage = ((BI%bmiHeader%biWidth * cClrBits + 31) /8) * BI%bmiHeader%biHeight
BI%bmiHeader%biXPelsPerMeter = 0! 96*100/2.54+1
BI%bmiHeader%biYPelsPerMeter = 0! 96*100/2.54+1
BI%bmiHeader%biClrUsed = nColorTable
BI%bmiHeader%biClrImportant = 0
bfh%bfType = 'BM'
bfh%bfSize = SIZEOF(bfh) + BI%bmiHeader%biSize + nColorTable * RGBQUAD_SIZE + BI%bmiHeader%biSizeImage
bfh%bfReserved1 = 0
bfh%bfReserved2 = 0
bfh%bfOffBits = SIZEOF(hdr) + BI%bmiHeader%biSize + nColorTable * RGBQUAD_SIZE
bfh%bfSize = SIZEOF(bfh) + BI%bmiHeader%biSize + nColorTable * RGBQUAD_SIZE + BI%bmiHeader%biSizeImage
bfh%bfReserved1 = 0
bfh%bfReserved2 = 0
bfh%bfOffBits = SIZEOF(hdr) + BI%bmiHeader%biSize + nColorTable * RGBQUAD_SIZE
ALLOCATE(bmBits(BI%bmiHeader%biSizeImage))
hBitmap = CreateDIBSection (hDC, BI, DIB_RGB_COLORS, LOC(bmBits), 0, 0)
hmemDC = CreateCompatibleDC (hDC)
hOldBitmap = SelectObject (hmemDC, hBitmap)
call SetGLPixelFormat(hmemDC, "bmp")
hmemDC = CreateCompatibleDC (hDC)
hOldBitmap = SelectObject (hmemDC, hBitmap)
call SetGLPixelFormat(hmemDC, "bmp")
hrc1 = fwglCreateContext(hmemDC)
bret = fwglMakeCurrent(hmemDC, hrc1)
call CreateDisplayList()
call InitLights(shadeon)
bret = fwglMakeCurrent(hmemDC, hrc1)
call CreateDisplayList()
call InitLights(shadeon)
transXo = 0.0; transYo = 0.0; transZo = 0.0
angleXo = 0.0; angleYo = 0.0; angleZo = 0.0
angleXo = 0.0; angleYo = 0.0; angleZo = 0.0
call fglMatrixMode(GL_PROJECTION)
call fglLoadIdentity()
call fgluPerspective(DBLE(ViewAngle), gldAspect, DBLE(NearPlane), DBLE(FarPlane) )
call fglLoadIdentity()
call fgluPerspective(DBLE(ViewAngle), gldAspect, DBLE(NearPlane), DBLE(FarPlane) )
call fglMatrixMode(GL_MODELVIEW)
call fglLoadIdentity()
call DrawScene (hmemDC, angleX,angleY,angleZ,transX,transY,transZ)
call fglLoadIdentity()
call DrawScene (hmemDC, angleX,angleY,angleZ,transX,transY,transZ)
bret = fwglMakeCurrent(hDC, hrc)
!DEC$IF (_DF_VERSION_.LT.650 .OR. .NOT.DEFINED(XLITE))
bret = GetDIBits(hmemDC, hBitmap, 0, BI%bmiHeader%biHeight, LOC(bmBits), BI, DIB_RGB_COLORS)
!DEC$ELSE
bret = GetDIBits(hmemDC, hBitmap, 0, BI%bmiHeader%biHeight, LOC(bmBits), LOC(BI), DIB_RGB_COLORS)
!DEC$ENDIF
bret = GetDIBits(hmemDC, hBitmap, 0, BI%bmiHeader%biHeight, LOC(bmBits), BI, DIB_RGB_COLORS)
!DEC$ELSE
bret = GetDIBits(hmemDC, hBitmap, 0, BI%bmiHeader%biHeight, LOC(bmBits), LOC(BI), DIB_RGB_COLORS)
!DEC$ENDIF
bret = fwglDeleteContext(hrc1)
bret = DeleteDC(hmemDC)
bret = DeleteDC(hmemDC)
bmpfile = bmpfile(1:lt(bmpfile))//'.bmp'
OPEN(bmpfunit, file = bmpfile, ACTION = 'WRITE', ACCESS = 'SEQUENTIAL', STATUS = 'UNKNOWN', FORM = 'BINARY', IOSTAT = iErr)
IF (iErr.NE.0) RETURN
WRITE(bmpfunit, IOSTAT = iErr) bfh, BI, bmBits
CLOSE(bmpfunit)
OPEN(bmpfunit, file = bmpfile, ACTION = 'WRITE', ACCESS = 'SEQUENTIAL', STATUS = 'UNKNOWN', FORM = 'BINARY', IOSTAT = iErr)
IF (iErr.NE.0) RETURN
WRITE(bmpfunit, IOSTAT = iErr) bfh, BI, bmBits
CLOSE(bmpfunit)
Save_Bmp = 1
End Function Save_Bmp
End Function Save_Bmp
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
What did you have to change to get it to 'work'?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content

Reply
Topic Options
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page