Browse Source

fix: when a group is deleted, switch to the group of the active tab

Jocelyn Boullier 4 years ago
parent
commit
c6c515be0e

+ 9 - 6
src/Background.purs

@@ -1,7 +1,7 @@
 module PureTabs.Background where
 
 import Browser.Runtime as Runtime
-import Browser.Tabs (Tab, TabId, WindowId)
+import Browser.Tabs (Tab, TabId(..), WindowId(..))
 import Browser.Tabs as BT
 import Browser.Tabs.OnActivated as OnActivated
 import Browser.Tabs.OnAttached as OnAttached
@@ -25,9 +25,10 @@ import Data.Lens (_Just, set, view)
 import Data.Lens.At (at)
 import Data.List (List, foldMap)
 import Data.Map as M
-import Data.Set as Set
 import Data.Maybe (Maybe(..))
 import Data.Monoid ((<>))
+import Data.Newtype (unwrap)
+import Data.Set as Set
 import Data.Show (show)
 import Data.Unit (unit)
 import Effect (Effect)
@@ -35,7 +36,7 @@ import Effect.Aff (launchAff_)
 import Effect.Class (liftEffect)
 import Effect.Console (log)
 import Effect.Ref as Ref
-import Prelude (Unit, bind, ($), discard, (<<<))
+import Prelude (Unit, bind, ($), discard, (<<<), (<$>))
 import PureTabs.Model.Events (BackgroundEvent(..), SidebarEvent(..))
 import PureTabs.Model.GlobalState as GS
 
@@ -49,8 +50,8 @@ main :: Effect Unit
 main = do
   log "starting background"
   launchAff_ do
-     allTabs <- BT.browserQuery
-     liftEffect $ initializeBackground =<< (Ref.new $ GS.initialTabListToGlobalState allTabs)
+     allTabs <- BT.browserQuery {}
+     liftEffect $ initializeBackground =<< (Ref.new $ GS.initialTabsToGlobalState allTabs)
 
 initializeBackground :: Ref.Ref GS.GlobalState -> Effect Unit
 initializeBackground ref = do
@@ -199,7 +200,9 @@ manageSidebar ref winId port = case _ of
 
   SbDeletedGroup gid tabIds -> launchAff_ do
      BT.browserRemove tabIds
-     liftEffect $ Runtime.postMessageJson port $ BgGroupDeleted gid
+     activeTab <- BT.browserQuery { windowId: unwrap winId, active: true }
+     let activeTabId = activeTab # A.head >>> (<$>) (unwrap >>> _.id)
+     liftEffect $ Runtime.postMessageJson port $ BgGroupDeleted gid activeTabId
 
 
   SbDetacheTab -> pure unit

+ 4 - 2
src/Browser/Tabs.js

@@ -1,7 +1,9 @@
 "use strict";
 
