diff --git a/app/ghcup/GHCup/OptParse.hs b/app/ghcup/GHCup/OptParse.hs
index ebe48edd8c56baa3c2f0c4766011f45c7af94d2d..3dad2bca22e7f4e8bf3163126153a0ee2f5ce980 100644
--- a/app/ghcup/GHCup/OptParse.hs
+++ b/app/ghcup/GHCup/OptParse.hs
@@ -113,8 +113,8 @@ data Command
 opts :: Parser Options
 opts =
   Options
-    <$> invertableSwitch "verbose" 'v' False (help "Enable verbosity (default: disabled)")
-    <*> invertableSwitch "cache" 'c' False (help "Cache downloads in ~/.ghcup/cache (default: disabled)")
+    <$> invertableSwitch "verbose" (Just 'v') False (help "Enable verbosity (default: disabled)")
+    <*> invertableSwitch "cache" (Just 'c') False (help "Cache downloads in ~/.ghcup/cache (default: disabled)")
     <*> optional (option auto (long "metadata-caching" <> help "How long the yaml metadata caching interval is (in seconds), 0 to disable" <> internal))
     <*> optional
           (option
@@ -127,7 +127,7 @@ opts =
             <> completer fileUri
             )
           )
-    <*> (fmap . fmap) not (invertableSwitch "verify" 'n' True (help "Disable tarball checksum verification (default: enabled)"))
+    <*> (fmap . fmap) not (invertableSwitch "verify" (Just 'n') True (help "Disable tarball checksum verification (default: enabled)"))
     <*> optional (option
           (eitherReader keepOnParser)
           (  long "keep"
@@ -153,7 +153,7 @@ opts =
 #endif
           <> hidden
           ))
