Skip to content

Commit

Permalink
Fix WebView2 instances not recreating when environment options changed
Browse files Browse the repository at this point in the history
WebView2 environment options are global to all instances in an environment,
and an environment is associated with a disk folder where temporary data
and user profile data is stored. Each environment also has a root browser
process associated with it. If one attempts to alter an environment option
and then create a new webview2 instance in an environment when there are
existing instances, or the browser process is still running, then the
creation will fail. Although most of the environment options are probably
not things one might alter very often, they do include some weirdly
misplaced properties like the scrollbar style, which seems like it ought
to be per view. If this is changed in the Web Browser sample, the
WebView2View attemps to recreate itself, but doesn't get very far. The
reason is a race condition in the recreation process that the browser
process doesn't shut down quickly enough, and as it is still running the
attempt to create a new view with different options fails (silently).
As the process shutdown is asynchronous, and there is an event fired, it
seems like it might be feasible to wait for the event after destroying the
existing view, and then create the new view on being notified. There are
two problems with this: 1) the environment events were being torn down
when the view was destroyed, so the event would never be received anyway,
and 2) it is difficult to split the recreation logic so that the recreation
can happen asynchronously on an event. A much more reliable approach that
also allows views with different environment options to be open
simultaneously, is to just ensure that the data folder paths are unique
for a particular combination of options. If this is the case, then a new
browser process is started when recreating with new environment options,
and we don't need to wait for the old process to exit.
The data folders names are made unique by appending a thumbprint generated
from the environment settings. This is then hashed with MD5 to keep it
reasonably short, and appended to the existing local app data path
based on the application name.
  • Loading branch information
blairmcg committed Dec 14, 2024
1 parent b2462c0 commit c366a38
Show file tree
Hide file tree
Showing 14 changed files with 246 additions and 127 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -149,8 +149,6 @@ createUnavailableLink
to: self!

createWebView
"Currently we don't attempt to set any controller options - see ICoreWebView2ControllerOptions[2]"

| controllerOptions |
controllerOptions := webviewEnvironment createCoreWebView2ControllerOptions.
self isInPrivateModeEnabled ifTrue: [controllerOptions isInPrivateModeEnabled: true].
Expand All @@ -165,7 +163,9 @@ createWebView
createWebViewEnvironment
| completed userDataFolder |
completed := (WebView2CompletionHandler
completionBlock: [:hr :env | hr < 0 ifFalse: [self onEnvironmentCreated: env]])
completionBlock: [:hr :env | hr < 0
ifTrue: [HRESULTError signal: 'Failed to create WebView2 environment' with: hr]
ifFalse: [self onEnvironmentCreated: env]])
queryInterface: ICoreWebView2CreateCoreWebView2EnvironmentCompletedHandler.
userDataFolder := self defaultUserDataFolder.

Expand All @@ -183,8 +183,13 @@ createWebViewEnvironment
to: self!

defaultUserDataFolder
"Answer a path for the browser data folder that is writable with user privileges. We make this unique for a particular configuration of environment options, because it isn't possible to start webview2 instances with the same data folder that have mismatched environment options."

^File composePath: (SessionManager current getenv: 'LocalAppData')
subPath: (File splitFilenameFrom: (DynamicLinkLibrary moduleFileName: nil)) , '.WebView2'!
subPath: '<1s>-<2s>.WebView2' << {
File splitStemFrom: (DynamicLinkLibrary moduleFileName: nil).
self environmentOptions thumbprint
}!

defaultWindowProcessing: message wParam: wParam lParam: lParam
"Private - Pass an event to the 'default' window procedure of the receiver."
Expand Down Expand Up @@ -353,6 +358,22 @@ notifyMove
webviewController isNull ifTrue: [^self].
webviewController NotifyParentWindowPositionChanged!

observeBrowserProcessExit
"Private - Process exit is a special case as we don't want to unregister this immediately when closing the browser view, or we will never get the event!!.
When the view is being fully recreated, e.g. due to changing a style that is set in environment options such as the scrollbar style, we may very well receive this for the previous browser process after we have already started creating the new view."

| urlPresenter processExited |
urlPresenter := self presenter.
processExited := WebView2EventSink new.
processExited
source: webviewEnvironment
interfaceClass: ICoreWebView2BrowserProcessExitedEventHandler
handler:
[:source :args |
urlPresenter trigger: #processExited: with: args.
processExited free].
processExited register!

observeControllerEvents
##({
ICoreWebView2AcceleratorKeyPressedEventHandler.
Expand All @@ -369,17 +390,22 @@ observeControllerEvents
do: [:each | self observeEvent: each from: webviewComposition]]!

