Skip to content

Commit

Permalink
GIF encoder: switch static (non-animated) GIF encoder to homebrew sol…
Browse files Browse the repository at this point in the history
…ution

With this commit, PhotoDemon no longer leans on the 3rd-party FreeImage library for any GIF encoding tasks (static or animated).  This is a meaningful change not just because PD now produces much smaller GIF files while using less memory, but because I can now switch FreeImage to a load-on-demand model for esoteric image types.  This will meaningfully improve program startup time (FreeImage is a large library, and AV software tends to target it aggressively).

This new static GIF encoder is much more streamlined, and smarter about tasks like how it palettizes true-color images.  (Large, full-color images will use a faster palettizer, but if the user specifically requests color counts below 256, PD switches to its neural-network palette generator which produces much better small-size palettes.)  I've also tweaked PD's LZW encoder for further improved performance, so GIFs should save a little faster than before too.

The Export GIF dialog has also been switched to a pure in-house solution, and GIF encoding now always uses a "safe" approach (where the image is saved to a temporary file, then verified for correctness, and if it passes only *then* overwriting the original file if any).

Thank you also to @wqweto for finding me a proper credit link for the LZW encoder.  His expertise is always a welcome treat!
  • Loading branch information
tannerhelland committed Oct 24, 2021
1 parent de026cc commit cfee72e
Show file tree
Hide file tree
Showing 8 changed files with 521 additions and 165 deletions.
4 changes: 1 addition & 3 deletions Classes/pdColorCount.cls
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,7 @@ Private m_Colors() As PD_ColorEntry
Private m_NumOfRGBTriplets As Long, m_NumOfRGBAQuads As Long

'Used for fast lookup indices
Private m_PowersOfTwo() As Long, m_DivBy32() As Byte
Private m_PowersOfTwo(0 To 31) As Long, m_DivBy32(0 To 255) As Byte

'Used as a persistent temporary buffer when changing the lower bound of existing arrays, since VB
' doesn't allow this w/ ReDim Preserve.
Expand Down Expand Up @@ -502,14 +502,12 @@ Private Sub Class_Initialize()
m_TrackRGBA = True

'Prep some persistent luts
ReDim m_PowersOfTwo(0 To 31) As Long
Dim i As Long
For i = 0 To 30
m_PowersOfTwo(i) = 2 ^ i
Next i
m_PowersOfTwo(31) = &H80000000

ReDim m_DivBy32(0 To 255) As Byte
For i = 0 To 255
m_DivBy32(i) = i \ 32
Next i
Expand Down
354 changes: 354 additions & 0 deletions Classes/pdGIF.cls

Large diffs are not rendered by default.

103 changes: 28 additions & 75 deletions Forms/File_Save_GIF.frm
Original file line number Diff line number Diff line change
Expand Up @@ -184,8 +184,12 @@ Attribute VB_Exposed = False
'GIF export dialog
'Copyright 2012-2021 by Tanner Helland
'Created: 11/December/12
'Last updated: 11/April/16
'Last update: repurpose old color-depth dialog into a GIF-specific one
'Last updated: 20/October/21
'Last update: remove all FreeImage dependencies; everything here is 100% homebrew, baby!
'
'UI for GIF export settings. Live previews are available for all relevant features. Note that some
' ancient GIF features (like interlacing) are deliberately hidden to prevent users from producing large,
' slow GIFs for no good reason.
'
'Unless otherwise noted, all source code in this file is shared under a simplified BSD license.
' Full license details are available in the LICENSE.md file, or at https://photodemon.org/license/
Expand All @@ -194,17 +198,15 @@ Attribute VB_Exposed = False

Option Explicit

'This form can (and should!) be notified of the image being exported. The only exception to this rule is invoking
' the dialog from the batch process dialog, as no image is associated with that preview.
'This form should always be notified of the image being exported. (One exception to this rule is
' invoking the dialog from the batch process dialog, as no image is associated with that preview.
' This case is automatically covered by this dialog.)
Private m_SrcImage As pdImage

