diff --git a/src/Gargantext/Components/Forest.purs b/src/Gargantext/Components/Forest.purs
index 6c38d148984d676cfa343b2b8c52612517e6afef..f62cd0c48d27baa19d04af7087be0ed65d328071 100644
--- a/src/Gargantext/Components/Forest.purs
+++ b/src/Gargantext/Components/Forest.purs
@@ -10,7 +10,6 @@ import Gargantext.Routes (AppRoute)
 import Gargantext.Sessions (Session(..), Sessions, unSessions)
 import Gargantext.Components.Forest.Tree (treeView)
 import Gargantext.Utils.Reactix as R2
-import Gargantext.Utils (glyphicon)
 
 type Props =
   ( sessions  :: Sessions
diff --git a/src/Gargantext/Components/Forest/Tree.purs b/src/Gargantext/Components/Forest/Tree.purs
index 2a69665137d9f74cabee1cfc2b4aaceb6f595dec..9f0f6f037f53d24d571f460acc3035118d7964e8 100644
--- a/src/Gargantext/Components/Forest/Tree.purs
+++ b/src/Gargantext/Components/Forest/Tree.purs
@@ -1,25 +1,14 @@
 module Gargantext.Components.Forest.Tree where
 
 import DOM.Simple.Console (log2)
-import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
-import Data.Array (filter, null)
-import Data.Generic.Rep (class Generic)
-import Data.Generic.Rep.Eq (genericEq)
-import Data.Generic.Rep.Show (genericShow)
-import Data.Maybe (Maybe(..), fromJust)
-import Data.Newtype (class Newtype)
-import Data.Tuple (Tuple)
+import Data.Maybe (Maybe)
+-- import Data.Newtype (class Newtype)
 import Data.Tuple.Nested ((/\))
-import Effect.Aff (Aff, launchAff, runAff)
+import Effect.Aff (Aff)
 import Effect.Class (liftEffect)
-import Effect.Uncurried (mkEffectFn1)
-import FFI.Simple ((..))
 import Gargantext.Components.Forest.Tree.Node.Action
-import Gargantext.Components.Forest.Tree.Node.Action.Add
-import Gargantext.Components.Forest.Tree.Node.Action.Rename
-import Gargantext.Components.Forest.Tree.Node.Action.Upload
-import Gargantext.Components.Forest.Tree.Node
-import Gargantext.Components.Forest.Tree.Node.Box
+import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadFile)
+import Gargantext.Components.Forest.Tree.Node.Box (nodeMainSpan)
 import Gargantext.Ends (Frontends)
 import Gargantext.Components.Loader (loader)
 import Gargantext.Routes (AppRoute)
diff --git a/src/Gargantext/Components/Forest/Tree/Node/Box.purs b/src/Gargantext/Components/Forest/Tree/Node/Box.purs
index 77eba82b35ecf08c5115d9c6ce865dd12e4a9d83..adf4a3920aefac61dc3c95bab86cee0484152cdd 100644
--- a/src/Gargantext/Components/Forest/Tree/Node/Box.purs
+++ b/src/Gargantext/Components/Forest/Tree/Node/Box.purs
@@ -1,32 +1,31 @@
 module Gargantext.Components.Forest.Tree.Node.Box where
 
 import DOM.Simple.Console (log2)
-import Data.Array (filter, null)
-import Data.Maybe (Maybe(..), fromJust, isJust)
-import Data.Tuple (fst, Tuple(..))
+import Data.Maybe (Maybe(..), fromJust)
+import Data.Tuple (Tuple(..))
 import Data.Tuple.Nested ((/\))
 import Effect.Aff (Aff, launchAff, runAff)
 import Effect.Class (liftEffect)
 import Effect.Uncurried (mkEffectFn1)
 import FFI.Simple ((..))
-import Gargantext.Components.Forest.Tree.Node
-import Gargantext.Components.Forest.Tree.Node.Action
-import Gargantext.Components.Forest.Tree.Node.Action.Add
-import Gargantext.Components.Forest.Tree.Node.Action.Rename
-import Gargantext.Components.Forest.Tree.Node.Action.Upload
-import Gargantext.Components.Search.Types
-import Gargantext.Components.Search.SearchBar
+import Gargantext.Components.Forest.Tree.Node (NodeAction(..), SettingsBox(..), glyphiconNodeAction, settingsBox)
+import Gargantext.Components.Forest.Tree.Node.Action (Action(..), DroppedFile(..), FileType(..), ID, Name, UploadFileContents(..))
+import Gargantext.Components.Forest.Tree.Node.Action.Add (NodePopup(..), createNodeView)
+import Gargantext.Components.Forest.Tree.Node.Action.Rename (renameBox)
+import Gargantext.Components.Forest.Tree.Node.Action.Upload (fileTypeView)
+import Gargantext.Components.Search.Types (allLangs)
+import Gargantext.Components.Search.SearchBar (searchBar)
 import Gargantext.Components.Search.SearchField (Search, defaultSearch, isIsTex)
 
 import Gargantext.Ends (Frontends, url)