observeEnvironmentEvents
environmentEventHandlers := OrderedCollection new: 3.
##({
ICoreWebView2NewBrowserVersionAvailableEventHandler.
ICoreWebView2BrowserProcessExitedEventHandler.
ICoreWebView2ProcessInfosChangedEventHandler
}) do:
[:each |
self registerEnvironmentEventSink: (WebView2EventSink
source: webviewEnvironment
interfaceClass: each
handler: (each triggerBlockFor: self presenter))]!
"Process exit is a special case as we don't want to unregister this immediately when closing the browser view, or we will never get the event!!"

environmentEventHandlers
ifNil:
[environmentEventHandlers := ##({
ICoreWebView2NewBrowserVersionAvailableEventHandler.
ICoreWebView2ProcessInfosChangedEventHandler
}) collect:
[:each |
(WebView2EventSink
source: webviewEnvironment
interfaceClass: each
handler: (each triggerBlockFor: self presenter))
register;
yourself]].
self observeBrowserProcessExit!

observeEvent: anICoreWebView2EventHandlerClass from: anICoreWebView2EventSource
^self registerEventSink: (WebView2EventSink
Expand Down Expand Up @@ -439,8 +465,12 @@ observeWindowEvents
}) do: [:each | self observeEvent: each from: webview]!

onControllerCreated: anICoreWebView2Controller
webviewController := self queryControllerInterface: anICoreWebView2Controller.
self observeControllerEvents.
webviewController := anICoreWebView2Controller downCast.
"Since we cannot trigger events off the presenter until it has been set, we delay observing environment events to here as at this point we know we definitely have a presenter and webview environment"
self
observeEnvironmentEvents;
observeControllerEvents.
self presenter trigger: #controllerAvailable.
self resizeContentToFit.
webview := webviewController coreWebView2.
self initializeControl!
Expand All @@ -449,13 +479,13 @@ onDestroyed
self unregisterEvents.
self content close.
self releaseWebView.
"We don't free the webview environment, but rather let it be finalised. This allows an external observer to watch for the browser process exiting."
webviewEnvironment := nil.
self releaseWebViewEnvironment.
^super onDestroyed!

onEnvironmentCreated: anICoreWebView2Environment
webviewEnvironment := anICoreWebView2Environment downCast.
self observeEnvironmentEvents.
"Note that the presenter has not been set this point"
self trigger: #environmentAvailable.
self createWebView!

onHistoryChanged
Expand Down Expand Up @@ -522,19 +552,6 @@ profileName: aString
profileName := aString.
webviewController notNull ifTrue: [self recreate]!

queryControllerInterface: anIUnknown
| interfaceClass |
interfaceClass := ICoreWebView2Controller4.

[(anIUnknown queryInterface: interfaceClass ifNone: []) ifNotNil: [:interface | ^interface].
(interfaceClass := interfaceClass superclass) == ICoreWebView2Controller]
whileFalse.
^anIUnknown queryInterface: ICoreWebView2Controller!

registerEnvironmentEventSink: aWebView2EventSink
aWebView2EventSink register.
^environmentEventHandlers add: aWebView2EventSink!

registerEventSink: aWebView2EventSink
aWebView2EventSink register.
^eventHandlers add: aWebView2EventSink!
Expand All @@ -550,6 +567,9 @@ releaseWebView
[webviewController free.
webviewController := nil]!

releaseWebViewEnvironment
webviewEnvironment := nil!

resizeContentToFit
self content rectangle: self clientRectangle!

Expand All @@ -568,7 +588,7 @@ scrollBarStyle: anInteger
| style |
style := anInteger ?? COREWEBVIEW2_SCROLLBAR_STYLE_DEFAULT.
self scrollBarStyle = style ifTrue: [^self].
self recreateAround: [environmentOptions scrollBarStyle: style]!
self recreateAround: ["self halt. "environmentOptions scrollBarStyle: style]!

setControlBackcolor: aColor
self webviewController defaultBackgroundColor: aColor!
Expand All @@ -594,13 +614,13 @@ subViews
^#()!

trackingPreventionLevel
^environmentOptions trackingPreventionLevel!
^environmentOptions isTrackingPreventionEnabled
ifTrue: [self profile preferredTrackingPreventionLevel]
ifFalse: [COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_NONE]!

trackingPreventionLevel: anInteger
| level |
level := anInteger ?? COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_BALANCED.
self trackingPreventionLevel = level ifTrue: [^self].
self recreateAround: [environmentOptions trackingPreventionLevel: level]!
self profile
preferredTrackingPreventionLevel: anInteger ?? COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_BALANCED!