'A composite of the current image, 32-bpp, fully composited. This is only regenerated if the source image changes.
'A composite of the current image, 32-bpp, fully composited. This only needs to be regenerated
' if the source image changes.
Private m_CompositedImage As pdDIB

'FreeImage-specific copy of the preview window corresponding to m_CompositedImage, above. We cache this to save time,
' but note that it must be regenerated whenever the preview source is regenerated.
Private m_FIHandle As Long

'OK or CANCEL result
Private m_UserDialogAnswer As VbMsgBoxResult

Expand Down Expand Up @@ -267,7 +269,6 @@ Public Sub ShowDialog(Optional ByRef srcImage As pdImage = Nothing)
UpdatePanelVisibility
UpdateAllVisibility
UpdateTransparencyOptions
UpdatePreviewSource
UpdatePreview

'Apply translations and visual themes
Expand All @@ -281,7 +282,6 @@ End Sub

Private Sub btsAlpha_Click(ByVal buttonIndex As Long)
UpdateTransparencyOptions
UpdatePreviewSource
UpdatePreview
End Sub

Expand Down Expand Up @@ -330,7 +330,6 @@ End Sub

Private Sub btsColorModel_Click(ByVal buttonIndex As Long)
UpdateAllVisibility
UpdatePreviewSource
UpdatePreview
End Sub

Expand Down Expand Up @@ -361,17 +360,14 @@ Private Sub UpdateColorCountVisibility(ByVal newValue As Boolean)
End Sub

Private Sub chkColorCount_Click()
UpdatePreviewSource
UpdatePreview
End Sub

Private Sub clsAlphaColor_ColorChanged()
UpdatePreviewSource
UpdatePreview
End Sub

Private Sub clsBackground_ColorChanged()
UpdatePreviewSource
UpdatePreview
End Sub

Expand Down Expand Up @@ -407,7 +403,6 @@ End Sub

Private Sub Form_Unload(Cancel As Integer)
ReleaseFormTheming Me
Plugin_FreeImage.ReleasePreviewCache m_FIHandle
End Sub

Private Function GetExportParamString() As String
Expand Down Expand Up @@ -443,8 +438,8 @@ Private Function GetExportParamString() As String

cParams.AddParam "gif-alpha-mode", outputAlphaMode

'If "auto" mode is selected, we currently enforce a hard-coded cut-off value. There may be a better way to do this,
' but I'm not currently aware of it!
'If "auto" mode is selected, we currently enforce a hard-coded cut-off value.
' There may be a better way to do this (Otsu's, but for alpha?), but I haven't investigated in detail.
Dim outputAlphaCutoff As Long
If (btsAlpha.ListIndex = 0) Or (Not sldAlphaCutoff.IsValid) Then outputAlphaCutoff = PD_DEFAULT_ALPHA_CUTOFF Else outputAlphaCutoff = sldAlphaCutoff.Value
cParams.AddParam "gif-alpha-cutoff", outputAlphaCutoff
Expand All @@ -468,80 +463,38 @@ Private Sub pdFxPreview_ColorSelected()
End Sub

Private Sub pdFxPreview_ViewportChanged()
UpdatePreviewSource
UpdatePreview
End Sub

'When a parameter changes that requires a new source DIB for the preview (e.g. changing the background composite color),
' call this function to generate a new preview DIB. Note that you *do not* need to call this function for format-specific
' changes (like quality, subsampling, etc).
Private Sub UpdatePreviewSource()

If (Not m_CompositedImage Is Nothing) Then

'Because the user can change the preview viewport, we can't guarantee that the preview region hasn't changed
' since the last preview. Prep a new preview now.
Dim tmpSafeArray As SafeArray2D
EffectPrep.PreviewNonStandardImage tmpSafeArray, m_CompositedImage, pdFxPreview, True

'Convert the DIB to a FreeImage-compatible handle, at a color-depth that matches the current settings.
' (Note that one way or another, we'll always be converting the image to an 8-bpp mode.)
Dim forceGrayscale As Boolean
forceGrayscale = (btsColorModel.ListIndex = 2)

