haskell-hint / hint

Runtime Haskell interpreter
https://hackage.haskell.org/package/hint
BSD 3-Clause "New" or "Revised" License
260 stars 43 forks source link

Safe extension is not working #124

Open yaitskov opened 3 years ago

yaitskov commented 3 years ago

Hi,

hint is for 3rd party running code provided by the end user, but I was not able to find how to control access to packages from script code.

Let's looks at example. System.Process modules allows to launch anything. I put Safe extension in 2 different ways to prevent running script importing System.Process and it is ignored.

{-# LANGUAGE Safe #-}
module Hourse where
import System.Process
launch :: IO ()
launch = system "echo OOPS!!!!" >> pure ()

Interpreter:

{-# LANGUAGE ScopedTypeVariables #-}

module Main where
import           Data.Typeable
import           Data.Text as T
import           Options.Applicative
import           Language.Haskell.Interpreter
import           System.FilePath.Posix (dropExtensions)

main :: IO ()
main = do
  args <- parseCommandLineArgs 
  runR args
  where
    runR (EvalFunc func file) = do
      putStrLn $ " Evaluating function " ++ show func ++ " from file " ++ show file
      let sFile = T.unpack file
      ir <- runInterpreter (myInter sFile (T.unpack func))
      case ir of
        Left e -> putStrLn ("Failed " ++ show e)
        Right (a :: ()) -> putStrLn $ "SUCCESS!: " ++ show a

    myInter :: (Show a, Typeable a) => FilePath -> String -> Interpreter a
    myInter sFile sFunc = do
      loadModules [ sFile  ]
      modules <- getLoadedModules
      liftIO $ putStrLn ("Loaded modules: " ++ show modules)
      set [ languageExtensions := [Safe] ]
      setTopLevelModules [ dropExtensions sFile ]
      setImportsQ [("Prelude", Nothing)]
      resultIo <- interpret sFunc (as :: (Show a, Typeable a) => IO a)
      liftIO resultIo -- $ putStrLn ("Result: " ++ show result)

data EvalFunc
  = EvalFunc
    { _eval_function :: Text
    , _eval_file :: Text
    } deriving (Show, Eq)

commandParser :: Parser EvalFunc
commandParser =
  EvalFunc
    <$> argument str (metavar "FUNC" <> help "haskell function to call")
    <*> argument str (metavar "FILE" <> help "file containing a haskell function")

parseCommandLineArgs :: IO EvalFunc
parseCommandLineArgs = execParser $ info (commandParser <**> helper) desc
  where
    desc = progDesc "demo app showing hint library capabilities"
$ main launch Hourse.hs
 Evaluating function "launch" from file "Hourse.hs"
Loaded modules: ["Hourse"]
OOPS!!!!
SUCCESS!: ()

I use ghc (8.8.4) provided from stack.

gelisam commented 3 years ago

The Safe language extension is a feature of ghc, not a feature of hint. If you compile your Hourse.hs module with ghc (or equivalently, with stack or cabal), you will see that ghc accepts your program. Therefore, the fact that hint accepts the program as well is the expected behaviour. Conversely, the following program

{-# LANGUAGE Safe #-}
module Hourse where
import System.IO.Unsafe

myUnit :: ()
myUnit = unsafePerformIO $ putStrLn "oops"

is rejected both by ghc and by hint. I would thus say that hint is working as expected with respect to the Safe language extension.

I recommend taking a closer look at the documentation for the Safe language extension in order to double-check your understanding of how the feature works. If you still think the Safe language extension is not working as documented, please open a ticket on the ghc issue tracker, not hint's.

That being said, I do not recommend running untrusted code using hint, with or without the Safe language extension. While you can easily restrict which functions the user has access to using setImportsQ, users can still write infinite loops and consume all of your resources. This is especially problematic in Haskell since the timeout function relies on throwing an asynchronous exception to the wrapped code, which interrupts the program on the next memory allocation, and so a malicious piece of code could avoid getting interrupted by writing a tight loop which never allocates any memory.

The kind of projects for which hint is well-suited are things like loading a Haskell-based configuration file à la xmonad, or a spreadsheet program which uses Haskell as its expression language; desktop programs in which the user running the program is the same as the user writing the Haskell code being interpreted, and thus the user doesn't have an incentive to write malicious code in order to hack into their own computer. If you want to run untrusted code from the internet, I recommend building a much thicker defence layer around the untrusted code, e.g. by running it inside a virtual machine or something like that, don't run it directly inside your Haskell process.

Or, even better, define a smaller DSL which only includes the actions you do want to allow your users to perform, and then parse and interpret it. Don't give your users access to the entire Haskell language when a smaller language will do; when security matters, the smaller the attack surface, the better!

gelisam commented 3 years ago

Looks like the Safe extension is going away anyway.

yaitskov commented 3 years ago

Thanks for explaining. Yeah safe feature looks not very practical.

I tested same source file with safe pragma on with ghc and hint. Ghc reports violation, hint doesn't. That's why I filed my concern.

I am going to use haskell-src-ext to ensure safe imports and extensions. It is very easy to get AST for a file top. Looping without memory consumption looks impossible. At least I wasn't able active this.

gelisam commented 3 years ago

I tested same source file with safe pragma on with ghc and hint. Ghc reports violation, hint doesn't.

Reopening the ticket, that does sound like a bug. Could you give more details about how you tested on the ghc side? I cannot reproduce:

$ cat Hourse.hs
{-# LANGUAGE Safe #-}
module Hourse where
import System.Process
launch :: IO ()
launch = system "echo OOPS!!!!" >> pure ()
$ ghc Hourse.hs
[1 of 1] Compiling Hourse           ( Hourse.hs, Hourse.o )
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 9.0.1