diff --git a/INSTALL b/INSTALL
index 7203f7c7e..864dd33b7 100644
--- a/INSTALL
+++ b/INSTALL
@@ -94,6 +94,7 @@ It is possible to compile pandoc such that the data files
 pandoc uses are embedded in the binary.  The resulting binary
 can be run from any directory and is completely self-contained.
 
+    cabal install hsb2hs  # a required build tool
     cabal install --flags="embed_data_files" citeproc-hs
     cabal configure --flags="embed_data_files"
     cabal build
diff --git a/Setup.hs b/Setup.hs
index ba89b51cf..4245df203 100644
--- a/Setup.hs
+++ b/Setup.hs
@@ -1,6 +1,7 @@
 {-# LANGUAGE CPP #-}
 
 import Distribution.Simple
+import Distribution.Simple.PreProcess
 import Distribution.Simple.Setup
          (copyDest, copyVerbosity, fromFlag, installVerbosity, BuildFlags(..))
 import Distribution.PackageDescription (PackageDescription(..), Executable(..))
@@ -8,10 +9,11 @@ import Distribution.Simple.LocalBuildInfo
          (LocalBuildInfo(..), absoluteInstallDirs)
 import Distribution.Verbosity ( Verbosity, silent )
 import Distribution.Simple.InstallDirs (mandir, CopyDest (NoCopyDest))
-import Distribution.Simple.Utils (installOrdinaryFiles)
+import Distribution.Simple.Utils (installOrdinaryFiles, info)
 import Prelude hiding (catch)
 import System.Process ( rawSystem )
 import System.FilePath ( (</>) )
+import System.Directory ( findExecutable )
 import System.Exit
 
 main :: IO ()
@@ -29,6 +31,7 @@ main = do
     , instHook = \pkgdescr ->
          (instHook simpleUserHooks) pkgdescr{ executables =
             [x | x <- executables pkgdescr, exeName x /= "make-pandoc-man-pages"] }
+    , hookedPreProcessors = [ppBlobSuffixHandler]
     }
   exitWith ExitSuccess
 
@@ -53,3 +56,16 @@ installManpages pkg lbi verbosity copy =
   installOrdinaryFiles verbosity (mandir (absoluteInstallDirs pkg lbi copy))
              (zip (repeat manDir) manpages)
 
+ppBlobSuffixHandler :: PPSuffixHandler
+ppBlobSuffixHandler = ("hsb", \_ _ ->
+  PreProcessor {
+    platformIndependent = True,
+    runPreProcessor = mkSimplePreProcessor $ \infile outfile verbosity ->
+      do info verbosity $ "Preprocessing " ++ infile ++ " to " ++ outfile
+         hsb2hsPath <- findExecutable "hsb2hs"
+         case hsb2hsPath of
+            Just p  -> rawSystem p [infile, infile, outfile]
+            Nothing -> error "hsb2hs is needed to build this program: cabal install hsb2hs"
+         return ()
+
+  })
diff --git a/pandoc.cabal b/pandoc.cabal
index 8d8aaf442..e89628e81 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -246,9 +246,9 @@ Library
     build-depends:
                  blaze-html >= 0.4.3.0 && < 0.5
   if flag(embed_data_files)
-     build-depends: file-embed >= 0.0.4.7 && < 0.1,
-                    template-haskell >= 2.4 && < 2.9
      cpp-options:   -DEMBED_DATA_FILES
+     -- build-tools:   hsb2hs
+     other-modules: Text.Pandoc.Data
   if impl(ghc >= 7.0.1)
     Ghc-Options:   -rtsopts -Wall -fno-warn-unused-do-bind
   else
@@ -314,9 +314,6 @@ Library
                    Text.Pandoc.Slides,
                    Paths_pandoc
 
-  if flag(embed_data_files)
-    Other-Modules: Text.Pandoc.Data
-
   Buildable:       True
 
 Executable pandoc
diff --git a/src/Text/Pandoc/Data.hs b/src/Text/Pandoc/Data.hsb
similarity index 56%
rename from src/Text/Pandoc/Data.hs
rename to src/Text/Pandoc/Data.hsb
index 441fa5913..28e7f5112 100644
--- a/src/Text/Pandoc/Data.hs
+++ b/src/Text/Pandoc/Data.hsb
@@ -1,7 +1,7 @@
-{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE OverloadedStrings #-}
+-- to be processed using hsb2hs
 module Text.Pandoc.Data (dataFiles) where
-import Data.FileEmbed
 import qualified Data.ByteString as B
 
 dataFiles :: [(FilePath, B.ByteString)]
-dataFiles = $(embedDir "data")
+dataFiles = %blobs "data"