Virtual Box Seamless mode

Joined
Feb 22, 2010
Messages
76
Reaction score
1
Points
8
Your Mac's Specs
21.5", 3.06 GHz intel Core 2 duo, ATI Radeon HD 4670 graphics with 256MB
I have virtual box set up with windows 7. They recently updated so it can support 2 monitors now, but that changed seamless mode. Now I when I run in seamless mode it completely blocks my mac desktop, all I see is windows on both monitors. It's pretty much the same as running in full screen except I can see the mac app bar on the bottom of my one screen. Has anybody experienced this and do you know how to fix it?

Thanks!
 
Joined
Jul 16, 2010
Messages
40
Reaction score
1
Points
8
Location
Ukraine, Kiev
There is some program called xMonad. Try to use it for this.
Here configuration for it :

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances, FlexibleContexts, NoMonomorphismRestriction #-}
import XMonad
import qualified XMonad.StackSet as W -- to shift and float windows
import Data.Ratio
import qualified Data.Map as M
import XMonad.Actions.CycleWS
import XMonad.Actions.WindowGo
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.FadeInactive
import XMonad.Hooks.DynamicLog
import XMonad.Layout.Grid
import XMonad.Layout.LayoutModifier
import XMonad.Layout.PerWorkspace
import XMonad.Layout.LayoutCombinators hiding ( (|||) )
import XMonad.Layout.IM
import XMonad.Layout.IndependentScreens
import XMonad.Layout.ShowWName
import XMonad.Util.EZConfig
import XMonad.Util.Run
import XMonad.Util.WindowProperties
import Control.Monad
import Graphics.X11.ExtraTypes.XF86
import Foreign.C.Types

-- Get the property value box
getProp :: Atom -> Window -> X (Maybe [CLong])
getProp a w = withDisplay $ \dpy -> io $ getWindowProperty32 dpy a w
-- This function checks whether the property is put up the window name in the value of value
checkAtom name value = ask >>= \w -> liftX $ do
a <- getAtom name
val <- getAtom value
mbr <- getProp a w
case mbr of
Just [r] -> return $ elem (fromIntegral r) [val]
_ -> return False
-- This function checks whether the dialog
checkDialog = checkAtom "_NET_WM_WINDOW_TYPE" "_NET_WM_WINDOW_TYPE_DIALOG"
-- Coming off (tear-off) menu
checkMenu = checkAtom "_NET_WM_WINDOW_TYPE" "_NET_WM_WINDOW_TYPE_MENU"

basicLayout = Mirror tiled where
tiled = Tall nmaster delta ratio
nmaster = 1
delta = 2/100
ratio = 3/7
basicALayout = avoidStruts $ basicLayout
tallLayout = Mirror basicLayout
tallALayout = avoidStruts $ Mirror basicLayout
imLayout = withIMs ratio rosters chatLayout where
chatLayout = Mirror Grid
ratio = 1%5
rosters = [skypeRoster, pidginRoster]
pidginRoster = (ClassName "Pidgin") `And` (Role "buddy_list")
--skypeRoster = (ClassName "Skype") `And` (Not (Title "Options")) `And` (Not (Role "Chats")) `And` (Not (Title "*чат")) `And` (Not (Role "CallWindowForm"))
skypeRoster = (Title "evvproffessorr - Skype™ (Beta)")

myLayoutHook = fullscreen $ iml $ normal where
normal = basicLayout ||| basicALayout ||| tallLayout ||| tallALayout ||| Full
fullscreen = onWorkspace "0_music, 1_music, 0_video, 1_video" Full
iml = onWorkspace "1_im" imLayout
--av = onWorkspace "7, 9" basicALayout

manageMenus = checkMenu --> doFloat
manageDialogs = checkDialog --> doFloat

imManageHooks = composeAll . concat $
[ [className =? "Firefox" --> moveTo "1_firefox"]
, [title =? d --> doFloat | d <- myTFloats]
, [className =? c --> doFloat | c <- myFloats]
, [className =? a --> moveTo "1_im" | a <- myIMs]
, [title =? "NCMPC" --> moveTo "4"]
, [title =? "SMPlayer" --> moveTo "5"]
, [className =? "Krusader" --> moveTo "1_main"]
, [className =? "Wine" --> moveTo "1_wine"]
, [title =? "Sun VirtualBox" --> moveTo "8"]
, [className =? b --> doIgnore | b <- myIgnores]
, [className =? "Basket" --> moveTo "9"]
,[isFullscreen --> (doF W.focusDown <+> doFullFloat)]
]
where
--moveTo = doF . W.shift
moveTo = doShift
myIMs = ["Pidgin", "Skype"]
myIgnores = ["Qt-subapplication", "Plasma"]
myFloats = ["KMix", "Gimp-2.6", "Wine"]
myTFloats = ["Firefox Preferences", "Preparation filter FOR Adblock Plus"]

myManageHook = imManageHooks <+> manageMenus <+> manageDialogs

