From 4b7bc40e8ba5a0981bd6429f48fa6acdb21d5d69 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Mon, 15 Jan 2018 10:46:40 -0800
Subject: Renaming: Json -> JSON in modules and functions.

---
 pandoc.cabal                        |  2 +-
 src/Text/Pandoc/Filter.hs           |  4 +-
 src/Text/Pandoc/Filter/JSON.hs      | 97 +++++++++++++++++++++++++++++++++++++
 src/Text/Pandoc/Filter/Json.hs      | 97 -------------------------------------
 src/Text/Pandoc/Lua/Module/Utils.hs | 10 ++--
 5 files changed, 105 insertions(+), 105 deletions(-)
 create mode 100644 src/Text/Pandoc/Filter/JSON.hs
 delete mode 100644 src/Text/Pandoc/Filter/Json.hs

diff --git a/pandoc.cabal b/pandoc.cabal
index dc9b3d471..d8d2d7952 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -500,7 +500,7 @@ library
                    Text.Pandoc.BCP47,
                    Text.Pandoc.Class
   other-modules:   Text.Pandoc.Filter,
-                   Text.Pandoc.Filter.Json,
+                   Text.Pandoc.Filter.JSON,
                    Text.Pandoc.Filter.Lua,
                    Text.Pandoc.Filter.Path,
                    Text.Pandoc.Readers.Docx.Lists,
diff --git a/src/Text/Pandoc/Filter.hs b/src/Text/Pandoc/Filter.hs
index 30c99cc28..67b3a5f2c 100644
--- a/src/Text/Pandoc/Filter.hs
+++ b/src/Text/Pandoc/Filter.hs
@@ -39,7 +39,7 @@ import Data.Foldable (foldrM)
 import Text.Pandoc.Class (PandocIO)
 import Text.Pandoc.Definition (Pandoc)
 import Text.Pandoc.Options (ReaderOptions)
-import qualified Text.Pandoc.Filter.Json as JsonFilter
+import qualified Text.Pandoc.Filter.JSON as JSONFilter
 import qualified Text.Pandoc.Filter.Lua as LuaFilter
 
 data Filter = LuaFilter FilePath
@@ -54,7 +54,7 @@ applyFilters :: ReaderOptions
 applyFilters ropts filters args d = do
   foldrM ($) d $ map applyFilter filters
  where
-  applyFilter (JSONFilter f) = JsonFilter.apply ropts args f
+  applyFilter (JSONFilter f) = JSONFilter.apply ropts args f
   applyFilter (LuaFilter f)  = LuaFilter.apply ropts args f
 
 $(deriveJSON defaultOptions ''Filter)
