Safe Haskell

11 downloads 68951 Views 7MB Size Report
module PluginAPI (PluginInterface, RIO(), log) where type PluginInterface = String -> RIO Bool newtype RIO a = UnsafeRIO { runRIO :: IO a } instance Monad RIO ...
Safe Haskell David Terei, Simon Marlow, Simon Peyton Jones, David Mazières

Tuesday, September 25, 12

Motivation Write a server in Haskell that accepts arbitrary Haskell source code from clients, compiles the code with an -XSafe flag and safely executes it.

For example, an online version of GHCi.

Tuesday, September 25, 12

Motivation Can’t run just any code, need to protect the server module MaliciousPete (main) where import System.Process wipe :: IO ExitCode wipe = system “rm -rf /” main = wipe

Tuesday, September 25, 12

How? • Use the type system. • Simplest policy: we will only execute pure functions. Server

module PluginAPI where type PuginInterface = String -> Bool module ClientCode where

Client

Tuesday, September 25, 12

import PluginAPI search :: PluginInterface search s = ...

How? • We can extend this by using a monad. module PluginAPI (PluginInterface, RIO(), log) where type PluginInterface = String -> RIO Bool newtype RIO a = UnsafeRIO { runRIO :: IO a } instance Monad RIO ... log :: String -> RIO ()

Note: UnsafeRIO not exported! Tuesday, September 25, 12

How? • We can now extend our sandbox simply by defining function in RIO. -- Scratch directory access readFile :: String -> RIO String writeFile :: String -> RIO String -- Allow access to a white list of network endpoints sendMsg :: EndPoint -> String -> RIO ()

• Monads correspond with security mechanisms. • Untrusted code from client can import IO, we just use types to make sure it cannot be run. • Allow far more flexibility than other language based mechanism (Java, Javascript...) Tuesday, September 25, 12

Existing Research • W. Harrison. Achieving information flow security through precise control of effects. In Computer Security Foundations Workshop. IEEE Computer Society, 2005.

• P. Li and S. Zdancewic. Encoding information flow in Haskell. In Computer Security Foundations Workshop. IEEE Computer Society, 2006.

• T.-c. Tsai, A. Russo, and J. Hughes. A library for secure multi- threaded information flow in Haskell. In Computer Security Foun- dations Symposium. IEEE Computer Society, 2007.

• A. Russo, K. Claessen, and J. Hughes. A library for light-weight information flow security in Haskell. In Haskell Symposium. ACM SIGPLAN, 2008

• D. Stefan, A. Russo, J. C. Mitchell, and D. Mazières. Flexible dynamic information flow control in Haskell. In Haskell Symposium. ACM SIGPLAN, 2011.

• D. Stefan, A. Russo, P. Buiras, A. Levy, J. C. Mitchell, D. Mazières. Addressing Covert Termination and Timing Channels in Concurrent Information Flow Systems. In ICFP. ACM SIGPLAN, 2012.

• .... Tuesday, September 25, 12

Attacks • While very appealing it relies on there being no holes at all in Haskell type system. • This is trivial to attack.

Tuesday, September 25, 12

Attacks 1) Unsafe primitives module MaliciousPete (search) where import PluginAPI import GHC.Base (realWorld#) ourUnIO :: IO a -> a ourUnIO (IO m) = case m realWorld# of (# _, r #) -> r search :: PluginInterface search _ = (ourUnIO $ do {- remove file system -} ) `seq` return False

Tuesday, September 25, 12

Attacks 2) Unsafe functions module MaliciousPete (search) where import PluginAPI import System.IO.Unsafe (unsafePerformIO) search :: PluginInterface search _ = (unsafePerformIO $ do {- remove file system -} ) `seq` return False

Tuesday, September 25, 12

Attacks 3) FFI module MaliciousPete (search) where import PluginAPI import Foreign.C foreign import ccall “system” c_system :: CString -> () wipe ::() wipe = c_system “rm -rf /” search :: PluginInterface search _ = wipe`seq` return False

Tuesday, September 25, 12

Attacks 4) Data.Typeable module MaliciousPete (search) where import PluginAPI import Data.Maybe import Data.Typeable instance Typeable1 RIO where typeOf1 _ = typeOf1 (return ‘c’ :: IO Char) search :: String -> Logging Bool search _ = (fromJust . cast $ do {- remove file system -} ) >> return False