unregisterEvents
eventHandlers
Expand Down Expand Up @@ -723,6 +743,7 @@ isWebMessageEnabled:!public!settings! !
isZoomControlEnabled!public!settings! !
isZoomControlEnabled:!public!settings! !
notifyMove!event handling!private! !
observeBrowserProcessExit!private!realizing/unrealizing! !
observeControllerEvents!private!realizing/unrealizing! !
observeEnvironmentEvents!private!realizing/unrealizing! !
observeEvent:from:!helpers!private! !
Expand All @@ -740,10 +761,9 @@ onViewCreated!event handling!public! !
profile!commands!public! !
profileName!accessing!public! !
profileName:!accessing!public! !
queryControllerInterface:!helpers!private! !
registerEnvironmentEventSink:!helpers!public! !
registerEventSink:!helpers!public! !
releaseWebView!operations!private!realizing/unrealizing! !
releaseWebViewEnvironment!operations!private!realizing/unrealizing! !
resizeContentToFit!helpers!private! !
scriptLocale!accessing!public! !
scriptLocale:!accessing!public! !
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -93,7 +93,7 @@ Core.Tests.DolphinTest
UI.Tests.PresenterTest
subclass: #'WebView2.Tests.WebView2ViewTest'
instanceVariableNames: 'domContentLoaded navigationCompleted processFailed webViewReady processExitedSink webviewEnvironment processExited navigationStarting'
instanceVariableNames: 'domContentLoaded navigationCompleted processFailed webViewReady webviewEnvironment processExited navigationStarting'
classVariableNames: ''
imports: #(#{UI})
classInstanceVariableNames: ''
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,9 @@ browserProcessExitKind
self get_BrowserProcessExitKind: buf.
^buf asSignedInteger!