myLogHook :: X ()
myLogHook = fadeInactiveLogHook fadeAmount
where fadeAmount = 0x66666666

-- | Data type for LayoutModifier which converts given layout to IM-layout
-- (with dedicated space for the roster and original layout for chat windows)
data AddRosters a = AddRosters Rational [Property] deriving (Read, Show)

instance LayoutModifier AddRosters Window where
modifyLayout (AddRosters ratio props) = applyIMs ratio props
modifierDescription _ = "IMs"

-- | Modifier which converts given layout to IMs-layout (with dedicated
-- space for rosters and original layout for chat windows)
withIMs :: LayoutClass l a => Rational -> [Property] -> l a -> ModifiedLayout AddRosters l a
withIMs ratio props = ModifiedLayout $ AddRosters ratio props

-- | IM layout modifier applied to the Grid layout
gridIMs :: Rational -> [Property] -> ModifiedLayout AddRosters Grid a
gridIMs ratio props = withIMs ratio props Grid

hasAnyProperty :: [Property] -> Window -> X Bool
hasAnyProperty [] _ = return False
hasAnyProperty (p:ps) w = do
b <- hasProperty p w
if b then return True else hasAnyProperty ps w

-- | Internal function for placing the rosters specified by
-- the properties and running original layout for all chat windows
applyIMs :: (LayoutClass l Window) =>
Rational
-> [Property]
-> W.Workspace WorkspaceId (l Window) Window
-> Rectangle
-> X ([(Window, Rectangle)], Maybe (l Window))
applyIMs ratio props wksp rect = do
let stack = W.stack wksp
let ws = W.integrate' $ stack
rosters <- filterM (hasAnyProperty props) ws
let n = fromIntegral $ length rosters
let (rostersRect, chatsRect) = splitHorizontallyBy (n * ratio) rect
let rosterRects = splitHorizontally n rostersRect
let filteredStack = stack >>= W.filter (`notElem` rosters)
wrs <- runLayout (wksp {W.stack = filteredStack}) chatsRect
return ((zip rosters rosterRects) ++ fst wrs, snd wrs)

myMouseBindings (XConfig {XMonad.modMask = mod4Mask}) = M.fromList $
[ ((0, 9), (\_ -> toggleWS)),
((mod4Mask, button1), (\w -> focus w >> mouseMoveWindow w)),
((mod4Mask, button3), (\w -> focus w >> mouseResizeWindow w))
]

--myWorkspaces =
--withScreens 1 ["first"]["main","firefox","im","music","video","wine","virtualbox","smth","smth2"]
--withScreens 2 ["second"]["info","chats","player","films"]

myWorkspaces = withScreens 2 ["main","firefox","im","music","video","wine","virtualbox","smth","smth2"]

main = do
xmonad $ defaultConfig {
modMask = mod4Mask
, layoutHook = showWName myLayoutHook
, manageHook = myManageHook
, workspaces = myWorkspaces
, borderWidth = 0
, logHook = myLogHook
, terminal = "urxvt"
, mouseBindings = myMouseBindings
}
`additionalKeysP`
[ ("M1-<F4>", kill)
, ("M1-<Tab>", windows W.focusDown)
, ("M1-S-<Tab>", windows W.focusUp)
, ("<XF86Explorer>", spawn "urxvt")
, ("<XF86Launch3>", spawn "urxvt --title NCMPC -e ncmpc -c -m -S")
, ("<XF86Launch5>", spawn "~/.mpd/playlist.sh")
, ("<XF86Launch6>", spawn "urxvt -e ssh -p 43434 [email protected]")
, ("<XF86Launch7>", spawn "urxvt -e ssh -p 43434 [email protected]")
, ("<XF86Launch9>", prevWS)
, ("<XF86Mail>", toggleWS)
, ("<XF86Favorites>", nextWS)
, ("<XF86MenuKB>", windows $ W.view "3")
, ("S-<XF86MenuKB>", (windows $ W.shift "3") >> (windows $ W.view "3"))
, ("C-<XF86MenuKB>", windows $ W.view "6")
, ("<XF86Sleep>", spawn "sudo pm-suspend")
, ("<XF86AudioLowerVolume>", spawn "amixer -q set Master 1- unmute")
, ("<XF86AudioRaiseVolume>", spawn "amixer -q set Master 1+ unmute")
, ("<XF86MyComputer>", spawn "gmrun")
]


Write if smth wrong or you need some other advice.
 
OP
N
Joined
Feb 22, 2010
Messages
76
Reaction score
1
Points
8
Your Mac's Specs
21.5", 3.06 GHz intel Core 2 duo, ATI Radeon HD 4670 graphics with 256MB
Thanks! I will give it a try and hopefully it will fix it
 

Shop Amazon


Shop for your Apple, Mac, iPhone and other computer products on Amazon.
We are a participant in the Amazon Services LLC Associates Program, an affiliate program designed to provide a means for us to earn fees by linking to Amazon and affiliated sites.
Top