{-# OPTIONS_GHC -Wno-identities #-}
{-# LANGUAGE
ForeignFunctionInterface, TypeSynonymInstances,
ScopedTypeVariables, FlexibleInstances, FlexibleContexts,
UndecidableInstances
#-}
module Language.Perl
(
Context(..)
, SV
, ToSV(..)
, FromSV(..)
, withPerl
, callSub, (.:), (.!)
, callMethod, (.$), (.$!)
, eval
, eval_
, use
)
where
import Control.Concurrent
import Control.Exception (bracket, throwIO, Exception(..))
import Control.Monad
import qualified Data.ByteString as BS
import Data.Dynamic (toDyn)
import Data.List ( intercalate)
import Data.Text (Text)
import qualified Data.Text.Encoding as T
import Foreign hiding (void)
import Foreign.C.Types
import Foreign.C.String
import Language.Perl.Internal
import Language.Perl.Internal.Types
{-# ANN module ("HLint: ignore Eta reduce" :: String) #-}
{-# ANN module ("HLint: ignore Use camelCase" :: String) #-}
withPerl :: IO a -> IO a
withPerl f =
withCString "-e" $ \prog -> withCString "" $ \cstr ->
withArray [prog, prog, cstr] $ \argv ->
bracket (acquire argv) release between
where
acquire argv = hsperl_init 3 argv
release interp = do
hsperl_set_destruct_level
void $ perl_destruct interp
perl_free interp
between _interp = (if rtsSupportsBoundThreads then runInBoundThread else id)
f
class ToSV a where
toSV :: a -> IO SV
class FromSV a where
fromSV :: SV -> IO a
instance ToSV SV where toSV = return
instance FromSV SV where fromSV = return
instance ToSV () where
toSV _ = hsperl_sv_undef
instance FromSV () where
fromSV x = seq x (return ())
instance ToSV String where
toSV str = withCStringLen str $ \(cstr, len) ->
hsperl_newSVpvn cstr (toEnum len)
instance FromSV String where
fromSV sv = do
cstr <- hsperl_SvPV sv
peekCString cstr
instance ToSV Text where
toSV txt = BS.useAsCStringLen (T.encodeUtf8 txt) $ \(cstr, len) -> do
sv <- hsperl_newSVpvn cstr (toEnum len)
hsperl_SvUTF8_on sv
return sv
instance FromSV Text where
fromSV sv =
alloca $ \(lenPtr :: Ptr CSize) -> do
cStr <- hsperl_sv_2pvutf8 sv lenPtr
len <- peek lenPtr
T.decodeUtf8 <$> BS.packCStringLen (cStr, fromIntegral len)
instance ToSV Int where
toSV = hsperl_newSViv . toEnum
instance FromSV Int where
fromSV = fmap fromEnum . hsperl_SvIV
instance ToSV IV where
toSV = toSV . toInt
where
toInt :: IV -> Int
toInt = fromIntegral
instance FromSV IV where
fromSV = fmap fromInt . fromSV
where
fromInt :: Int -> IV
fromInt = fromIntegral
instance ToSV NV where
toSV = hsperl_newSVnv . realToFrac
instance FromSV NV where
fromSV = fmap realToFrac . hsperl_SvNV
instance FromSV Bool where
fromSV = hsperl_SvTRUE
instance ToSV Bool where
toSV True = hsperl_sv_yes
toSV False = hsperl_sv_no
class ToCV a where
toCV :: a -> Int -> IO SV
instance {-# OVERLAPS #-} ToSV a => ToCV a where
toCV x _ = toSV x
class ToArgs a where
toArgs :: a -> IO [SV]
class FromArgs a where
fromArgs :: [SV] -> IO a
contextOf :: a -> Context
contextOf _ = ScalarCtx
instance ToArgs [String] where
toArgs = mapM toSV
instance FromArgs [String] where
fromArgs = mapM fromSV
instance FromArgs () where
fromArgs _ = return ()
contextOf _ = VoidCtx
instance ToArgs () where
toArgs _ = return []
instance {-# OVERLAPS #-} ToSV a => ToArgs a where
toArgs = fmap (:[]) . toSV
instance (ToSV a, ToSV b) => ToArgs (a, b) where
toArgs (x, y) = do
x' <- toSV x
y' <- toSV y
return [x', y']
instance {-# OVERLAPS #-} FromSV a => FromArgs a where
fromArgs [] = error "Can't convert an empty return list!"
fromArgs (x:_) = fromSV x
contextOf _ = ScalarCtx
instance (FromSV a, FromSV b) => FromArgs (a, b) where
fromArgs [] = error "Can't convert an empty return list!"
fromArgs [_] = error "Can't convert a single return list!"
fromArgs (x:y:_) = do
x' <- fromSV x
y' <- fromSV y
return (x', y')
contextOf _ = ListCtx
instance ToArgs [SV] where
toArgs = return
instance FromArgs [SV] where
fromArgs = return
instance ToArgs a => ToSV (IO a) where
toSV f = do
sp <- newStablePtr $ \_ _ -> do
svs <- toArgs =<< f
mkSVList svs
hsperl_make_cv sp
instance {-# OVERLAPS #-} (ToArgs a, FromArgs r) => ToSV (r -> IO a) where
toSV f = do
sp <- newStablePtr $ \args _ -> do
args' <- fromArgs =<< asSVList args
svs <- toArgs =<< f args'
mkSVList svs
hsperl_make_cv sp
instance (ToArgs a, FromArgs (r1, r2)) => ToSV (r1 -> r2 -> IO a) where
toSV f = do
sp <- newStablePtr $ \args _ -> do
(a1, a2) <- fromArgs =<< asSVList args
svs <- toArgs =<< f a1 a2
mkSVList svs
hsperl_make_cv sp
instance {-# OVERLAPS #-} (ToArgs a, FromArgs r) => ToSV (r -> a) where
toSV f = do
sp <- newStablePtr $ \args _ -> do
args' <- fromArgs =<< asSVList args
svs <- toArgs $ f args'
mkSVList svs
hsperl_make_cv sp
instance (ToArgs a, FromArgs (r1, r2)) => ToSV (r1 -> r2 -> a) where
toSV f = do
sp <- newStablePtr $ \args _ -> do
(a1, a2) <- fromArgs =<< asSVList args
svs <- toArgs $ f a1 a2
mkSVList svs
hsperl_make_cv sp
returnPerl :: forall a. FromArgs a => Ptr SV -> IO a
returnPerl rv = do
res <- svEither rv
case res of
Left [err] -> throwIO (toException $ toDyn err)
Left (_:x:_) -> error =<< fromSV x
Right r -> fromArgs r
_ -> error "unexpected return value"
eval :: forall a. FromArgs a => String -> IO a
eval str = withCStringLen str $ \(cstr, len) ->
hsperl_eval cstr (toEnum len) (numContext $ contextOf (undefined :: a)) returnPerl
eval_ :: String -> IO ()
eval_ str = eval str
callSub :: forall s a r. (ToCV s, ToArgs a, FromArgs r) => s -> a -> IO r
callSub sub args = do
args' <- toArgs args
sub' <- toCV sub (length args')
withSVArray args' $ \argsPtr ->
hsperl_apply sub' (SV nullPtr) argsPtr (numContext $ contextOf (undefined :: r)) returnPerl
callMethod :: forall i m a r. (ToSV i, ToSV m, ToArgs a, FromArgs r) => i -> m -> a -> IO r
callMethod inv meth args = do
inv' <- toSV inv
args' <- toArgs args
sub' <- toSV meth
withSVArray args' $ \argsPtr ->
hsperl_apply sub' inv' argsPtr (numContext $ contextOf (undefined :: r)) returnPerl
(.:) :: (ToCV sub, ToArgs args, FromArgs ret) => sub -> args -> IO ret
(.:) = callSub
(.!) :: (ToCV sub, ToArgs args) => sub -> args -> IO ()
(.!) = callSub
(.$) :: (ToSV meth, ToArgs args, FromArgs ret) => SV -> meth -> args -> IO ret
(.$) = callMethod
(.$!) :: (ToSV meth, ToArgs args) => SV -> meth -> args -> IO ()
(.$!) = callMethod
use :: String -> IO SV
use m = eval $ "use " ++ m ++ "; q[" ++ m ++ "]"
instance FromArgs r => FromSV (IO r) where
fromSV x =
return $ callSub x ()
instance (ToArgs a, FromArgs r) => FromSV (a -> IO r) where
fromSV x =
return $ callSub x
instance (ToArgs a, ToArgs b, FromArgs r) => FromSV (a -> b -> IO r) where
fromSV x =
return $ \arg1 arg2 -> do
as1 <- toArgs arg1
as2 <- toArgs arg2
callSub x (as1 ++ as2)
instance {-# OVERLAPS #-} ToCV String where
toCV sub count = do
cv <- withCString sub hsperl_get_cv
if unCV cv /= nullPtr then return (SV $ castPtr $ unCV cv) else do
let prms = map (\i -> "$_[" ++ show i ++ "]") [0 .. count-1]
eval ("sub { " ++ sub ++ "(" ++ intercalate ", " prms ++ ") }")
hsPerlApply :: StablePtr Callback -> Ptr SV -> CInt -> IO (Ptr SV)
hsPerlApply ptr args cxt = do
f <- deRefStablePtr ptr
f args cxt
foreign export ccall "hsPerlApply"
hsPerlApply :: StablePtr Callback -> Ptr SV -> CInt -> IO (Ptr SV)