browserProcessExitKindName
^(#('Normal' 'Failed') lookup: self browserProcessExitKind + 1) ?? 'Unknown'!

browserProcessId
"Answer the unsigned <integer> value of the 'BrowserProcessId' property of the receiver."

Expand Down Expand Up @@ -78,10 +81,11 @@ isNormalExit
^self browserProcessExitKind == COREWEBVIEW2_BROWSER_PROCESS_EXIT_KIND_NORMAL!

printableProperties
^#(#browserProcessExitKind #browserProcessId)! !
^#(#browserProcessExitKindName #browserProcessId)! !

!WebView2.ICoreWebView2BrowserProcessExitedEventArgs categoriesForMethods!
browserProcessExitKind!properties!public! !
browserProcessExitKindName!properties!public! !
browserProcessId!properties!public! !
get_BrowserProcessExitKind:!**auto generated**!COM Interfaces-ICoreWebView2BrowserProcessExitedEventArgs!private! !
get_BrowserProcessId:!**auto generated**!COM Interfaces-ICoreWebView2BrowserProcessExitedEventArgs!private! !
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -224,7 +224,7 @@ defaultBackgroundColor
"Answer the <Color> value of the 'DefaultBackgroundColor' property of the receiver."

| buf |
buf := ByteArray newFixed: 4.
buf := UInt32Bytes new.
self get_DefaultBackgroundColor: buf.
^Graphics.Color fromArray: buf!

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -109,13 +109,13 @@ releaseChannels: value
self put_ReleaseChannels: value! !

!WebView2.ICoreWebView2EnvironmentOptions7 categoriesForMethods!
channelSearchKind!**auto generated**!properties!public! !
channelSearchKind!properties!public! !
channelSearchKind:!**auto generated**!properties!public! !
get_ChannelSearchKind:!**auto generated**!COM Interfaces-ICoreWebView2EnvironmentOptions7!private! !
get_ReleaseChannels:!**auto generated**!COM Interfaces-ICoreWebView2EnvironmentOptions7!private! !
put_ChannelSearchKind:!**auto generated**!COM Interfaces-ICoreWebView2EnvironmentOptions7!private! !
put_ReleaseChannels:!**auto generated**!COM Interfaces-ICoreWebView2EnvironmentOptions7!private! !
releaseChannels!**auto generated**!properties!public! !
releaseChannels!properties!public! !
releaseChannels:!**auto generated**!properties!public! !
!

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ scrollBarStyle: value
!WebView2.ICoreWebView2EnvironmentOptions8 categoriesForMethods!
get_ScrollBarStyle:!**auto generated**!COM Interfaces-ICoreWebView2EnvironmentOptions8!private! !
put_ScrollBarStyle:!**auto generated**!COM Interfaces-ICoreWebView2EnvironmentOptions8!private! !
scrollBarStyle!**auto generated**!properties!public! !
scrollBarStyle!properties!public! !
scrollBarStyle:!**auto generated**!properties!public! !
!

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -60,14 +60,14 @@ eventName
^self subclassResponsibility!

hasArgs
^self argsClass == IUnknown!
^self argsClass ~~ IUnknown!

triggerBlockFor: aUrlPresenter
| event |
event := self eventName.
^self hasArgs
ifTrue: [[aUrlPresenter trigger: event]]
ifFalse: [[:source :args | aUrlPresenter trigger: event with: args]]! !
ifTrue: [[:source :args | aUrlPresenter trigger: event with: args]]
ifFalse: [[aUrlPresenter trigger: event]]! !

!WebView2.ICoreWebView2EventHandler class categoriesForMethods!
argsClass!constants!public! !
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -114,12 +114,14 @@ testEnableTrackingPrevention
subject := WebView2EnvironmentOptions new.
interface := subject queryInterface: ICoreWebView2EnvironmentOptions5.
self assert: subject trackingPreventionLevel equals: COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_BALANCED.
self assert: interface enableTrackingPrevention
equals: COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_BALANCED.
interface enableTrackingPrevention: COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_STRICT.
self assert: subject trackingPreventionLevel equals: COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_STRICT.
self assert: interface enableTrackingPrevention
equals: COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_STRICT!
self assert: interface enableTrackingPrevention.
interface enableTrackingPrevention: false.
self deny: subject isTrackingPreventionEnabled.
self assert: subject trackingPreventionLevel equals: COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_NONE.
interface enableTrackingPrevention: true.
self assert: subject isTrackingPreventionEnabled.
self assert: subject trackingPreventionLevel equals: COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_BALANCED.
!

testExclusiveDataFolderAccess
| subject interface |
Expand Down Expand Up @@ -193,20 +195,20 @@ testStlConvertFromVersion0
self assert: options isCustomCrashReportingEnabled.
self assert: options browserVersion equals: '100.0.1185'.
self assert: options locale equals: 'fr-FR'.
self assert: options trackingPreventionLevel equals: COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_BALANCED.
self assert: options isTrackingPreventionEnabled.
self assert: options channelSearchKind equals: COREWEBVIEW2_CHANNEL_SEARCH_KIND_MOST_STABLE.
self assert: options releaseChannels equals: COREWEBVIEW2_RELEASE_CHANNELS_STABLE.
self assert: options scrollBarStyle equals: COREWEBVIEW2_SCROLLBAR_STYLE_DEFAULT.
self assert: options customSchemeRegistrations equals: #()!

testStlConvertFromVersion0a
| options |
options := (Object fromLiteralStoreArray: #(#'!!STL' 6 1286 #{WebView2.WebView2EnvironmentOptions} nil 13 8 'fr-FR' 8 '100.0.1185' 5)).
options := (Object fromLiteralStoreArray: #(#'!!STL' 6 1286 #{WebView2.WebView2EnvironmentOptions} nil 13 8 'fr-FR' 8 '100.0.1185' 1)).
self deny: options allowSSO.
self assert: options isCustomCrashReportingEnabled.
self assert: options browserVersion equals: '100.0.1185'.
self assert: options locale equals: 'fr-FR'.
self assert: options trackingPreventionLevel equals: COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_BALANCED.
self deny: options isTrackingPreventionEnabled.
self assert: options channelSearchKind equals: COREWEBVIEW2_CHANNEL_SEARCH_KIND_MOST_STABLE.
self assert: options releaseChannels equals: COREWEBVIEW2_RELEASE_CHANNELS_STABLE.
self assert: options scrollBarStyle equals: COREWEBVIEW2_SCROLLBAR_STYLE_DEFAULT.
Expand All @@ -220,7 +222,7 @@ testStlConvertFromVersion1
self assert: options isCustomCrashReportingEnabled.
self assert: options browserVersion equals: '100.0.1185'.
self assert: options locale equals: 'fr-FR'.
self assert: options trackingPreventionLevel equals: COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_STRICT.
self assert: options isTrackingPreventionEnabled.
self assert: options channelSearchKind equals: COREWEBVIEW2_CHANNEL_SEARCH_KIND_LEAST_STABLE.
self assert: options releaseChannels equals: COREWEBVIEW2_RELEASE_CHANNELS_BETA.
self assert: options scrollBarStyle equals: COREWEBVIEW2_SCROLLBAR_STYLE_FLUENT_OVERLAY.
Expand All @@ -233,7 +235,7 @@ testStlConvertFromVersion2
self assert: options isCustomCrashReportingEnabled.
self assert: options browserVersion equals: '100.0.1185'.
self assert: options locale equals: 'fr-FR'.
self assert: options trackingPreventionLevel equals: COREWEBVIEW2_TRACKING_PREVENTION_LEVEL_BALANCED.
self assert: options isTrackingPreventionEnabled.
self assert: options channelSearchKind equals: COREWEBVIEW2_CHANNEL_SEARCH_KIND_MOST_STABLE.
self assert: options releaseChannels equals: COREWEBVIEW2_RELEASE_CHANNELS_STABLE.
self assert: options scrollBarStyle equals: COREWEBVIEW2_SCROLLBAR_STYLE_DEFAULT.
Expand Down
Loading

0 comments on commit c366a38

Please sign in to comment.