Tuesday, September 25, 12

More Attacks Violate the type system:



realWorld#

• FFI • Hand-crafted Typeable instances Violate module boundaries: • Generalized Newtype Deriving • Template Haskell Can change server code: • RULES • Overlapping Instances Tuesday, September 25, 12

Safe Subset • First step is to define a safe subset of the Haskell language where the use of these features is removed. • Compile code in the safe subset with -XSafe. • Intuition of the safe subset is to enforce the property:

Types never lie

Tuesday, September 25, 12

Protected module MaliciousPete (search) where import PluginAPI import Foreign.C foreign import ccall “system” c_system :: CString -> () wipe ::() wipe = c_system “rm -rf /” search :: PluginInterface search _ = wipe`seq` return False sh$ ghc -c MaliciousPete.hs -XSafe MaliciousPete.hs:6:1: Unacceptable result type in foreign declaration: () Safe Haskell is on, all FFI imports must be in the IO monad When checking declaration: foreign import ccall "system" c_system :: CString -> () Tuesday, September 25, 12

Imports & Tracking • Second step is to ensure that imports are safe. • unsafePerformIO for example is simply a function that unsafely uses the realWorld# symbol. {-# LANGUAGE Safe #-} module Unknown (search) where import A (f) -- safe? import B (g) -- ““ search :: String -> Logging Bool search x = return $ f x || g x

• How can we ensure that A and B won’t allow the Unknown module to lie about types? Tuesday, September 25, 12

Trusting ByteString • Could only allow modules compiled with -XSafe to be imported. • But, client imports ByteString and the module is considered unsafe, so compilation fails! module Data.ByteString where ... cons :: Word8 -> ByteString -> ByteString cons c (PS x s len) = unsafeCreate (l+1) $ \p -> withForeignPtr x $ \f -> do poke p c memcpy (p `plusPtr` 1) (f `plusPtr` s) len

• An important step then is deciding when internally unsafe modules can be trusted to provide an externally safe API. Tuesday, September 25, 12

Safe Haskell

Tuesday, September 25, 12

Safe Haskell

Key Client can’t import Client can import

uses safe features

uses unsafe features

Tuesday, September 25, 12

Compilation Failure

Safe Haskell

Key Client can’t import Client can import

inferred safe

uses safe features

uses unsafe features

Tuesday, September 25, 12

Compilation Failure

Safe Haskell safe imports trusted

safe imports not trusted

Key Client can’t import Client can import

uses safe features

uses unsafe features

Tuesday, September 25, 12

Compilation Failure

Safe Haskell safe imports trusted

safe imports not trusted

Key Client can’t import Client can import

uses safe features

uses unsafe features author asserted Unsafe Tuesday, September 25, 12

Compilation Failure

Safe Haskell safe imports trusted

safe imports not trusted

compiled with -XSafe uses safe features

uses unsafe features author asserted Unsafe Tuesday, September 25, 12

Key Client can’t import Client can import Compilation Failure

Safe Haskell safe imports trusted

safe imports not trusted

compiled with -XSafe uses safe features author claimed Trustworthy uses unsafe features author asserted Unsafe Tuesday, September 25, 12

Key Client can’t import Client can import Compilation Failure

Server trusts author Server doesn’t trust author

Safe Haskell safe imports trusted

Safe

safe imports not trusted

compiled with -XSafe uses safe features

Trustworthy

author claimed Trustworthy uses unsafe features

Unsafe Tuesday, September 25, 12

author asserted Unsafe

Key Client can’t import Client can import Compilation Failure

Server trusts author Server doesn’t trust author

Trust A module M in a package P is trusted on the server if either: 1. The compiler can check that M is worthy of trust: • M declared Safe • All of M’s direct imports are trusted 2. The server administrator trusts M: • M declares itself Trustworthy • The package that M resides in is trusted by the user • All of M’s direct safe imports are trusted Tuesday, September 25, 12

Trustworthy 2. The user trusts A: • A is declared Trustworthy • The package that A resides in is trusted by the user • All of A’s direct safe imports are trusted • Trustworthy modules are a controlled escape hatch. • The guarantees of Safe Haskell are dependent on the Trustworthy modules you trust.

Tuesday, September 25, 12