Dim paletteCount As Long
If (btsColorModel.ListIndex = 0) Then
paletteCount = 256
Else
If chkColorCount.Value And sldColorCount.IsValid Then paletteCount = sldColorCount.Value Else paletteCount = 256
End If

Dim desiredAlphaMode As PD_ALPHA_STATUS, desiredAlphaCutoff As Long
If btsAlpha.ListIndex = 0 Then
desiredAlphaMode = PDAS_BinaryAlpha 'Auto
desiredAlphaCutoff = PD_DEFAULT_ALPHA_CUTOFF
ElseIf btsAlpha.ListIndex = 1 Then
desiredAlphaMode = PDAS_NoAlpha 'None
desiredAlphaCutoff = 0
ElseIf btsAlpha.ListIndex = 2 Then
desiredAlphaMode = PDAS_BinaryAlpha 'By cut-off
If sldAlphaCutoff.IsValid Then desiredAlphaCutoff = sldAlphaCutoff.Value Else desiredAlphaCutoff = 96
Else
desiredAlphaMode = PDAS_NewAlphaFromColor 'By color
desiredAlphaCutoff = clsAlphaColor.Color
End If

If (m_FIHandle <> 0) Then Plugin_FreeImage.ReleaseFreeImageObject m_FIHandle
m_FIHandle = Plugin_FreeImage.GetFIDib_SpecificColorMode(workingDIB, 8, desiredAlphaMode, PDAS_ComplicatedAlpha, desiredAlphaCutoff, clsBackground.Color, forceGrayscale, paletteCount)

End If

End Sub

Private Sub UpdatePreview()

If (cmdBar.PreviewsAllowed And ImageFormats.IsFreeImageEnabled() And sldColorCount.IsValid And (Not m_SrcImage Is Nothing)) Then
If (cmdBar.PreviewsAllowed And sldColorCount.IsValid And (Not m_CompositedImage Is Nothing)) Then

'Make sure the preview source is up-to-date
If (m_FIHandle = 0) Then UpdatePreviewSource
'Because the user can change the preview viewport, we can't guarantee that the preview region
' hasn't changed since the last preview. Prep a new preview now.
Dim tmpSafeArray As SafeArray2D
EffectPrep.PreviewNonStandardImage tmpSafeArray, m_CompositedImage, pdFxPreview

'Retrieve a BMP-saved version of the current preview image
workingDIB.ResetDIB
If Plugin_FreeImage.GetExportPreview(m_FIHandle, workingDIB, PDIF_GIF) Then
FinalizeNonstandardPreview pdFxPreview, True
End If
'This export dialog is a little weird because we need to preview a lot of possible settings,
' but none of them require the GIF encoder. Instead, they are just convenience options
' for converting a 32-bpp image to an 8-bpp GIF with (or without) transparency.
'
'As such, we won't actually involve the GIF encoder at all here. Just create a pdGIF class
' and request the pre-processing step by itself.
Dim cGIF As pdGIF
Set cGIF = New pdGIF
cGIF.GetGifReadyImage workingDIB, GetExportParamString(), True
FinalizeNonstandardPreview pdFxPreview, False

End If

End Sub

Private Sub sldAlphaCutoff_Change()
UpdatePreviewSource
UpdatePreview
End Sub

Private Sub sldColorCount_Change()
If (Not chkColorCount.Value) Then chkColorCount.Value = True
UpdatePreviewSource
UpdatePreview
End Sub
2 changes: 1 addition & 1 deletion Modules/DibSupport.bas
Original file line number Diff line number Diff line change
Expand Up @@ -727,7 +727,7 @@ End Function
Public Function MakeDIBGrayscale(ByRef srcDIB As pdDIB, Optional ByVal numOfShades As Long = 256, Optional ByVal ignoreMagicMagenta As Boolean = True) As Boolean

'Make sure the DIB exists
If srcDIB Is Nothing Then Exit Function
If (srcDIB Is Nothing) Then Exit Function

