module Text.Sass.Compilation
(
compileFile
, compileString
, SassExtendedResult
, StringResult
, ExtendedResult
, ExtendedResultBS
, resultString
, resultIncludes
, resultSourcemap
, SassError
, errorStatus
, errorJson
, errorText
, errorMessage
, errorFile
, errorSource
, errorLine
, errorColumn
) where
import qualified Bindings.Libsass as Lib
import Data.ByteString (ByteString, packCString)
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Control.Monad (forM, (>=>))
import Foreign
import Foreign.C
import Text.Sass.Internal
import Text.Sass.Options
data SassError = SassError {
errorStatus :: Int,
errorContext :: ForeignPtr Lib.SassContext
}
data SassExtendedResult a = SassExtendedResult {
resultString :: a,
resultContext :: ForeignPtr Lib.SassContext
}
type StringResult = IO (Either SassError String)
type ExtendedResult = IO (Either SassError (SassExtendedResult String))
type ExtendedResultBS = IO (Either SassError (SassExtendedResult ByteString))
class SassResult a where
toSassResult :: ForeignPtr Lib.SassContext -> IO a
instance Show SassError where
show (SassError s _) =
"SassError: cannot compile provided source, error status: " ++ show s
instance Eq SassError where
(SassError s1 _) == (SassError s2 _) = s1 == s2
instance Show (SassExtendedResult a) where
show _ = "SassExtendedResult"
instance SassResult String where
toSassResult ptr = withForeignPtr ptr $ \ctx -> do
result <- Lib.sass_context_get_output_string ctx
!result' <- peekCString result
return result'
instance SassResult ByteString where
toSassResult ptr = withForeignPtr ptr $ \ctx -> do
result <- Lib.sass_context_get_output_string ctx
!result' <- packCString result
return result'
instance (SassResult a) => SassResult (SassExtendedResult a) where
toSassResult ptr = do
str <- toSassResult ptr
return $ SassExtendedResult str ptr
loadFromError :: (Ptr Lib.SassContext -> IO a)
-> (a -> IO b)
-> SassError
-> IO b
loadFromError get conv err = withForeignPtr ptr $ get >=> conv
where ptr = errorContext err
loadStringFromError
:: (Ptr Lib.SassContext -> IO CString)
-> SassError
-> IO String
loadStringFromError get = loadFromError get peekCString
loadIntFromError :: (Integral a)
=> (Ptr Lib.SassContext -> IO a)
-> SassError
-> IO Int
loadIntFromError get = loadFromError get (return.fromIntegral)
errorJson :: SassError -> IO String
errorJson = loadStringFromError Lib.sass_context_get_error_json
errorText :: SassError -> IO String
errorText = loadStringFromError Lib.sass_context_get_error_text
errorMessage :: SassError -> IO String
errorMessage = loadStringFromError Lib.sass_context_get_error_message
errorFile :: SassError -> IO String
errorFile = loadStringFromError Lib.sass_context_get_error_file
errorSource :: SassError -> IO String
errorSource = loadStringFromError Lib.sass_context_get_error_src
errorLine :: SassError -> IO Int
errorLine = loadIntFromError Lib.sass_context_get_error_line
errorColumn :: SassError -> IO Int
errorColumn = loadIntFromError Lib.sass_context_get_error_column
resultIncludes :: SassExtendedResult a -> IO [String]
resultIncludes ex = withForeignPtr (resultContext ex) $ \ctx -> do
lst <- Lib.sass_context_get_included_files ctx
len <- Lib.sass_context_get_included_files_size ctx
forM (arrayRange $ fromIntegral len) (peekElemOff lst >=> peekCString)
resultSourcemap :: SassExtendedResult a -> IO (Maybe String)
resultSourcemap ex = withForeignPtr (resultContext ex) $ \ctx -> do
cstr <- Lib.sass_context_get_source_map_string ctx
if cstr == nullPtr
then return Nothing
else Just <$> peekCString cstr
compileInternal :: (SassResult b)
=> CString
-> SassOptions
-> (CString -> IO (Ptr a))
-> (Ptr a -> IO CInt)
-> FinalizerPtr a
-> IO (Either SassError b)
compileInternal str opts make compile finalizer = do
context <- make str
let opts' = castPtr context
copyOptionsToNative opts opts'
status <- withFunctions opts opts' $ compile context
fptr <- castForeignPtr <$> newForeignPtr finalizer context
if status /= 0
then return $ Left $
SassError (fromIntegral status) fptr
else do
result <- toSassResult fptr
return $ Right result
compileFile :: SassResult a
=> FilePath
-> SassOptions
-> IO (Either SassError a)
compileFile path opts = withCString path $ \cpath ->
compileInternal cpath opts
Lib.sass_make_file_context
Lib.sass_compile_file_context
Lib.p_sass_delete_file_context
compileString :: SassResult a
=> String
-> SassOptions
-> IO (Either SassError a)
compileString str opts = do
cdata <- newCString str
compileInternal cdata opts
Lib.sass_make_data_context
Lib.sass_compile_data_context
Lib.p_sass_delete_data_context