Trustworthy 2. The user trusts A: • A is declared Trustworthy • The package that A resides in is trusted by the user • All of A’s direct safe imports are trusted • Package authors should carefully consider the safety of their API before adding Trustworthy • However, the onus is always on the consumer of a Trustworthy module since some authors may be malicious.

Tuesday, September 25, 12

Safe Imports 2. The user trusts A: • A is declared Trustworthy • The package that A resides in is trusted by the user • All of A’s direct safe imports are trusted {-# LANGUAGE Trustworthy #-} module B where import B1 import safe B2 ...

Allows flexibility in what responsibility you take when using Trustworthy Tuesday, September 25, 12

Example Package France: {-# LANGUAGE Safe #-} module Paris (key) where key = “henry”

admin decides to trust England

Package England: {-# LANGUAGE Trustworthy #-} module London where import System.IO.Unsafe import safe Paris ...

Does the server admin trust module London? Tuesday, September 25, 12

GHC.IO Demo time! module M (NoIO(), runNoIO) where newtype NoIO a = NoIO { runNoIO :: IO a } instance Monad NoIO where return a = NoIO $ return a (>>=) k f = NoIO $ noio k >>= noio . f

ghci> :runmonad NoIO

Tuesday, September 25, 12

How safe is Hackage? Safe (27%)

Unsafe (73%)

11000

8250

5500

2750

0 Tuesday, September 25, 12

Infered Modules

How safe is Hackage? Buildable (83%)

Failed (17%)

1500

1125

750

375

0 Tuesday, September 25, 12

Buildable Packages (with all imports regarded as trusted)

How safe is Hackage? GND (54%) Typeable (13%)

TH (31%) FFI (12%)

150

112.5

75

37.5

0 Tuesday, September 25, 12

Reason for failed package builds

Going forward • GND solvable. • Typeable solvable now we have polymorphic kinds in GHC. • Unsafe functions moving to own modules in base package.

Tuesday, September 25, 12

Call to arms! • Language designers: make your extensions safe! • Package maintainers: Make your modules safe where possible! contain unsafe functions in own modules.

Tuesday, September 25, 12

Safe Haskell GHC 7.4+ http://safehaskell.scs.stanford.edu http://ghc.io

Tuesday, September 25, 12

Other Slides

Tuesday, September 25, 12

Attacks 4) Generalized Newtype Deriving {-# LANGUAGE GeneralizedNewtypeDeriving #-} module MaliciousPete (run) where import PluginAPI -- GND tricks (see paper) breakBoundaries :: c (Logging Bool) -> c Bool breakBoundaries = -- GND tricks

A ‘research’ bug (for 5 years now) http://hackage.haskell.org/trac/ghc/ticket/1496 Tuesday, September 25, 12

Safe Haskell • A set of guarantees that Safe Haskell provides for code in the safe subset. • Categorization of Haskell modules according to what safety guarantees they can provide. • A system of trust to track and restrict what modules you trust.

Tuesday, September 25, 12

Guarantees* Safe Haskell looks to provide: • Type safety • Referential transparency • Module encapsulation • Modular reasoning • Semantic consistency

Tuesday, September 25, 12

Safe Haskell • Classifies modules as either: • Safe: module confined to safe subset • Trustworthy: unsafe internals but safe API • Unsafe: all other modules • Modules can be explicitly marked using either {-# LANGUAGE Safe #-} in a module or -XSafe on the command line. • Unmarked modules have their safety inferred (Safe or Unsafe). Tuesday, September 25, 12

Trust {-# LANGUAGE Safe #-} module Unknown (search) where import A (f) -- safe? import B (g) -- ““ search :: String -> Logging Bool search _ = return $ f x || g x

When should an import be allowed?

Tuesday, September 25, 12

Trust {-# LANGUAGE Safe #-} module Unknown (search) where import A (f) -- safe? import B (g) -- ““ search :: String -> Logging Bool search _ = return $ f x || g x

Checked that: • Unknown doesn’t use any unsafe language features. • Imported modules A and B are “trusted”.

Tuesday, September 25, 12

Safe Haskell users • GitStar -- www.gitstar.com • Built on top of Hakell Hails web framework • Uses information flow control (LIO package) for security of users data in the face of untrusted plugins • Stanford class CS242. • Course work needed to be submitted using -XSafe.

Tuesday, September 25, 12