module System.Miniplex.Sekrit ( pathFromTag , reallySend , reallyRecv , bytesFromInt , intFromBytes , closeOnExec ) where import Foreign.C.Error import Network.Socket import Data.Bits import System.Directory import System.Posix.IO import System.Posix.Types good :: String -> Bool good s = not (null s) && head s /= '.' && all (`elem` chs) s where chs = ['a' .. 'z'] ++ ['A' .. 'Z'] ++ ['0' .. '9'] ++ ",$=-#%.+_^&'@~()[]{}" pathFromTag :: String -> String -> IO String pathFromTag context what | not $ good what = ioError $ errnoToIOError context eADDRNOTAVAIL Nothing (Just what) | otherwise = do dir <- getAppUserDataDirectory "miniplex" createDirectoryIfMissing False dir return $ dir ++ "/" ++ what reallySend :: Socket -> String -> IO () reallySend sock str = step (length str) str where step n msg | n <= 0 = return () | otherwise = do w <- send sock msg step (n - w) (drop w msg) reallyRecv :: Socket -> Int -> IO String reallyRecv sock = step where step n | n <= 0 = return "" | otherwise = do (s, r) <- recvLen sock n t <- step (n - r) return (s ++ t) bytesFromInt :: Int -> String bytesFromInt n = map (toEnum . (.&.) 255 . shiftR n . (*) 8) . reverse $ [0 .. 3] intFromBytes :: String -> Int intFromBytes = sum . zipWith (\n c -> fromEnum c `shiftL` (8 * n)) (reverse [0 .. 3]) closeOnExec :: Socket -> IO () closeOnExec (MkSocket fd _ _ _ _) = setFdOption (Fd fd) CloseOnExec True {- killSocket :: Socket -> IO () killSocket s = do bracket (openFd "/dev/null" WriteOnly Nothing defaultFileFlags) closeFd (`dupTo` Fd (fdSocket s)) return () -}