diff --git a/cabal.project b/cabal.project
index 99ea20b46da8302bef8c4952e635dd53e0a3653e..019d44d36601d9cff488a2e7475e52d0c5ddc742 100644
--- a/cabal.project
+++ b/cabal.project
@@ -8,6 +8,11 @@ package ghcup
     tests: True
     flags: +tui
 
+source-repository-package
+  type: git
+  location: https://github.com/bgamari/terminal-size.git
+  tag: 34ea816bd63f75f800eedac12c6908c6f3736036
+
 constraints: http-io-streams -brotli,
              any.Cabal ==3.6.2.0,
              any.aeson >= 2.0.1.0
diff --git a/ghcup.cabal b/ghcup.cabal
index 8b3e22cfbf478eb11a0c33cba530393a1092c633..c5d61761bbf0a4766c537f4e02cadb49b4da8f83 100644
--- a/ghcup.cabal
+++ b/ghcup.cabal
@@ -166,11 +166,10 @@ library
       GHCup.Utils.File.Posix
       GHCup.Utils.Posix
       GHCup.Utils.Prelude.Posix
-      System.Console.Terminal.Common
-      System.Console.Terminal.Posix
 
     build-depends:
       , bz2              >=0.5.0.5 && <1.1
+      , terminal-size    ^>=0.3.2.1
       , unix             ^>=2.7
       , unix-bytestring  ^>=0.3.7.3
 
diff --git a/lib/GHCup/Utils.hs b/lib/GHCup/Utils.hs
index 3ee7478112324645d58152e8eb44219e829a0074..a95d6854f919fb44ac02fe532e4798074ec3db4a 100644
--- a/lib/GHCup/Utils.hs
+++ b/lib/GHCup/Utils.hs
@@ -1141,11 +1141,11 @@ ensureDirectories (Dirs baseDir binDir cacheDir logsDir confDir trashDir) = do
 
 -- | For ghc without arch triple, this is:
 --
---    - ghc-<ver> (e.g. ghc-8.10.4)
+--    - ghc
 --
 -- For ghc with arch triple:
 --
---    - <triple>-ghc-<ver> (e.g. arm-linux-gnueabihf-ghc-8.10.4)
+--    - <triple>-ghc (e.g. arm-linux-gnueabihf-ghc)
 ghcBinaryName :: GHCTargetVersion -> String
-ghcBinaryName (GHCTargetVersion (Just t) v') = T.unpack (t <> "-ghc-" <> prettyVer v' <> T.pack exeExt)
-ghcBinaryName (GHCTargetVersion Nothing  v') = T.unpack ("ghc-" <> prettyVer v' <> T.pack exeExt)
+ghcBinaryName (GHCTargetVersion (Just t) _) = T.unpack (t <> "-ghc" <> T.pack exeExt)
+ghcBinaryName (GHCTargetVersion Nothing  _) = T.unpack ("ghc" <> T.pack exeExt)
diff --git a/lib/GHCup/Utils/File/Posix.hs b/lib/GHCup/Utils/File/Posix.hs
index b13aec958366d8665336f30c8992078c04f4f35b..57e03c1cd6b14c1d26f849a740020f8748e816b5 100644
--- a/lib/GHCup/Utils/File/Posix.hs
+++ b/lib/GHCup/Utils/File/Posix.hs
@@ -35,7 +35,6 @@ import           Data.Sequence                  ( Seq, (|>) )
 import           Data.List
 import           Data.Word8
 import           GHC.IO.Exception
-import           System.Console.Terminal.Common
 import           System.IO.Error
 import           System.FilePath
 import           System.Directory
@@ -51,7 +50,7 @@ import qualified Data.Sequence                 as Sq
 import qualified Data.Text                     as T
 import qualified Data.Text.Encoding            as E
 import qualified System.Posix.Process          as SPP
-import qualified System.Console.Terminal.Posix as TP
+import qualified System.Console.Terminal.Size  as TP
 import qualified Data.ByteString               as BS
 import qualified Data.ByteString.Lazy          as BL
 import qualified "unix-bytestring" System.Posix.IO.ByteString