'Make sure the source DIB isn't empty
If (srcDIB.GetDIBDC <> 0) And (srcDIB.GetDIBWidth <> 0) And (srcDIB.GetDIBHeight <> 0) Then
Expand Down
107 changes: 47 additions & 60 deletions Modules/ImageFormats_GIF.bas
Original file line number Diff line number Diff line change
Expand Up @@ -3,10 +3,8 @@ Attribute VB_Name = "ImageFormats_GIF"
'Additional support functions for GIF support
'Copyright 2001-2021 by Tanner Helland
'Created: 4/15/01
'Last updated: 16/October/21
'Last update: overhaul GIF optimizations. PhotoDemon can now produce smaller GIFs than pretty much any
' other general-purpose photo editor, and it can even beat dedicated optimizers like
' gifsicle on certain image types!
'Last updated: 24/October/21
'Last update: switch static GIF encoder to new homebrew GIF encoder; FreeImage is no longer used for any GIF features!
'
'Most image exporters exist in the ImageExporter module. GIF is a weird exception because animated GIFs
' require a ton of preprocessing (to optimize animation frames), so I've moved them to their own home.
Expand Down Expand Up @@ -77,76 +75,67 @@ Private m_allFrames() As PD_GifFrame
' (Local palettes will automatically be generated too, as necessary.)
Private m_globalPalette() As RGBQuad, m_numColorsInGP As Long, m_GlobalTrnsIndex As Long

'Low-level GIF export interface
'Low-level GIF export interface. As of 2021, image pre-processing (including palettization) and GIf encoding
' is all performed using homebrew code.
Public Function ExportGIF_LL(ByRef srcPDImage As pdImage, ByVal dstFile As String, Optional ByVal formatParams As String = vbNullString, Optional ByVal metadataParams As String = vbNullString) As Boolean

On Error GoTo ExportGIFError

ExportGIF_LL = False

'Parse all relevant GIF parameters. (See the GIF export dialog for details on how these are generated.)
Dim cParams As pdSerialize
Set cParams = New pdSerialize
cParams.SetParamString formatParams

'Only two parameters are mandatory; the others are used on an as-needed basis
Dim gifColorMode As String, gifAlphaMode As String
gifColorMode = cParams.GetString("gif-color-mode", "auto")
gifAlphaMode = cParams.GetString("gif-alpha-mode", "auto")

Dim gifAlphaCutoff As Long, gifColorCount As Long, gifBackgroundColor As Long, gifAlphaColor As Long
gifAlphaCutoff = cParams.GetLong("gif-alpha-cutoff", 64)
gifColorCount = cParams.GetLong("gif-color-count", 256)
gifBackgroundColor = cParams.GetLong("gif-backcolor", vbWhite)
gifAlphaColor = cParams.GetLong("gif-alpha-color", RGB(255, 0, 255))

'Some combinations of parameters invalidate other parameters. Calculate any overrides now.
Dim gifForceGrayscale As Boolean
gifForceGrayscale = Strings.StringsEqual(gifColorMode, "gray", True)
If Strings.StringsEqual(gifColorMode, "auto", True) Then gifColorCount = 256

Dim desiredAlphaStatus As PD_ALPHA_STATUS
desiredAlphaStatus = PDAS_BinaryAlpha
If Strings.StringsEqual(gifAlphaMode, "none", True) Then desiredAlphaStatus = PDAS_NoAlpha
If Strings.StringsEqual(gifAlphaMode, "by-color", True) Then
desiredAlphaStatus = PDAS_NewAlphaFromColor
gifAlphaCutoff = gifAlphaColor
'If the target file already exists, use "safe" file saving (e.g. write the save data to
' a new file, and if it's saved successfully, overwrite the original file - this way,
' if an error occurs mid-save, the original file remains untouched).
Dim tmpFilename As String
If Files.FileExists(dstFile) Then
Dim cRandom As pdRandomize
Set cRandom = New pdRandomize
cRandom.SetSeed_AutomaticAndRandom
tmpFilename = dstFile & Hex$(cRandom.GetRandomInt_WH()) & ".pdtmp"
Else
tmpFilename = dstFile
End If

