Skip to content

Commit

Permalink
Use terminal-size instead of getTerminalWidth
Browse files Browse the repository at this point in the history
  • Loading branch information
NeonGraal committed May 1, 2019
1 parent dfbf85a commit 9b34190
Show file tree
Hide file tree
Showing 4 changed files with 6 additions and 42 deletions.
1 change: 1 addition & 0 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,7 @@ dependencies:
- tar
- template-haskell
- temporary
- terminal-size
- text
- text-metrics
- th-reify-many
Expand Down
4 changes: 2 additions & 2 deletions src/Stack/Runners.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ import Stack.Types.Docker (dockerEnable)
import Stack.Types.Nix (nixEnable)
import Stack.Types.Version (stackMinorVersion, stackVersion, minorVersion)
import System.Console.ANSI (hSupportsANSIWithoutEmulation)
import System.Terminal (getTerminalWidth)
import System.Console.Terminal.Size (size, width)

-- | Ensure that no project settings are used when running 'withConfig'.
withGlobalProject :: RIO Runner a -> RIO Runner a
Expand Down Expand Up @@ -154,7 +154,7 @@ withRunnerGlobal go inner = do
ColorAuto -> fromMaybe True <$>
hSupportsANSIWithoutEmulation stderr
termWidth <- clipWidth <$> maybe (fromMaybe defaultTerminalWidth
<$> getTerminalWidth)
<$> fmap (fmap width) size)
pure (globalTermWidth go)
menv <- mkDefaultProcessContext
logOptions0 <- logOptionsHandle stderr False
Expand Down
34 changes: 1 addition & 33 deletions src/unix/System/Terminal.hsc
Original file line number Diff line number Diff line change
@@ -1,42 +1,10 @@
{-# LANGUAGE ForeignFunctionInterface #-}

module System.Terminal
( getTerminalWidth
, fixCodePage
( fixCodePage
, hIsTerminalDeviceOrMinTTY
) where

import Foreign
import Foreign.C.Types
import RIO (MonadIO, Handle, hIsTerminalDevice)

#include <sys/ioctl.h>
#include <unistd.h>

newtype WindowWidth = WindowWidth CUShort
deriving (Eq, Ord, Show)

instance Storable WindowWidth where
sizeOf _ = (#size struct winsize)
alignment _ = (#alignment struct winsize)
peek p = WindowWidth <$> (#peek struct winsize, ws_col) p
poke p (WindowWidth w) = do
(#poke struct winsize, ws_col) p w

foreign import ccall "sys/ioctl.h ioctl"
ioctl :: CInt -> CInt -> Ptr WindowWidth -> IO CInt

-- | Get the width, in columns, of the terminal if we can.
getTerminalWidth :: IO (Maybe Int)
getTerminalWidth =
alloca $ \p -> do
errno <- ioctl (#const STDOUT_FILENO) (#const TIOCGWINSZ) p
if errno < 0
then return Nothing
else do
WindowWidth w <- peek p
return . Just . fromIntegral $ w

fixCodePage :: x -> y -> a -> a
fixCodePage _ _ = id

Expand Down
9 changes: 2 additions & 7 deletions src/windows/System/Terminal.hs
Original file line number Diff line number Diff line change
@@ -1,20 +1,15 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module System.Terminal
( getTerminalWidth
, fixCodePage
,hIsTerminalDeviceOrMinTTY
( fixCodePage
, hIsTerminalDeviceOrMinTTY
) where

import Distribution.Types.Version (mkVersion)
import Stack.Prelude
import System.Win32 (isMinTTYHandle, withHandleToHANDLE)
import System.Win32.Console (setConsoleCP, setConsoleOutputCP, getConsoleCP, getConsoleOutputCP)

-- | Get the width, in columns, of the terminal if we can.
getTerminalWidth :: IO (Maybe Int)
getTerminalWidth = return Nothing

-- | Set the code page for this process as necessary. Only applies to Windows.
-- See: https://github.com/commercialhaskell/stack/issues/738
fixCodePage
Expand Down

0 comments on commit 9b34190

Please sign in to comment.