@@ -182,7 +181,7 @@ execLogged exe args chdir lfile env = do
       modify (swapRegs bs')
       liftIO TP.size >>= \case
         Nothing -> pure ()
-        Just (Window _ w) -> do
+        Just (TP.Window _ w) -> do
           regs <- get
           liftIO $ forM_ (Sq.zip regs (Sq.fromList [0..(Sq.length regs - 1)])) $ \(bs, i) -> do
               BS.putStr
diff --git a/lib/System/Console/Terminal/Common.hs b/lib/System/Console/Terminal/Common.hs
deleted file mode 100644
index 768e0e0eb35a0968eeb6c1a77630d5b36228f07f..0000000000000000000000000000000000000000
--- a/lib/System/Console/Terminal/Common.hs
+++ /dev/null
@@ -1,43 +0,0 @@
-{-# LANGUAGE CPP #-}
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE DeriveTraversable #-}
-
-#if __GLASGOW_HASKELL__ >= 702
-#define LANGUAGE_DeriveGeneric
-{-# LANGUAGE DeriveGeneric #-}
-#endif
-
-module System.Console.Terminal.Common
-  ( Window(..)
-  ) where
-
-import Data.Data (Typeable, Data)
-
-#if __GLASGOW_HASKELL__ < 710
-import Data.Foldable (Foldable)
-import Data.Traversable (Traversable)
-#endif
-
-#ifdef LANGUAGE_DeriveGeneric
-import GHC.Generics
-  ( Generic
-#if __GLASGOW_HASKELL__ >= 706
-  , Generic1
-#endif
-  )
-#endif
-
--- | Terminal window width and height
-data Window a = Window
-  { height :: !a
-  , width  :: !a
-  } deriving
-    ( Show, Eq, Read, Data, Typeable
-    , Foldable, Functor, Traversable
-#ifdef LANGUAGE_DeriveGeneric
-    , Generic
-#if __GLASGOW_HASKELL__ >= 706
-    , Generic1
-#endif
-#endif
-    )
diff --git a/lib/System/Console/Terminal/Posix.hsc b/lib/System/Console/Terminal/Posix.hsc
deleted file mode 100644
index 9b2df59fd33d4fc7a95dd1b904d46c3a669c4c07..0000000000000000000000000000000000000000
--- a/lib/System/Console/Terminal/Posix.hsc
+++ /dev/null
@@ -1,65 +0,0 @@
-{-# LANGUAGE CApiFFI #-}
-
-module System.Console.Terminal.Posix
-  ( size, fdSize, hSize
-  ) where
-
-import System.Console.Terminal.Common
-import Control.Exception (catch)
-import Data.Typeable (cast)
-import Foreign
-import Foreign.C.Error
-import Foreign.C.Types
-import GHC.IO.FD (FD(FD, fdFD))
-import GHC.IO.Handle.Internals (withHandle_)
-import GHC.IO.Handle.Types (Handle, Handle__(Handle__, haDevice))
-#if defined(__GLASGOW_HASKELL__) && (__GLASGOW_HASKELL__ < 706)
-import Prelude hiding (catch)
-#endif
-import System.Posix.Types (Fd(Fd))
-
-#include <sys/ioctl.h>
-#include <unistd.h>
-
-
-#let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t (y__); }, y__)
-
-
--- Interesting part of @struct winsize@
-data CWin = CWin CUShort CUShort
-
-instance Storable CWin where
-  sizeOf _ = (#size struct winsize)
-  alignment _ = (#alignment struct winsize)
-  peek ptr = do
-    row <- (#peek struct winsize, ws_row) ptr
-    col <- (#peek struct winsize, ws_col) ptr
-    return $ CWin row col
-  poke ptr (CWin row col) = do
-    (#poke struct winsize, ws_row) ptr row
-    (#poke struct winsize, ws_col) ptr col
-
-
-fdSize :: Integral n => Fd -> IO (Maybe (Window n))
-fdSize (Fd fd) = with (CWin 0 0) $ \ws -> do
-  _ <- throwErrnoIfMinus1 "ioctl" $
-    ioctl fd (#const TIOCGWINSZ) ws
-  CWin row col <- peek ws
-  return . Just $ Window (fromIntegral row) (fromIntegral col)
- `catch`
-  handler
- where
-  handler :: IOError -> IO (Maybe (Window h))
-  handler _ = return Nothing
-
-foreign import capi "sys/ioctl.h ioctl"
-  ioctl :: CInt -> CULong -> Ptr CWin -> IO CInt
-
-size :: Integral n => IO (Maybe (Window n))
-size = fdSize (Fd (#const STDOUT_FILENO))
-
-hSize :: Integral n => Handle -> IO (Maybe (Window n))
-hSize h = withHandle_ "hSize" h $ \Handle__ { haDevice = dev } ->
-  case cast dev of
-    Nothing -> return Nothing
-    Just FD { fdFD = fd } -> fdSize (Fd fd)