-import Gargantext.Routes (AppRoute, SessionRoute(..))
+import Gargantext.Routes (AppRoute)
 import Gargantext.Routes as Routes
-import Gargantext.Sessions (Session, sessionId, get, put, post, postWwwUrlencoded, delete)
-import Gargantext.Types (class ToQuery, toQuery, NodeType(..), NodePath(..), readNodeType, fldr)
-import Gargantext.Utils (id, glyphicon, glyphiconActive)
+import Gargantext.Sessions (Session, sessionId)
+import Gargantext.Types (NodeType(..), NodePath(..), fldr)
+import Gargantext.Utils (glyphicon, glyphiconActive)
 import Gargantext.Utils.Reactix as R2
 import Partial.Unsafe (unsafePartial)
-import Prelude hiding (div)
+import Prelude (Unit, bind, const, discard, identity, map, pure, show, unit, void, ($), (<>), (==))
 import React.SyntheticEvent as E
 import Reactix as R
 import Reactix.DOM.HTML as H
@@ -173,6 +172,7 @@ type NodePopupProps =
   , session  :: Session
   )
 
+iconAStyle :: { color :: String, paddingTop :: String, paddingBottom :: String}
 iconAStyle = { color         : "black"
              , paddingTop    : "6px"
              , paddingBottom : "6px"
@@ -200,7 +200,7 @@ nodePopupView d p mPop@(Just NodePopup /\ setPopupOpen) = R.createElement el p [
                 ]
               ]
             , panelHeading renameBoxOpen
-            , panelBody nodePopupState d
+            , panelBody    nodePopupState d
             , panelAction d {id, name, nodeType, action:nodePopup.action, session, search} mPop
             ]
           , if nodePopup.action == Just SearchBox then
@@ -258,11 +258,11 @@ nodePopupView d p mPop@(Just NodePopup /\ setPopupOpen) = R.createElement el p [
               ]
             editIcon (true /\ _) = H.div {} []
 
-        panelBody nodePopupState d =
+        panelBody nodePopupState d' =
           H.div {className: "panel-body flex-center"}
