module Text.Sass.Utils
(
withOptionalCString
, listEntryNotNull
, loopCList
, copyToCList
, concatPaths
, arrayRange
) where
import Control.Monad (zipWithM_, (>=>))
import Control.Monad.IO.Class
import Control.Monad.Loops (whileM_)
import Control.Monad.Trans.Class
import Control.Monad.Trans.State.Strict
import Data.List (intercalate)
import Foreign
import Foreign.C
import System.FilePath (searchPathSeparator)
#if !MIN_VERSION_transformers(0,4,0)
modify' :: (Monad m) => (s -> s) -> StateT s m ()
modify' f = do
s <- get
put $! f s
#endif
withOptionalCString :: Maybe String -> (CString -> IO ()) -> IO ()
withOptionalCString (Just str) action = withCString str action
withOptionalCString Nothing _ = return ()
listEntryNotNull :: (Monad m, MonadIO m) => StateT (Ptr (Ptr a)) m Bool
listEntryNotNull = do
ptr <- get
val <- liftIO $ peek ptr
return $ val /= nullPtr
loopCList :: (Monad m, MonadIO m) => (Ptr a -> m ()) -> Ptr (Ptr a) -> m ()
loopCList action list =
flip evalStateT list $ whileM_ listEntryNotNull $ do
ptr <- get
val <- liftIO $ peek ptr
modify' (`plusPtr` sizeOf val)
lift $ action val
copyToCList :: (Num size, Enum size)
=> (CSize -> IO list)
-> (a -> IO element)
-> (list -> size -> element -> IO ())
-> [a]
-> IO list
copyToCList create convert set list = do
let len = length list
result <- create $ fromIntegral len
zipWithM_ (addToList result) [0..fromIntegral len 1] list
return result
where
addToList lst idx = convert >=> set lst idx
concatPaths :: [FilePath] -> FilePath
concatPaths = intercalate [searchPathSeparator]
arrayRange :: (Num a, Integral a, Enum a) => a -> [a]
arrayRange 0 = []
arrayRange l = [0..l 1]