-exports.queryImpl = function () {
-  return browser.tabs.query({});
+exports.queryImpl = function (query) {
+  return function () {
+    return browser.tabs.query(query);
+  };
 };
 
 exports["browserRemove'"] = function (tabs) {

+ 33 - 8
src/Browser/Tabs.purs

@@ -23,7 +23,6 @@ import Data.Eq (class Eq)
 import Data.Function (($))
 import Data.Generic.Rep (class Generic)
 import Data.Generic.Rep.Show (genericShow)
-import Data.List (List, fromFoldable)
 import Data.Maybe (Maybe)
 import Data.Newtype (class Newtype)
 import Data.Number.Format (toString)
@@ -43,6 +42,8 @@ import Prim.Row (class Union)
 newtype WindowId
   = WindowId Number
 
+derive instance newtypeWindowId :: Newtype WindowId _
+
 derive instance eqWindowId :: Eq WindowId
 
 derive instance ordWindowId :: Ord WindowId
@@ -122,14 +123,38 @@ instance encodeTab :: Encode Tab where
 instance decodeTab :: Decode Tab where
   decode x = genericDecode (defaultOptions { unwrapSingleConstructors = true }) x
 
-foreign import queryImpl :: Effect (Promise (Array Foreign))
 
-browserQuery :: Aff (List Tab)
-browserQuery = do
-  tabsArray <- toAffE queryImpl
-  let
-    tabsList = fromFoldable tabsArray
-  parsed <- liftEffect $ traverse unwrapForeign tabsList
+type QueryRecord = 
+  ( active :: Boolean
+  , audible :: Boolean
+  , autoDiscardable :: Boolean
+  , cookieStoreId :: String
+  , currentWindow :: Boolean
+  , discarded :: Boolean
+  , hidden :: Boolean
+  , highlighted :: Boolean
+  , index :: Int
+  , muted :: Boolean
+  , lastFocusedWindow :: Boolean
+  , pinned :: Boolean
+  , title :: String
+  , url :: String
+  , windowId :: Number
+  )
+
+foreign import queryImpl 
+  :: forall r
+   . { | r }
+  -> Effect (Promise (Array Foreign))
+
+browserQuery 
+  :: forall r r2
+   . Union r r2 QueryRecord
+  => Record r
+  -> Aff (Array Tab)
+browserQuery query = do
+  tabsArray <- toAffE $ queryImpl query
+  parsed <- liftEffect $ traverse unwrapForeign tabsArray
   pure parsed
 
 foreign import browserRemove' :: (Array Number) -> Effect (Promise Unit)

+ 1 - 1
src/Model/Events.purs

@@ -21,7 +21,7 @@ data BackgroundEvent
   | BgTabActivated (Maybe TabId) TabId
   | BgTabAttached Tab
   | BgTabDetached TabId
-  | BgGroupDeleted GroupId
+  | BgGroupDeleted GroupId (Maybe TabId)
 
 derive instance genBackgroundEvent :: Generic BackgroundEvent _
 

+ 9 - 9
src/Model/GlobalState.purs

@@ -19,7 +19,7 @@ module PureTabs.Model.GlobalState (
   , _windows
   , emptyWindow
   , initialGlobalState
-  , initialTabListToGlobalState
+  , initialTabsToGlobalState
   , addEmptyWindow
   , deleteWindow
   , createTab
@@ -41,7 +41,7 @@ import Control.Alt ((<|>))
 import Control.Bind (join, bind, (>>=))
 import Control.Category (identity, (<<<), (>>>))
 import Control.Plus (empty) as A
-import Data.Array (deleteAt, filter, foldl, fromFoldable, insertAt, mapWithIndex, sortBy, (!!)) as A
+import Data.Array (deleteAt, filter, foldl, fromFoldable, insertAt, mapWithIndex, sortBy, groupBy, (!!)) as A
 import Data.Eq ((==), (/=))
 import Data.Function (const, on, ($))
 import Data.Functor (map, (<#>), (<$>))
@@ -49,8 +49,8 @@ import Data.Lens (Lens', Traversal', _Just, over, preview, set, view)
 import Data.Lens.At (at)
 import Data.Lens.Iso.Newtype (_Newtype)
 import Data.Lens.Record (prop)
-import Data.List (List, groupBy, head) as L
-import Data.List.NonEmpty (NonEmptyList, head) as NEL
+import Data.List (head) as L
+import Data.Array.NonEmpty (NonEmptyArray, head) as NEA
 import Data.Map as M
 import Data.Maybe (Maybe(..), fromMaybe, maybe, maybe')
 import Data.Monoid ((<>))
@@ -170,15 +170,15 @@ sendToWindowPort wid state event =
     Just port -> postMessageJson port event
     Nothing -> error $ "bg: no port found for window id " <> (show wid)
 
-initialTabListToGlobalState :: L.List Tab -> GlobalState
-initialTabListToGlobalState tabs = { windows: windows, detached: Nothing }
+initialTabsToGlobalState :: Array Tab -> GlobalState
+initialTabsToGlobalState tabs = { windows: windows, detached: Nothing }
   where
-  groupedTabs = L.groupBy (\(Tab t1) (Tab t2) -> t1.windowId == t2.windowId) tabs
+  groupedTabs = A.groupBy (\(Tab t1) (Tab t2) -> t1.windowId == t2.windowId) tabs
 
-  tabsToWindow :: NEL.NonEmptyList Tab -> Tuple WindowId ExtWindow
+  tabsToWindow :: NEA.NonEmptyArray Tab -> Tuple WindowId ExtWindow
   tabsToWindow tabs' =
     let
-      windowId = (\(Tab t) -> t.windowId) $ NEL.head tabs'
+      windowId = (\(Tab t) -> t.windowId) $ NEA.head tabs'
 
       window =
         { tabs: M.fromFoldable $ tabs' <#> \(Tab t) -> Tuple t.id (Tab t)

+ 9 - 5
src/Sidebar/Components/Bar.purs

@@ -2,7 +2,7 @@ module PureTabs.Sidebar.Bar where
 
 import Browser.Tabs (Tab(..), TabId)
 import Control.Alternative (pure)
-import Control.Bind (bind, discard, map, void, (<#>))
+import Control.Bind (bind, discard, map, void, (<#>), (>>=))
 import Data.Array ((:))
 import Data.Array as A
 import Data.Eq ((/=))
@@ -24,7 +24,7 @@ import Halogen as H
 import Halogen.HTML as HH
 import Halogen.HTML.Events as HE
 import Halogen.HTML.Properties as HP
-import Prelude (flip, show, (#), (&&), (+), (-), (<<<), (<>), (==), (>), (>>>))
+import Prelude (flip, show, (<$>), (#), (&&), (+), (-), (<<<), (<>), (==), (>), (>>>))
 import PureTabs.Model.Events (SidebarEvent(..))
 import PureTabs.Model.Group (GroupId(..))
 import PureTabs.Sidebar.Component.GroupName as GroupName
@@ -62,7 +62,7 @@ data Action
 
 data Query a
   = TabsQuery (Tabs.Query a)
-  | GroupDeleted GroupId a
+  | GroupDeleted GroupId (Maybe TabId) a
 
 initialState :: forall i. i -> State
 initialState _ =
@@ -276,8 +276,12 @@ handleQuery :: forall act a m. Query a -> H.HalogenM State act Slots SidebarEven
 handleQuery = case _ of 
    TabsQuery q -> handleTabsQuery q
 
-   GroupDeleted gid a -> do 
-      H.modify_ \s -> s { groups = M.delete gid s.groups }
+   GroupDeleted gid currentTid a -> do 
+      H.modify_ \s -> 
+        let 
+            currentGroup = fromMaybe s.currentGroup $ currentTid >>= (flip M.lookup s.tabsToGroup)
+         in
+            s { groups = M.delete gid s.groups, currentGroup = currentGroup }
       pure $ Just a
 
 

+ 2 - 2
src/Sidebar/Sidebar.purs

@@ -81,8 +81,8 @@ onBackgroundMsgConsumer query =
           void $ query $ H.tell $ \q -> Bar.TabsQuery (Tabs.TabAttached tab q)
           pure Nothing
 
-        BgGroupDeleted gid -> do
-           void $ query $ H.tell $ Bar.GroupDeleted gid
+        BgGroupDeleted gid currentTid -> do
+           void $ query $ H.tell $ Bar.GroupDeleted gid currentTid
            pure Nothing
 
 -- | Workaround for https://bugzilla.mozilla.org/show_bug.cgi?id=1640112