{-# LINE 1 "System/Posix/Env/PosixString.hsc" #-}
{-# LANGUAGE CApiFFI #-}
module System.Posix.Env.PosixString (
       
        getEnv
        , getEnvDefault
        , getEnvironmentPrim
        , getEnvironment
        , setEnvironment
        , putEnv
        , setEnv
        , unsetEnv
        , clearEnv
       
       , getArgs
) where
import Control.Monad
import Foreign
import Foreign.C
import Data.Maybe       ( fromMaybe )
import GHC.IO.Encoding.UTF8 ( mkUTF8 )
import GHC.IO.Encoding.Failure ( CodingFailureMode(..) )
import System.Posix.Env ( clearEnv )
import System.OsPath.Posix
import System.OsString.Internal.Types
import qualified System.OsPath.Data.ByteString.Short as B
import Data.ByteString.Short.Internal ( copyToPtr )
import qualified System.Posix.Env.Internal as Internal
getEnv ::
  PosixString             ->
  IO (Maybe PosixString) 
getEnv (PS name) = do
  litstring <- B.useAsCString name c_getenv
  if litstring /= nullPtr
     then (Just . PS) <$> B.packCString litstring
     else return Nothing
getEnvDefault ::
  PosixString     ->
  PosixString     ->
  IO PosixString 
getEnvDefault name fallback = fromMaybe fallback <$> getEnv name
foreign import ccall unsafe "getenv"
   c_getenv :: CString -> IO CString
getEnvironmentPrim :: IO [PosixString]
getEnvironmentPrim = Internal.getEnvironmentPrim >>= mapM (fmap PS . B.packCString)
getEnvironment :: IO [(PosixString,PosixString)] 
getEnvironment = do
  env <- getEnvironmentPrim
  return $ map (dropEq . (B.break ((==) _equal)) . getPosixString) env
 where
   dropEq (x,y)
      | B.head y == _equal = (PS x, PS (B.tail y))
      | otherwise          = error $ "getEnvironment: insane variable " ++ _toStr x
setEnvironment ::
  [(PosixString,PosixString)]  ->
  IO ()
setEnvironment env = do
  clearEnv
  forM_ env $ \(key,value) ->
    setEnv key value True 
unsetEnv :: PosixString  -> IO ()
{-# LINE 104 "System/Posix/Env/PosixString.hsc" #-}
{-# LINE 105 "System/Posix/Env/PosixString.hsc" #-}
unsetEnv (PS name) = B.useAsCString name $ \ s ->
  throwErrnoIfMinus1_ "unsetenv" (c_unsetenv s)
foreign import capi unsafe "HsUnix.h unsetenv"
   c_unsetenv :: CString -> IO CInt
{-# LINE 118 "System/Posix/Env/PosixString.hsc" #-}
{-# LINE 121 "System/Posix/Env/PosixString.hsc" #-}
putEnv :: PosixString  -> IO ()
putEnv (PS sbs) = do
  buf <- mallocBytes (l+1)
  copyToPtr sbs 0 buf (fromIntegral l)
  pokeByteOff buf l (0::Word8)
  throwErrnoIfMinus1_ "putenv" (c_putenv buf)
 where l = B.length sbs
foreign import ccall unsafe "putenv"
   c_putenv :: CString -> IO CInt
setEnv ::
  PosixString  ->
  PosixString  ->
  Bool        ->
  IO ()
{-# LINE 149 "System/Posix/Env/PosixString.hsc" #-}
setEnv (PS key) (PS value) ovrwrt = do
  B.useAsCString key $ \ keyP ->
    B.useAsCString value $ \ valueP ->
      throwErrnoIfMinus1_ "setenv" $
        c_setenv keyP valueP (fromIntegral (fromEnum ovrwrt))
foreign import ccall unsafe "setenv"
   c_setenv :: CString -> CString -> CInt -> IO CInt
{-# LINE 165 "System/Posix/Env/PosixString.hsc" #-}
getArgs :: IO [PosixString]
getArgs =
  alloca $ \ p_argc ->
  alloca $ \ p_argv -> do
   getProgArgv p_argc p_argv
   p    <- fromIntegral <$> peek p_argc
   argv <- peek p_argv
   peekArray (p - 1) (advancePtr argv 1) >>= mapM (fmap PS . B.packCString)
foreign import ccall unsafe "getProgArgv"
  getProgArgv :: Ptr CInt -> Ptr (Ptr CString) -> IO ()
_equal :: Word8
_equal = 0x3d
_toStr :: B.ShortByteString -> String
_toStr = either (error . show) id . decodeWith (mkUTF8 TransliterateCodingFailure) . PosixString