{-# LINE 1 "src/System/Posix/Directory/Foreign.hsc" #-}
module System.Posix.Directory.Foreign where
{-# LINE 2 "src/System/Posix/Directory/Foreign.hsc" #-}

import Data.Bits
import Data.List (foldl')
import Foreign.C.Types


{-# LINE 8 "src/System/Posix/Directory/Foreign.hsc" #-}

{-# LINE 9 "src/System/Posix/Directory/Foreign.hsc" #-}

{-# LINE 10 "src/System/Posix/Directory/Foreign.hsc" #-}

{-# LINE 11 "src/System/Posix/Directory/Foreign.hsc" #-}

{-# LINE 12 "src/System/Posix/Directory/Foreign.hsc" #-}

{-# LINE 13 "src/System/Posix/Directory/Foreign.hsc" #-}

newtype DirType = DirType Int deriving (Eq, Show)
data Flags = Flags Int | UnsupportedFlag String deriving (Eq, Show)

unFlags :: Flags -> Int
unFlags (Flags i) = i
unFlags (UnsupportedFlag name) = error (name ++ " is not supported on this platform")

-- |Returns @True@ if posix-paths was compiled with support for the provided
-- flag. (As of this writing, the only flag for which this check may be
-- necessary is 'oCloexec'; all other flags will always yield @True@.)
isSupported :: Flags -> Bool
isSupported (Flags _) = True
isSupported _ = False

-- |@O_CLOEXEC@ is not supported on every POSIX platform. Use
-- @'isSupported' oCloexec@ to determine if support for @O_CLOEXEC@ was
-- compiled into your version of posix-paths. (If not, using @oCloexec@ will
-- throw an exception.)
oCloexec :: Flags

{-# LINE 34 "src/System/Posix/Directory/Foreign.hsc" #-}
oCloexec = Flags 524288
{-# LINE 35 "src/System/Posix/Directory/Foreign.hsc" #-}

{-# LINE 40 "src/System/Posix/Directory/Foreign.hsc" #-}



-- If these enum declarations occur earlier in the file, haddock
-- gets royally confused about the above doc comments.
-- Probably http://trac.haskell.org/haddock/ticket/138

dtBlk :: DirType
dtBlk = DirType 6
dtChr :: DirType
dtChr = DirType 2
dtDir :: DirType
dtDir = DirType 4
dtFifo :: DirType
dtFifo = DirType 1
dtLnk :: DirType
dtLnk = DirType 10
dtReg :: DirType
dtReg = DirType 8
dtSock :: DirType
dtSock = DirType 12
dtUnknown :: DirType
dtUnknown = DirType 0

{-# LINE 48 "src/System/Posix/Directory/Foreign.hsc" #-}

oAppend :: Flags
oAppend = Flags 1024
oAsync :: Flags
oAsync = Flags 8192
oCreat :: Flags
oCreat = Flags 64
oDirectory :: Flags
oDirectory = Flags 65536
oExcl :: Flags
oExcl = Flags 128
oNoctty :: Flags
oNoctty = Flags 256
oNofollow :: Flags
oNofollow = Flags 131072
oNonblock :: Flags
oNonblock = Flags 2048
oRdonly :: Flags
oRdonly = Flags 0
oWronly :: Flags
oWronly = Flags 1
oRdwr :: Flags
oRdwr = Flags 2
oSync :: Flags
oSync = Flags 1052672
oTrunc :: Flags
oTrunc = Flags 512

{-# LINE 50 "src/System/Posix/Directory/Foreign.hsc" #-}

pathMax :: Int
pathMax = 4096
{-# LINE 53 "src/System/Posix/Directory/Foreign.hsc" #-}

unionFlags :: [Flags] -> CInt
unionFlags = fromIntegral . foldl' ((. unFlags) . (.|.)) 0