diff --git a/src/Text/Pandoc/Filter/JSON.hs b/src/Text/Pandoc/Filter/JSON.hs
new file mode 100644
index 000000000..5772c2c41
--- /dev/null
+++ b/src/Text/Pandoc/Filter/JSON.hs
@@ -0,0 +1,97 @@
+{-
+Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
+
+This program is free software; you can redistribute it and/or modify
+it under the terms of the GNU General Public License as published by
+the Free Software Foundation; either version 2 of the License, or
+(at your option) any later version.
+
+This program is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+GNU General Public License for more details.
+
+You should have received a copy of the GNU General Public License
+along with this program; if not, write to the Free Software
+Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
+-}
+
+{- |
+   Module      : Text.Pandoc.Filter
+   Copyright   : Copyright (C) 2006-2018 John MacFarlane
+   License     : GNU GPL, version 2 or above
+
+   Maintainer  : John MacFarlane <jgm@berkeley@edu>
+   Stability   : alpha
+   Portability : portable
+
+Programmatically modifications of pandoc documents via JSON filters.
+-}
+module Text.Pandoc.Filter.JSON (apply) where
+
+import Control.Monad (unless, when)
+import Control.Monad.Trans (MonadIO (liftIO))
+import Data.Aeson (eitherDecode', encode)
+import Data.Char (toLower)
+import Data.Maybe (isNothing)
+import System.Directory (executable, doesFileExist, findExecutable,
+                         getPermissions)
+import System.Environment (getEnvironment)
+import System.Exit (ExitCode (..))
+import System.FilePath ((</>), takeExtension)
+import Text.Pandoc.Class (PandocIO)
+import Text.Pandoc.Error (PandocError (PandocFilterError))
+import Text.Pandoc.Definition (Pandoc)
+import Text.Pandoc.Filter.Path (expandFilterPath)
+import Text.Pandoc.Options (ReaderOptions)
+import Text.Pandoc.Process (pipeProcess)
+import Text.Pandoc.Shared (pandocVersion)
+import qualified Control.Exception as E
+import qualified Text.Pandoc.UTF8 as UTF8
+
+apply :: ReaderOptions
+      -> [String]
+      -> FilePath
+      -> Pandoc
+      -> PandocIO Pandoc
+apply ropts args f d = do
+  f' <- expandFilterPath f
+  liftIO $ externalFilter ropts f' args d
+
+externalFilter :: MonadIO m
+               => ReaderOptions -> FilePath -> [String] -> Pandoc -> m Pandoc
+externalFilter ropts f args' d = liftIO $ do
+  exists <- doesFileExist f
+  isExecutable <- if exists
+                     then executable <$> getPermissions f
+                     else return True
+  let (f', args'') = if exists
+                        then case map toLower (takeExtension f) of
+                                  _      | isExecutable -> ("." </> f, args')
+                                  ".py"  -> ("python", f:args')
+                                  ".hs"  -> ("runhaskell", f:args')
+                                  ".pl"  -> ("perl", f:args')
+                                  ".rb"  -> ("ruby", f:args')
+                                  ".php" -> ("php", f:args')
+                                  ".js"  -> ("node", f:args')
+                                  ".r"   -> ("Rscript", f:args')
+                                  _      -> (f, args')
+                        else (f, args')
+  unless (exists && isExecutable) $ do
+    mbExe <- findExecutable f'
+    when (isNothing mbExe) $
+      E.throwIO $ PandocFilterError f ("Could not find executable " ++ f')
+  env <- getEnvironment
+  let env' = Just
+           ( ("PANDOC_VERSION", pandocVersion)
+           : ("PANDOC_READER_OPTIONS", UTF8.toStringLazy (encode ropts))
+           : env )
+  (exitcode, outbs) <- E.handle filterException $
+                              pipeProcess env' f' args'' $ encode d
+  case exitcode of
+       ExitSuccess    -> either (E.throwIO . PandocFilterError f)
+                                   return $ eitherDecode' outbs
+       ExitFailure ec -> E.throwIO $ PandocFilterError f
+                           ("Filter returned error status " ++ show ec)
+ where filterException :: E.SomeException -> IO a
+       filterException e = E.throwIO $ PandocFilterError f (show e)
diff --git a/src/Text/Pandoc/Filter/Json.hs b/src/Text/Pandoc/Filter/Json.hs
deleted file mode 100644
index 681c52720..000000000
--- a/src/Text/Pandoc/Filter/Json.hs
+++ /dev/null
@@ -1,97 +0,0 @@
-{-
-Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-{- |
-   Module      : Text.Pandoc.Filter
-   Copyright   : Copyright (C) 2006-2018 John MacFarlane
-   License     : GNU GPL, version 2 or above
-
-   Maintainer  : John MacFarlane <jgm@berkeley@edu>
-   Stability   : alpha
-   Portability : portable
-
-Programmatically modifications of pandoc documents via JSON filters.
--}
-module Text.Pandoc.Filter.Json (apply) where
-
-import Control.Monad (unless, when)
-import Control.Monad.Trans (MonadIO (liftIO))
-import Data.Aeson (eitherDecode', encode)
-import Data.Char (toLower)
-import Data.Maybe (isNothing)
-import System.Directory (executable, doesFileExist, findExecutable,
-                         getPermissions)
-import System.Environment (getEnvironment)
-import System.Exit (ExitCode (..))
-import System.FilePath ((</>), takeExtension)
-import Text.Pandoc.Class (PandocIO)
-import Text.Pandoc.Error (PandocError (PandocFilterError))
-import Text.Pandoc.Definition (Pandoc)
-import Text.Pandoc.Filter.Path (expandFilterPath)
-import Text.Pandoc.Options (ReaderOptions)
-import Text.Pandoc.Process (pipeProcess)
-import Text.Pandoc.Shared (pandocVersion)
-import qualified Control.Exception as E
-import qualified Text.Pandoc.UTF8 as UTF8
-
-apply :: ReaderOptions
-      -> [String]
-      -> FilePath
-      -> Pandoc
-      -> PandocIO Pandoc
-apply ropts args f d = do
-  f' <- expandFilterPath f
-  liftIO $ externalFilter ropts f' args d
-
-externalFilter :: MonadIO m
-               => ReaderOptions -> FilePath -> [String] -> Pandoc -> m Pandoc
-externalFilter ropts f args' d = liftIO $ do
-  exists <- doesFileExist f
-  isExecutable <- if exists
-                     then executable <$> getPermissions f
-                     else return True
-  let (f', args'') = if exists
-                        then case map toLower (takeExtension f) of
-                                  _      | isExecutable -> ("." </> f, args')
-                                  ".py"  -> ("python", f:args')
-                                  ".hs"  -> ("runhaskell", f:args')
-                                  ".pl"  -> ("perl", f:args')
-                                  ".rb"  -> ("ruby", f:args')
-                                  ".php" -> ("php", f:args')
-                                  ".js"  -> ("node", f:args')
-                                  ".r"   -> ("Rscript", f:args')
-                                  _      -> (f, args')
-                        else (f, args')
-  unless (exists && isExecutable) $ do
-    mbExe <- findExecutable f'
-    when (isNothing mbExe) $
-      E.throwIO $ PandocFilterError f ("Could not find executable " ++ f')
-  env <- getEnvironment
-  let env' = Just
-           ( ("PANDOC_VERSION", pandocVersion)
-           : ("PANDOC_READER_OPTIONS", UTF8.toStringLazy (encode ropts))
-           : env )
-  (exitcode, outbs) <- E.handle filterException $
-                              pipeProcess env' f' args'' $ encode d
-  case exitcode of
-       ExitSuccess    -> either (E.throwIO . PandocFilterError f)
-                                   return $ eitherDecode' outbs
-       ExitFailure ec -> E.throwIO $ PandocFilterError f
-                           ("Filter returned error status " ++ show ec)
- where filterException :: E.SomeException -> IO a
-       filterException e = E.throwIO $ PandocFilterError f (show e)
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index ab29cc0c7..f8eb96dc7 100644
--- a/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -40,7 +40,7 @@ import Text.Pandoc.Lua.Util (addFunction, popValue)
 import qualified Data.Digest.Pure.SHA as SHA
 import qualified Data.ByteString.Lazy as BSL
 import qualified Foreign.Lua as Lua
-import qualified Text.Pandoc.Filter.Json as JsonFilter
+import qualified Text.Pandoc.Filter.JSON as JSONFilter
 import qualified Text.Pandoc.Shared as Shared
 
 -- | Push the "pandoc.utils" module to the lua stack.
@@ -49,7 +49,7 @@ pushModule mbDatadir = do
   Lua.newtable
   addFunction "hierarchicalize" hierarchicalize
   addFunction "normalize_date" normalizeDate
-  addFunction "run_json_filter" (runJsonFilter mbDatadir)
+  addFunction "run_json_filter" (runJSONFilter mbDatadir)
   addFunction "sha1" sha1
   addFunction "stringify" stringify
   addFunction "to_roman_numeral" toRomanNumeral
@@ -67,12 +67,12 @@ normalizeDate :: String -> Lua (Lua.Optional String)
 normalizeDate = return . Lua.Optional . Shared.normalizeDate
 
 -- | Run a JSON filter on the given document.
-runJsonFilter :: Maybe FilePath
+runJSONFilter :: Maybe FilePath
               -> Pandoc
               -> FilePath
               -> Lua.Optional [String]
               -> Lua NumResults
-runJsonFilter mbDatadir doc filterFile optArgs = do
+runJSONFilter mbDatadir doc filterFile optArgs = do
   args <- case Lua.fromOptional optArgs of
             Just x -> return x
             Nothing -> do
@@ -80,7 +80,7 @@ runJsonFilter mbDatadir doc filterFile optArgs = do
               (:[]) <$> popValue
   filterRes <- Lua.liftIO . runIO $ do
     setUserDataDir mbDatadir
-    JsonFilter.apply def args filterFile doc
+    JSONFilter.apply def args filterFile doc
   case filterRes of
     Left err -> Lua.raiseError (show err)
     Right d -> (1 :: NumResults) <$ Lua.push d
-- 
cgit v1.2.3