{-# LINE 1 "src/unix/System/Uname.hsc" #-}
module System.Uname
    ( getRelease
    )
    where



import Foreign
import Foreign.C

getRelease :: IO String
getRelease = do
  alloca $ \ ptr ->
             do throwErrnoIfMinus1_ "uname" $ uname ptr
                peekCString $ release ptr
-- | @'uname' name@ stores nul-terminated strings of information
--   identifying the current system info to the structure referenced
--   by name.
--
--   > import Foreign.C
--   > import Foreign.Marshal
--   >
--   > sysName :: IO String
--   > sysName = alloca $ \ ptr ->
--   >           do throwErrnoIfMinus1_ "uname" $ uname ptr
--   >              peekCString $ sysname ptr
--
foreign import ccall unsafe "haskell_uname"
        uname :: Ptr Utsname -> IO CInt

data Utsname

instance Storable Utsname where
    sizeOf    = const (390)
{-# LINE 35 "src/unix/System/Uname.hsc" #-}
    alignment = const 1
{-# LINE 36 "src/unix/System/Uname.hsc" #-}
    poke      = error "Storable Utsname: peek: unsupported operation"
    peek      = error "Storable Utsname: poke: unsupported operation"

release :: Ptr Utsname -> CString
release = ((\hsc_ptr -> hsc_ptr `plusPtr` 130))
{-# LINE 41 "src/unix/System/Uname.hsc" #-}