-    <*> invertableSwitch "offline" 'o' False (help "Don't do any network calls, trying cached assets and failing if missing.")
+    <*> invertableSwitch "offline" (Just 'o') False (help "Don't do any network calls, trying cached assets and failing if missing.")
     <*> optional (option
           (eitherReader gpgParser)
           (  long "gpg"
diff --git a/app/ghcup/GHCup/OptParse/Common.hs b/app/ghcup/GHCup/OptParse/Common.hs
index cbe4cbc0391c3e040e78f80233ed476b2b3be75e..35867c77b34080ad712777214dc8377042725ac8 100644
--- a/app/ghcup/GHCup/OptParse/Common.hs
+++ b/app/ghcup/GHCup/OptParse/Common.hs
@@ -138,7 +138,7 @@ versionArgument criteria tool = argument (eitherReader tVersionEither) (metavar
 -- the help is shown only for --no-recursive.
 invertableSwitch
     :: String              -- ^ long option
-    -> Char                -- ^ short option for the non-default option
+    -> Maybe Char          -- ^ short option for the non-default option
     -> Bool                -- ^ is switch enabled by default?
     -> Mod FlagFields Bool -- ^ option modifier
     -> Parser (Maybe Bool)
@@ -149,14 +149,14 @@ invertableSwitch longopt shortopt defv optmod = invertableSwitch' longopt shorto
 -- | Allows providing option modifiers for both --foo and --no-foo.
 invertableSwitch'
     :: String              -- ^ long option (eg "foo")
-    -> Char                -- ^ short option for the non-default option
+    -> Maybe Char          -- ^ short option for the non-default option
     -> Bool                -- ^ is switch enabled by default?
     -> Mod FlagFields Bool -- ^ option modifier for --foo
     -> Mod FlagFields Bool -- ^ option modifier for --no-foo
     -> Parser (Maybe Bool)
 invertableSwitch' longopt shortopt defv enmod dismod = optional
-    ( flag' True ( enmod <> long longopt <> if defv then mempty else short shortopt)
-    <|> flag' False (dismod <> long nolongopt <> if defv then short shortopt else mempty)
+    ( flag' True ( enmod <> long longopt <> if defv then mempty else maybe mempty short shortopt)
+    <|> flag' False (dismod <> long nolongopt <> if defv then maybe mempty short shortopt else mempty)
     )
   where
     nolongopt = "no-" ++ longopt
diff --git a/app/ghcup/GHCup/OptParse/Compile.hs b/app/ghcup/GHCup/OptParse/Compile.hs
index 67da67080244cf329d4a51df28fb608a776b21df..23084729d7506165225e0c66c5cb3fdb59c557d9 100644
--- a/app/ghcup/GHCup/OptParse/Compile.hs
+++ b/app/ghcup/GHCup/OptParse/Compile.hs
@@ -234,12 +234,7 @@ ghcCompileOpts =
             )
           )
     <*> many (argument str (metavar "CONFIGURE_ARGS" <> help "Additional arguments to configure, prefix with '-- ' (longopts)"))
-    <*> flag
-          False
-          True
-          (long "set" <> help
-            "Set as active version after install"
-          )
+    <*> fmap (fromMaybe False) (invertableSwitch "set" Nothing False (help "Set as active version after install"))
     <*> optional
           (option
             (eitherReader
@@ -300,12 +295,7 @@ hlsCompileOpts =
               <> (completer $ listCompleter $ fmap show ([1..12] :: [Int]))
             )
           )
-    <*> flag
-          False
-          True
-          (long "set" <> help
-            "Set as active version after install"
-          )
+    <*> fmap (fromMaybe True) (invertableSwitch "set" Nothing True (help "Don't set as active version after install"))
     <*> optional
           (option
             (eitherReader
diff --git a/app/ghcup/GHCup/OptParse/Install.hs b/app/ghcup/GHCup/OptParse/Install.hs
index 3a2aaabda5e2cd6e46301c2bca6a230ea1fea176..d7a010b42fd2aa2eff69275a4afaafc938096526 100644
--- a/app/ghcup/GHCup/OptParse/Install.hs
+++ b/app/ghcup/GHCup/OptParse/Install.hs
@@ -197,12 +197,8 @@ installOpts tool =
             )
         <|> pure (Nothing, Nothing)
         )
-    <*> flag
-          False
-          True
-          (long "set" <> help
-            "Set as active version after install"
-          )
+    <*> fmap (fromMaybe setDefault) (invertableSwitch "set" Nothing setDefault
+      (help $ if not setDefault then "Set as active version after install" else "Don't set as active version after install"))
     <*> optional
           (option
            (eitherReader isolateParser)
@@ -215,6 +211,11 @@ installOpts tool =
           )
     <*> switch
           (short 'f' <> long "force" <> help "Force install")
+ where
+  setDefault = case tool of
+    Nothing  -> False
+    Just GHC -> False
+    Just _   -> True
           
 
 
diff --git a/lib/GHCup.hs b/lib/GHCup.hs
index 49bd93a4b078e035a1d18450282e40fb9904f08e..abf860f7adb261d6ca834ad9f37e1c8efab4bbe0 100644
--- a/lib/GHCup.hs
+++ b/lib/GHCup.hs
@@ -468,10 +468,6 @@ installCabalBindist dlinfo ver isoFilepath forceInstall = do
     Nothing -> do                 -- regular install
       liftE $ installCabalUnpacked workdir binDir (Just ver) forceInstall
 
-      -- create symlink if this is the latest version for regular installs
-      cVers <- lift $ fmap rights getInstalledCabals
-      let lInstCabal = headMay . reverse . sort $ cVers
-      when (maybe True (ver >=) lInstCabal) $ liftE $ setCabal ver
       
 -- | Install an unpacked cabal distribution.Symbol
 installCabalUnpacked :: (MonadCatch m, HasLog env, MonadIO m, MonadReader env m)
@@ -626,7 +622,6 @@ installHLSBindist dlinfo ver isoFilepath forceInstall = do
         liftE $ runBuildAction tmpUnpack Nothing $ installHLSUnpacked workdir inst ver
         liftE $ setHLS ver SetHLS_XYZ Nothing
 
-  liftE $ installHLSPostInst isoFilepath ver
 
 isLegacyHLSBindist :: FilePath -- ^ Path to the unpacked hls bindist
                    -> IO Bool
@@ -696,19 +691,6 @@ installHLSUnpackedLegacy path inst mver' forceInstall = do
   lift $ chmod_755 destWrapperPath
 
 
-installHLSPostInst :: (MonadReader env m, HasDirs env, HasLog env, MonadIO m, MonadCatch m, MonadMask m, MonadFail m, MonadUnliftIO m)
-                   => Maybe FilePath
-                   -> Version
-                   -> Excepts '[NotInstalled] m ()
-installHLSPostInst isoFilepath ver = 
-  case isoFilepath of
-    Just _ -> pure ()
-    Nothing -> do
-      -- create symlink if this is the latest version in a regular install
-      hlsVers <- lift $ fmap rights getInstalledHLSs
-      let lInstHLS = headMay . reverse . sort $ hlsVers
-      when (maybe True (ver >=) lInstHLS) $ liftE $ setHLS ver SetHLSOnly Nothing
-
 
 -- | Installs hls binaries @haskell-language-server-\<ghcver\>@
 -- into @~\/.ghcup\/bin/@, as well as @haskell-languager-server-wrapper@.
@@ -916,8 +898,6 @@ compileHLS targetHLS ghcs jobs ov isolateDir cabalProject cabalProjectLocal patc
           liftE $ installHLSUnpackedLegacy installDir binDir (Just installVer) True
     )
 
-  liftE $ installHLSPostInst isolateDir installVer
-
   pure installVer
 
 
@@ -1034,11 +1014,6 @@ installStackBindist dlinfo ver isoFilepath forceInstall = do
     Nothing -> do                     -- regular install
       liftE $ installStackUnpacked workdir binDir (Just ver) forceInstall
 
-      -- create symlink if this is the latest version and a regular install
-      sVers <- lift $ fmap rights getInstalledStacks
-      let lInstStack = headMay . reverse . sort $ sVers
-      when (maybe True (ver >=) lInstStack) $ liftE $ setStack ver
-
 
 -- | Install an unpacked stack distribution.
 installStackUnpacked :: (MonadReader env m, HasLog env, MonadCatch m, MonadIO m)