-          $ map (buttonClick nodePopupState d) buttons
+          $ map (buttonClick nodePopupState d') buttons
 
-        searchIsTexIframe id session search@(search' /\ _) =
+        searchIsTexIframe _id _session search@(search' /\ _) =
           if isIsTex search'.datafield then
             H.div { className: "istex-search panel panel-default" }
             [
@@ -290,8 +290,14 @@ nodePopupView _ p _ = R.createElement el p []
     cpt _ _ = pure $ H.div {} []
 
 
-
--- buttonAction :: NodeAction -> R.Element
+buttonClick :: R.State { id        :: ID
+                        , name     :: Name
+                        , nodeType :: NodeType
+                        , action   :: Maybe NodeAction
+                        }
+            -> (Action -> Aff Unit)
+            -> NodeAction
+            -> R.Element
 buttonClick (node@{action} /\ setNodePopup) _ todo = H.div {className: "col-md-1"}
             [ H.a { style: iconAStyle
                   , className: glyphiconActive (glyphiconNodeAction todo)
@@ -309,8 +315,6 @@ buttonClick (node@{action} /\ setNodePopup) _ todo = H.div {className: "col-md-1
                              then Nothing
                              else (Just todo)
 
-buttonClick _ _ _ = H.div {} []
-
 
 -- END Popup View
 
@@ -367,7 +371,7 @@ infoTitle nt = H.div {} [ H.h3 {} [H.text "Documentation about " ]
                         , H.h3 {className: fldr nt true} [ H.text $ show nt ]
                         ]
 
-
+reallyDelete :: (Action -> Aff Unit) -> R.Element
 reallyDelete d = H.div {className: "panel-footer"}
             [ H.a { type: "button"
                   , className: "btn glyphicon glyphicon-trash"
@@ -377,6 +381,3 @@ reallyDelete d = H.div {className: "panel-footer"}
               [H.text " Yes, delete!"]
             ]
 
-
-
-
diff --git a/src/Gargantext/Components/GraphExplorer.purs b/src/Gargantext/Components/GraphExplorer.purs
index 2ff18668e2981e97a95452bbbc722b11917315b5..31e0289c165f2cd94a48dc07ef588ee7f0a3dd19 100644
--- a/src/Gargantext/Components/GraphExplorer.purs
+++ b/src/Gargantext/Components/GraphExplorer.purs
@@ -5,7 +5,6 @@ import Gargantext.Prelude hiding (max,min)
 import Data.FoldableWithIndex (foldMapWithIndex)
 import Data.Foldable (foldMap)
 import Data.Int (toNumber)
-import Data.Map as Map
 import Data.Maybe (Maybe(..))
 import Data.Nullable (null, Nullable)
 import Data.Sequence as Seq
diff --git a/src/Gargantext/Components/Login.purs b/src/Gargantext/Components/Login.purs
index 1e10ad4b254e334958f60642312d3fa3b78a2d96..fde8a48f8f2a07f498141b9c9f2968b757097da1 100644
--- a/src/Gargantext/Components/Login.purs
+++ b/src/Gargantext/Components/Login.purs
@@ -96,14 +96,14 @@ chooserCpt :: R.Component ChooserProps
 chooserCpt = R.staticComponent "G.C.Login.chooser" cpt where
   cpt :: Record ChooserProps -> Array R.Element -> R.Element
   cpt {backend, backends, sessions} _ =
-    R.fragment $ new <> active
+    R.fragment $ active <> new <> search
       where
         active = if DS.length ss > 0 then [ H.h3 {} [H.text "Active connection(s)"]
                  , H.ul {} [ renderSessions sessions]
                  ] else [] where
                    Sessions {sessions:ss} = fst sessions
-        new    = [ H.input {className: "form-control", type:"text", placeholder: "Search for your institute"}
-                 , H.h3 {} [H.text "Last connection(s)"]
+        search = [ H.input {className: "form-control", type:"text", placeholder: "Search for your institute"}]
+        new    = [ H.h3 {} [H.text "Last connection(s)"]
                  , H.table {className : "table"}
                  [ H.thead {className: "thead-dark"} [ H.tr {} [ H.th {} [H.text "Label of instance"]
                                                                          , H.th {} [H.text "Gargurl"]
@@ -118,7 +118,7 @@ renderSessions :: R2.Reductor Sessions Sessions.Action -> R.Element
 renderSessions sessions = R.fragment (renderSession sessions <$> unSessions (fst sessions))
   where
     renderSession :: R2.Reductor Sessions Sessions.Action -> Session -> R.Element
-    renderSession sessions' session = H.li {} $ [ H.text $ "Active session: " <> show session ]
+    renderSession sessions' session = H.li {} $ [ H.text $ show session ]
                                             <> [ H.a { on : {click}
                                                      , className: "glyphitem glyphicon glyphicon-log-out"
                                                      , id : "log-out"
diff --git a/src/Gargantext/Components/Search/SearchBar.purs b/src/Gargantext/Components/Search/SearchBar.purs
index e3be4c3c18f4ee49ac6adc0a2bceef8dcd4f0beb..04a0f6291c14634c38346e50e8f0937ff99d333f 100644
--- a/src/Gargantext/Components/Search/SearchBar.purs
+++ b/src/Gargantext/Components/Search/SearchBar.purs
@@ -5,10 +5,7 @@ module Gargantext.Components.Search.SearchBar
 import Prelude (Unit, bind, discard, not, pure, show, ($), (<>), map)
 import Data.Maybe (Maybe(..))
 import Data.Array (nub, concat)
-import Data.Set as Set
 import Data.Newtype (over)
-import Data.Traversable (traverse_)
-import Data.Tuple (snd)
 import Data.Tuple.Nested ((/\))
 import Effect (Effect)
 import Effect.Class (liftEffect)
@@ -18,7 +15,7 @@ import Effect.Aff (Aff, launchAff_)
 import Reactix.DOM.HTML as H
 import Gargantext.Components.Search.Types -- (Database, SearchQuery(..), defaultSearchQuery, performSearch, Lang(..))
 import Gargantext.Components.Modals.Modal (modalShow)
-import Gargantext.Components.Search.SearchField (Search, defaultSearch, searchField)
+import Gargantext.Components.Search.SearchField (Search, searchField)
 import Gargantext.Sessions (Session)
 
 type Props = ( session   :: Session
diff --git a/src/Gargantext/Components/Search/SearchField.purs b/src/Gargantext/Components/Search/SearchField.purs
index c70799027d78a476261a7a8e84f7ddc85ae1ebc4..35406f9c2cd71782c8e9a70cf99c6685bc96ae23 100644
--- a/src/Gargantext/Components/Search/SearchField.purs
+++ b/src/Gargantext/Components/Search/SearchField.purs
@@ -67,35 +67,30 @@ searchFieldComponent = R.memo (R.hooksComponent "SearchField" cpt) eqProps
                   then
                     div {}[]
                   else
-                    div {} [ langNav search props.langs
-                           , if s.lang == Nothing
-                               then
-                                 div {} []
-                               else
-                                 div {} [ dataFieldNav search dataFields
-                                              , if isExternal s.datafield
-                                                then databaseInput search props.databases
-                                                else div {} []
-                                              , if isHAL s.datafield
-                                                then orgInput search allOrgs
-                                                else div {} []
-
-                                              , if isIMT s.datafield
-                                                then
-                                                  componentIMT search
-                                                else div {} []
-
-                                              , if isCNRS s.datafield
-                                                then
-                                                  componentCNRS search
-                                                else
-                                                  div {} []
-                                          ]
+                    div {} [ dataFieldNav search dataFields
+                            , if isExternal s.datafield
+                              then databaseInput search props.databases
+                              else div {} []
+
+                            , if isHAL s.datafield
+                              then orgInput search allOrgs
+                              else div {} []
+
+                            , if isIMT s.datafield
+                              then componentIMT search
+                              else div {} []
+
+                            , if isCNRS s.datafield
+                              then componentCNRS search
+                              else div {} []
                             ]
+                ]
               ]
-              ]
-
-          , submitButton search
+          , div { className : "panel-footer" }
+                [ if needsLang s.datafield then langNav search props.langs else div {} []
+                , div {} []
+                , div {className: "flex-center"} [submitButton search]
+                ]
           ]
     eqProps p p' =    (fst p.search == fst p'.search)
                    && (p.databases  == p'.databases )
@@ -147,7 +142,11 @@ isCNRS :: Maybe DataField -> Boolean
 isCNRS (Just ( External ( Just ( HAL ( Just ( CNRS _)))))) = true
 isCNRS _ = false
 
-
+needsLang :: Maybe DataField -> Boolean
+needsLang (Just Gargantext) = true
+needsLang (Just Web)        = true
+needsLang (Just ( External ( Just (HAL _)))) = true
+needsLang _ = false
 
 
 isIn :: IMT_org -> Maybe DataField -> Boolean
@@ -175,22 +174,21 @@ updateFilter org _ = (Just (External (Just (HAL (Just (IMT imtOrgs'))))))
                   else Set.fromFoldable [org]
 
 ------------------------------------------------------------------------
-langList :: R.State (Maybe Lang) -> Array Lang -> R.Element
+langList :: R.State Search -> Array Lang -> R.Element
 langList (lang /\ setLang) langs =
               div { className: "form-group" }
                    [ div {className: "text-primary center"} [text "with lang"]
                    , R2.select { className: "form-control"
-                               , on: { change: \e -> setLang
-                                                   $ const
-                                                   $ readLang
-                                                   $ e .. "target" .. "value"
-                                     }
+                               , on: { change: \e -> setLang $ _ {lang = lang' e}}
                                } (liItem <$> langs)
                    ]
     where
       liItem :: Lang -> R.Element
       liItem  lang = option {className : "text-primary center"} [ text (show lang) ]
 
+      lang' e = readLang $ e .. "target" .. "value"
+
+
 langNav :: R.State Search -> Array Lang -> R.Element
 langNav ({lang} /\ setSearch) langs =
   R.fragment [ div {className: "text-primary center"} [text "with lang"]
@@ -318,12 +316,11 @@ searchInput ({term} /\ setSearch) =
 submitButton :: R.State Search
              -> R.Element
 submitButton (search /\ setSearch) =
-  div { className : "panel-footer" }
-  [ button { className: "btn btn-primary"
-           , type: "button"
-           , on: {click: doSearch}
-           } [ text "Launch Search" ]
-  ]
+  button { className: "btn btn-primary"
+         , type: "button"
+         , on: {click: doSearch}
+         , style: { width: "100%" } 
+         } [ text "Launch Search" ]
   where
     doSearch = \_ -> do
       case search.term of
diff --git a/src/Gargantext/Components/Search/Types.purs b/src/Gargantext/Components/Search/Types.purs
index 081e3c0907158231fce7727b8bbf47d1c54247fc..2fcd26a5a7a33d21ce21c411b861fe116eac18a5 100644
--- a/src/Gargantext/Components/Search/Types.purs
+++ b/src/Gargantext/Components/Search/Types.purs
@@ -40,16 +40,16 @@ data Lang = FR | EN | Universal | No_extraction
 instance showLang :: Show Lang where
   show FR = "FR"
   show EN = "EN"
-  show Universal = "Universal"
-  show No_extraction = "No_extraction"
+  show Universal = "All"
+  show No_extraction = "Nothing"
 
 derive instance eqLang :: Eq Lang
 
 readLang :: String -> Maybe Lang
 readLang "FR"  = Just FR
 readLang "EN"  = Just EN
-readLang "Universal" = Just Universal
-readLang "No_extraction" = Just No_extraction
+readLang "All" = Just Universal
+readLang "Nothing" = Just No_extraction
 readLang _           = Nothing
 
 instance encodeJsonLang :: EncodeJson Lang where