module System.Wordexp
(
wordexp
, Flags, nosubst, errors, noundef
, WordexpError (..)
) where
import Control.Exception (Exception)
import Control.Monad
import Data.Data (Data)
import Data.Typeable (Typeable)
import Foreign
import Foreign.C
import Foreign.C.Types
import Data.Array (Ix)
import Data.Semigroup (Semigroup(..), Monoid(..))
data Wordexp
data FLAGS = WRDE_APPEND
| WRDE_DOOFFS
| WRDE_NOCMD
| WRDE_REUSE
| WRDE_SHOWERR
| WRDE_UNDEF
deriving (Show,Read,Eq,Ord,Bounded,Ix,Data,Typeable)
instance Enum FLAGS where
fromEnum WRDE_APPEND = 2
fromEnum WRDE_DOOFFS = 1
fromEnum WRDE_NOCMD = 4
fromEnum WRDE_REUSE = 8
fromEnum WRDE_SHOWERR = 16
fromEnum WRDE_UNDEF = 32
toEnum 2 = WRDE_APPEND
toEnum 1 = WRDE_DOOFFS
toEnum 4 = WRDE_NOCMD
toEnum 8 = WRDE_REUSE
toEnum 16 = WRDE_SHOWERR
toEnum 32 = WRDE_UNDEF
toEnum unmatched = error ("FLAGS.toEnum: Cannot match " ++ show unmatched)
newtype Flags = Flags Int
deriving (Show, Read, Eq, Ord, Bounded, Bits, Ix, Data, Typeable)
instance Semigroup Flags where
(<>) = (.|.)
instance Monoid Flags where
mempty = Flags 0
mappend = (<>)
nosubst :: Flags
nosubst = Flags $ fromEnum WRDE_NOCMD
errors :: Flags
errors = Flags $ fromEnum WRDE_SHOWERR
noundef :: Flags
noundef = Flags $ fromEnum WRDE_UNDEF
data WordexpError = OutOfSpace
| IllegalCharacterOccurence
| UndefinedShellVariable
| CommandSubstitution
| ShellSyntaxError
deriving (Show,Read,Eq,Ord,Bounded,Ix,Data,Typeable)
instance Enum WordexpError where
fromEnum OutOfSpace = 1
fromEnum IllegalCharacterOccurence = 2
fromEnum UndefinedShellVariable = 3
fromEnum CommandSubstitution = 4
fromEnum ShellSyntaxError = 5
toEnum 1 = OutOfSpace
toEnum 2 = IllegalCharacterOccurence
toEnum 3 = UndefinedShellVariable
toEnum 4 = CommandSubstitution
toEnum 5 = ShellSyntaxError
toEnum unmatched = error ("WordexpError.toEnum: Cannot match " ++ show unmatched)
instance Exception WordexpError
wordexp :: Flags -> String -> IO (Either WordexpError [String])
wordexp (Flags f) s =
withCString s $ \cs ->
allocaBytes size $ \p -> do
ret <- c_wordexp cs p (fromIntegral f)
case ret of
0 -> do
c <- fromIntegral `fmap` wordc p
v <- wordv p
xs <- forM [0 .. c1] $ peekElemOff v >=> peekCString
c_wordfree p
return $ Right xs
e -> return . Left . toEnum $ fromIntegral e
where
size = sizeOf (undefined :: CSize) + sizeOf (undefined :: Ptr CString) + sizeOf (undefined :: CSize)
wordc :: Ptr Wordexp -> IO CSize
wordc p = peekByteOff p 0
wordv :: Ptr Wordexp -> IO (Ptr CString)
wordv p = peekByteOff p (sizeOf (undefined :: CSize))
foreign import ccall unsafe "wordexp"
c_wordexp :: CString -> Ptr Wordexp -> CInt -> IO CInt
foreign import ccall unsafe "wordfree"
c_wordfree :: Ptr Wordexp -> IO ()