'Generate a composited image copy, with alpha automatically un-premultiplied
Dim tmpImageCopy As pdDIB
Set tmpImageCopy = New pdDIB
srcPDImage.GetCompositedImage tmpImageCopy, False
'As always, pdStream handles actual writing duties. (Memory mapping is used for ideal performance.)
Dim cStream As pdStream
Set cStream = New pdStream
If cStream.StartStream(PD_SM_FileMemoryMapped, PD_SA_ReadWrite, tmpFilename, optimizeAccess:=OptimizeSequentialAccess) Then

'FreeImage provides the most comprehensive GIF encoder, so we prefer it whenever possible
If ImageFormats.IsFreeImageEnabled Then
'A pdGIF instance handles the actual encoding
Dim cGIF As pdGIF
Set cGIF = New pdGIF
If cGIF.SaveGIF_ToStream_Static(srcPDImage, cStream, formatParams, metadataParams) Then

Dim fi_DIB As Long
fi_DIB = Plugin_FreeImage.GetFIDib_SpecificColorMode(tmpImageCopy, 8, desiredAlphaStatus, PDAS_ComplicatedAlpha, gifAlphaCutoff, gifBackgroundColor, gifForceGrayscale, gifColorCount)

'Finally, prepare some GIF save flags. If the user has requested RLE encoding, and this image is <= 8bpp,
' request RLE encoding from FreeImage.
Dim GIFflags As Long: GIFflags = GIF_DEFAULT

'Use that handle to save the image to GIF format, with required color conversion based on the outgoing color depth
If (fi_DIB <> 0) Then
ExportGIF_LL = FreeImage_SaveEx(fi_DIB, dstFile, PDIF_GIF, GIFflags, FICD_8BPP, , , , , True)
If ExportGIF_LL Then
ExportDebugMsg "Export to " & GIF_FILE_EXTENSION & " appears successful."
'Close the stream, then release the pdGIF instance
cStream.StopStream
Set cGIF = Nothing

'If we wrote our data to a temp file, attempt to replace the original file
If Strings.StringsNotEqual(dstFile, tmpFilename) Then

ExportGIF_LL = (Files.FileReplace(dstFile, tmpFilename) = FPR_SUCCESS)

If (Not ExportGIF_LL) Then
Files.FileDelete tmpFilename
PDDebug.LogAction "WARNING! ImageExporter could not overwrite GIF file; original file is likely open elsewhere."
End If

'Encode is already done!
Else
Message "%1 save failed (FreeImage_SaveEx silent fail). Please report this error using Help -> Submit Bug Report.", GIF_FILE_EXTENSION
ExportGIF_LL = True
End If

Else
Message "%1 save failed (FreeImage returned blank handle). Please report this error using Help -> Submit Bug Report.", GIF_FILE_EXTENSION
ExportGIF_LL = False
PDDebug.LogAction "WARNING! pdGIF failed to save GIF"
End If

'If FreeImage is unavailable, fall back to GDI+

ProgressBars.SetProgBarVal 0
ProgressBars.ReleaseProgressBar

Else
ExportGIF_LL = GDIPlusSavePicture(srcPDImage, dstFile, P2_FFE_GIF, 8)
PDDebug.LogAction "WARNING! Couldn't initialize stream against " & dstFile
End If


Exit Function

ExportGIFError:
Expand All @@ -155,9 +144,7 @@ ExportGIFError:

End Function

'Low-level animated GIF export. Currently relies on FreeImage for export, but it's designed so that any
' capable encoder can be easily dropped-in. (Frame optimization happens locally, using PD data structures,
' so the encoder doesn't need to support it at all.)
'Low-level animated GIF export. As of 2021, frame optimization and GIF encoding is all done with homebrew code.
Public Function ExportGIF_Animated_LL(ByRef srcPDImage As pdImage, ByVal dstFile As String, Optional ByVal formatParams As String = vbNullString, Optional ByVal metadataParams As String = vbNullString) As Boolean

On Error GoTo ExportGIFError
Expand Down
Loading

0 comments on commit cfee72e

Please sign in to comment.