diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs
index 0056a1591..60bc699ab 100644
--- a/src/Text/Pandoc/Error.hs
+++ b/src/Text/Pandoc/Error.hs
@@ -63,6 +63,7 @@ data PandocError = PandocIOError String IOError
                  | PandocResourceNotFound String
                  | PandocTemplateError String
                  | PandocAppError String
+                 | PandocEpubSubdirectoryError String
                  deriving (Show, Typeable, Generic)
 
 instance Exception PandocError
@@ -104,6 +105,8 @@ handleError (Left e) =
         "File " ++ fn ++ " not found in resource path"
     PandocTemplateError s -> err 5 s
     PandocAppError s -> err 1 s
+    PandocEpubSubdirectoryError s -> err 31 $
+      "EPUB subdirectory name '" ++ s ++ "' contains illegal characters"
 
 err :: Int -> String -> IO a
 err exitCode msg = do
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index c7211c86e..6519f807c 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -213,6 +213,7 @@ data WriterOptions = WriterOptions
   , writerHighlightStyle    :: Maybe Style  -- ^ Style to use for highlighting
                                            -- (Nothing = no highlighting)
   , writerSetextHeaders     :: Bool       -- ^ Use setext headers for levels 1-2 in markdown
+  , writerEpubSubdirectory  :: String       -- ^ Subdir for epub in OCF
   , writerEpubMetadata      :: Maybe String -- ^ Metadata to include in EPUB
   , writerEpubFonts         :: [FilePath] -- ^ Paths to fonts to embed
   , writerEpubChapterLevel  :: Int            -- ^ Header level for chapters (separate files)
@@ -249,6 +250,7 @@ instance Default WriterOptions where
                       , writerListings         = False
                       , writerHighlightStyle   = Just pygments
                       , writerSetextHeaders    = True
+                      , writerEpubSubdirectory = "EPUB"
                       , writerEpubMetadata     = Nothing
                       , writerEpubFonts        = []
                       , writerEpubChapterLevel = 1
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 11ca7d168..96c8847df 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -34,14 +34,14 @@ Conversion of 'Pandoc' documents to EPUB.
 module Text.Pandoc.Writers.EPUB ( writeEPUB2, writeEPUB3 ) where
 import Codec.Archive.Zip (Entry, addEntryToArchive, eRelativePath, emptyArchive,
                           fromArchive, fromEntry, toEntry)
-import Control.Monad (mplus, when, zipWithM)
+import Control.Monad (mplus, when, unless, zipWithM)
 import Control.Monad.Except (catchError, throwError)
 import Control.Monad.State.Strict (State, StateT, evalState, evalStateT, get, gets,
                             lift, modify, put)
 import qualified Data.ByteString.Lazy as B
 import qualified Data.ByteString.Lazy.Char8 as B8
 import qualified Data.Text.Lazy as TL
-import Data.Char (isAlphaNum, isDigit, toLower)
+import Data.Char (isAlphaNum, isDigit, toLower, isAscii)
 import Data.List (intercalate, isInfixOf, isPrefixOf)
 import qualified Data.Map as M
 import Data.Maybe (catMaybes, fromMaybe)
@@ -80,7 +80,6 @@ data Chapter = Chapter (Maybe [Int]) [Block]
 
 data EPUBState = EPUBState {
         stMediaPaths  :: [(FilePath, (FilePath, Maybe Entry))]
-      , stEPUBSubdir  :: String
       }
 
 type E m = StateT EPUBState m
@@ -362,9 +361,7 @@ writeEPUB :: PandocMonad m
           -> Pandoc         -- ^ Document to convert
           -> m B.ByteString
 writeEPUB epubVersion opts doc =
-  let initState = EPUBState { stMediaPaths = []
-                            , stEPUBSubdir = "EPUB"
-                            }
+  let initState = EPUBState { stMediaPaths = [] }
   in
     evalStateT (pandocToEPUB epubVersion opts doc)
       initState
@@ -375,7 +372,10 @@ pandocToEPUB :: PandocMonad m
              -> Pandoc
              -> E m B.ByteString
 pandocToEPUB version opts doc@(Pandoc meta _) = do
-  epubSubdir <- gets stEPUBSubdir
+  let epubSubdir = writerEpubSubdirectory opts
+  -- sanity check on epubSubdir
+  unless (all (\c -> isAscii c && isAlphaNum c) epubSubdir) $
+    throwError $ PandocEpubSubdirectoryError epubSubdir
   let epub3 = version == EPUB3
   let writeHtml o = fmap (UTF8.fromTextLazy . TL.fromStrict) .
                       writeHtmlStringForEPUB version o
@@ -888,7 +888,7 @@ modifyMediaRef :: PandocMonad m
 modifyMediaRef _ "" = return ""
 modifyMediaRef opts oldsrc = do
   media <- gets stMediaPaths
-  epubSubdir <- gets stEPUBSubdir
+  let epubSubdir = writerEpubSubdirectory opts
   case lookup oldsrc media of
          Just (n,_) -> return n
          Nothing    -> catchError