|
| 1 | +{-# LANGUAGE ScopedTypeVariables #-} |
| 2 | + |
| 3 | +#if __GLASGOW_HASKELL__ >= 709 |
| 4 | +{-# LANGUAGE Safe #-} |
| 5 | +#elif __GLASGOW_HASKELL__ >= 701 |
| 6 | +{-# LANGUAGE Trustworthy #-} |
| 7 | +#endif |
| 8 | +----------------------------------------------------------------------------- |
| 9 | +-- | |
| 10 | +-- Module : System.Win32.MinTTY |
| 11 | +-- Copyright : (c) University of Glasgow 2006 |
| 12 | +-- License : BSD-style (see the file LICENSE) |
| 13 | +-- |
| 14 | +-- Maintainer : Esa Ilari Vuokko <[email protected]> |
| 15 | +-- Stability : provisional |
| 16 | +-- Portability : portable |
| 17 | +-- |
| 18 | +-- A function to check if the current terminal uses MinTTY. |
| 19 | +-- Much of this code was originally authored by Phil Ruffwind and the |
| 20 | +-- git-for-windows project. |
| 21 | +-- |
| 22 | +----------------------------------------------------------------------------- |
| 23 | + |
| 24 | +module System.Win32.MinTTY (isMinTTY, isMinTTYHandle) where |
| 25 | + |
| 26 | +import Graphics.Win32.Misc |
| 27 | +import System.Win32.DLL |
| 28 | +import System.Win32.File |
| 29 | +import System.Win32.Types |
| 30 | + |
| 31 | +#if MIN_VERSION_base(4,6,0) |
| 32 | +import Control.Exception (catch) |
| 33 | +#endif |
| 34 | +import Data.List (isPrefixOf, isInfixOf, isSuffixOf) |
| 35 | +import Foreign |
| 36 | +import Foreign.C.Types |
| 37 | +import System.FilePath (takeFileName) |
| 38 | + |
| 39 | +#if __GLASGOW_HASKELL__ < 711 |
| 40 | +#let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t (y__); }, y__) |
| 41 | +#endif |
| 42 | + |
| 43 | +-- The headers that are shipped with GHC's copy of MinGW-w64 assume Windows XP. |
| 44 | +-- Since we need some structs that are only available with Vista or later, |
| 45 | +-- we must manually set WINVER/_WIN32_WINNT accordingly. |
| 46 | +#undef WINVER |
| 47 | +#define WINVER 0x0600 |
| 48 | +#undef _WIN32_WINNT |
| 49 | +#define _WIN32_WINNT 0x0600 |
| 50 | +##include "windows_cconv.h" |
| 51 | +#include <windows.h> |
| 52 | +#include "winternl_compat.h" |
| 53 | + |
| 54 | +-- | Returns 'True' if the current process's standard error is attached to a |
| 55 | +-- MinTTY console (e.g., Cygwin or MSYS). Returns 'False' otherwise. |
| 56 | +isMinTTY :: IO Bool |
| 57 | +isMinTTY = do |
| 58 | + h <- getStdHandle sTD_ERROR_HANDLE |
| 59 | + `catch` \(_ :: IOError) -> |
| 60 | + return nullHANDLE |
| 61 | + if h == nullHANDLE |
| 62 | + then return False |
| 63 | + else isMinTTYHandle h |
| 64 | + |
| 65 | +-- | Returns 'True' is the given handle is attached to a MinTTY console |
| 66 | +-- (e.g., Cygwin or MSYS). Returns 'False' otherwise. |
| 67 | +isMinTTYHandle :: HANDLE -> IO Bool |
| 68 | +isMinTTYHandle h = do |
| 69 | + fileType <- getFileType h |
| 70 | + if fileType /= fILE_TYPE_PIPE |
| 71 | + then return False |
| 72 | + else isMinTTYVista h `catch` \(_ :: IOError) -> isMinTTYCompat h |
| 73 | + -- GetFileNameByHandleEx is only available on Vista and later (hence |
| 74 | + -- the name isMinTTYVista). If we're on an older version of Windows, |
| 75 | + -- getProcAddress will throw an IOException when it fails to find |
| 76 | + -- GetFileNameByHandleEx, and thus we will default to using |
| 77 | + -- NtQueryObject (isMinTTYCompat). |
| 78 | + |
| 79 | +isMinTTYVista :: HANDLE -> IO Bool |
| 80 | +isMinTTYVista h = do |
| 81 | + fn <- getFileNameByHandle h |
| 82 | + return $ cygwinMSYSCheck fn |
| 83 | + `catch` \(_ :: IOError) -> |
| 84 | + return False |
| 85 | + |
| 86 | +isMinTTYCompat :: HANDLE -> IO Bool |
| 87 | +isMinTTYCompat h = do |
| 88 | + fn <- ntQueryObjectNameInformation h |
| 89 | + return $ cygwinMSYSCheck fn |
| 90 | + `catch` \(_ :: IOError) -> |
| 91 | + return False |
| 92 | + |
| 93 | +cygwinMSYSCheck :: String -> Bool |
| 94 | +cygwinMSYSCheck fn = ("cygwin-" `isPrefixOf` fn' || "msys-" `isPrefixOf` fn') && |
| 95 | + "-pty" `isInfixOf` fn' && |
| 96 | + "-master" `isSuffixOf` fn' |
| 97 | + where |
| 98 | + fn' = takeFileName fn |
| 99 | +-- Note that GetFileInformationByHandleEx might return a filepath like: |
| 100 | +-- |
| 101 | +-- \msys-dd50a72ab4668b33-pty1-to-master |
| 102 | +-- |
| 103 | +-- But NtQueryObject might return something like: |
| 104 | +-- |
| 105 | +-- \Device\NamedPipe\msys-dd50a72ab4668b33-pty1-to-master |
| 106 | +-- |
| 107 | +-- This means we can't rely on "\cygwin-" or "\msys-" being at the very start |
| 108 | +-- of the filepath. Therefore, we must take care to first call takeFileName |
| 109 | +-- before checking for "cygwin" or "msys" at the start using `isPrefixOf`. |
| 110 | + |
| 111 | +getFileNameByHandle :: HANDLE -> IO String |
| 112 | +getFileNameByHandle h = do |
| 113 | + let sizeOfDWORD = sizeOf (undefined :: DWORD) |
| 114 | + -- note: implicitly assuming that DWORD has stronger alignment than wchar_t |
| 115 | + bufSize = sizeOfDWORD + mAX_PATH * sizeOfTCHAR |
| 116 | + allocaBytes bufSize $ \buf -> do |
| 117 | + getFileInformationByHandleEx h fileNameInfo buf (fromIntegral bufSize) |
| 118 | + fni <- peek buf |
| 119 | + return $ fniFileName fni |
| 120 | + |
| 121 | +getFileInformationByHandleEx |
| 122 | + :: HANDLE -> CInt -> Ptr FILE_NAME_INFO -> DWORD -> IO () |
| 123 | +getFileInformationByHandleEx h cls buf bufSize = do |
| 124 | + lib <- getModuleHandle (Just "kernel32.dll") |
| 125 | + ptr <- getProcAddress lib "GetFileInformationByHandleEx" |
| 126 | + let c_GetFileInformationByHandleEx = |
| 127 | + mk_GetFileInformationByHandleEx (castPtrToFunPtr ptr) |
| 128 | + failIfFalse_ "getFileInformationByHandleEx" |
| 129 | + (c_GetFileInformationByHandleEx h cls buf bufSize) |
| 130 | + |
| 131 | +ntQueryObjectNameInformation :: HANDLE -> IO String |
| 132 | +ntQueryObjectNameInformation h = do |
| 133 | + let sizeOfONI = sizeOf (undefined :: OBJECT_NAME_INFORMATION) |
| 134 | + bufSize = sizeOfONI + mAX_PATH * sizeOfTCHAR |
| 135 | + allocaBytes bufSize $ \buf -> |
| 136 | + alloca $ \p_len -> do |
| 137 | + _ <- failIfNeg "NtQueryObject" $ c_NtQueryObject |
| 138 | + h objectNameInformation buf (fromIntegral bufSize) p_len |
| 139 | + oni <- peek buf |
| 140 | + return $ usBuffer $ oniName oni |
| 141 | + |
| 142 | +fileNameInfo :: CInt |
| 143 | +fileNameInfo = #const FileNameInfo |
| 144 | + |
| 145 | +mAX_PATH :: Num a => a |
| 146 | +mAX_PATH = #const MAX_PATH |
| 147 | + |
| 148 | +objectNameInformation :: CInt |
| 149 | +objectNameInformation = #const ObjectNameInformation |
| 150 | + |
| 151 | +type F_GetFileInformationByHandleEx = |
| 152 | + HANDLE -> CInt -> Ptr FILE_NAME_INFO -> DWORD -> IO BOOL |
| 153 | + |
| 154 | +foreign import WINDOWS_CCONV "dynamic" |
| 155 | + mk_GetFileInformationByHandleEx |
| 156 | + :: FunPtr F_GetFileInformationByHandleEx -> F_GetFileInformationByHandleEx |
| 157 | + |
| 158 | +data FILE_NAME_INFO = FILE_NAME_INFO |
| 159 | + { fniFileNameLength :: DWORD |
| 160 | + , fniFileName :: String |
| 161 | + } deriving Show |
| 162 | + |
| 163 | +instance Storable FILE_NAME_INFO where |
| 164 | + sizeOf _ = #size FILE_NAME_INFO |
| 165 | + alignment _ = #alignment FILE_NAME_INFO |
| 166 | + poke buf fni = withTStringLen (fniFileName fni) $ \(str, len) -> do |
| 167 | + let len' = (min mAX_PATH len) * sizeOfTCHAR |
| 168 | + start = advancePtr (castPtr buf) (#offset FILE_NAME_INFO, FileName) |
| 169 | + end = advancePtr start len' |
| 170 | + (#poke FILE_NAME_INFO, FileNameLength) buf len' |
| 171 | + copyArray start (castPtr str :: Ptr Word8) len' |
| 172 | + poke (castPtr end) (0 :: TCHAR) |
| 173 | + peek buf = do |
| 174 | + vfniFileNameLength <- (#peek FILE_NAME_INFO, FileNameLength) buf |
| 175 | + let len = fromIntegral vfniFileNameLength `div` sizeOfTCHAR |
| 176 | + vfniFileName <- peekTStringLen (plusPtr buf (#offset FILE_NAME_INFO, FileName), len) |
| 177 | + return $ FILE_NAME_INFO |
| 178 | + { fniFileNameLength = vfniFileNameLength |
| 179 | + , fniFileName = vfniFileName |
| 180 | + } |
| 181 | + |
| 182 | +foreign import WINDOWS_CCONV "winternl.h NtQueryObject" |
| 183 | + c_NtQueryObject :: HANDLE -> CInt -> Ptr OBJECT_NAME_INFORMATION |
| 184 | + -> ULONG -> Ptr ULONG -> IO NTSTATUS |
| 185 | + |
| 186 | +type NTSTATUS = #type NTSTATUS |
| 187 | + |
| 188 | +newtype OBJECT_NAME_INFORMATION = OBJECT_NAME_INFORMATION |
| 189 | + { oniName :: UNICODE_STRING |
| 190 | + } deriving Show |
| 191 | + |
| 192 | +instance Storable OBJECT_NAME_INFORMATION where |
| 193 | + sizeOf _ = #size OBJECT_NAME_INFORMATION |
| 194 | + alignment _ = #alignment OBJECT_NAME_INFORMATION |
| 195 | + poke buf oni = (#poke OBJECT_NAME_INFORMATION, Name) buf (oniName oni) |
| 196 | + peek buf = fmap OBJECT_NAME_INFORMATION $ (#peek OBJECT_NAME_INFORMATION, Name) buf |
| 197 | + |
| 198 | +data UNICODE_STRING = UNICODE_STRING |
| 199 | + { usLength :: USHORT |
| 200 | + , usMaximumLength :: USHORT |
| 201 | + , usBuffer :: String |
| 202 | + } deriving Show |
| 203 | + |
| 204 | +instance Storable UNICODE_STRING where |
| 205 | + sizeOf _ = #size UNICODE_STRING |
| 206 | + alignment _ = #alignment UNICODE_STRING |
| 207 | + poke buf us = withTStringLen (usBuffer us) $ \(str, len) -> do |
| 208 | + let len' = (min mAX_PATH len) * sizeOfTCHAR |
| 209 | + start = advancePtr (castPtr buf) (#size UNICODE_STRING) |
| 210 | + end = advancePtr start len' |
| 211 | + (#poke UNICODE_STRING, Length) buf len' |
| 212 | + (#poke UNICODE_STRING, MaximumLength) buf (len' + sizeOfTCHAR) |
| 213 | + (#poke UNICODE_STRING, Buffer) buf start |
| 214 | + copyArray start (castPtr str :: Ptr Word8) len' |
| 215 | + poke (castPtr end) (0 :: TCHAR) |
| 216 | + peek buf = do |
| 217 | + vusLength <- (#peek UNICODE_STRING, Length) buf |
| 218 | + vusMaximumLength <- (#peek UNICODE_STRING, MaximumLength) buf |
| 219 | + vusBufferPtr <- (#peek UNICODE_STRING, Buffer) buf |
| 220 | + let len = fromIntegral vusLength `div` sizeOfTCHAR |
| 221 | + vusBuffer <- peekTStringLen (vusBufferPtr, len) |
| 222 | + return $ UNICODE_STRING |
| 223 | + { usLength = vusLength |
| 224 | + , usMaximumLength = vusMaximumLength |
| 225 | + , usBuffer = vusBuffer |
| 226 | + } |
| 227 | + |
| 228 | +sizeOfTCHAR :: Int |
| 229 | +sizeOfTCHAR = sizeOf (undefined :: TCHAR) |
0 commit comments