aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/App/Opt.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-10-06 23:48:34 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2019-10-06 23:48:34 -0700
commit6e537aeda82e851c312291a79bce314b89052d06 (patch)
tree895faf66180e3bde2b59e6632a89d97ecc92a1cb /src/Text/Pandoc/App/Opt.hs
parent3ef0cdd8f9dafcd9e4b5c1e5f82e31bed0c3d847 (diff)
downloadpandoc-6e537aeda82e851c312291a79bce314b89052d06.tar.gz
T.P.App.Opt: custom FromJSON instance for LineEnding.
So either CRLF or crlf will work.
Diffstat (limited to 'src/Text/Pandoc/App/Opt.hs')
-rw-r--r--src/Text/Pandoc/App/Opt.hs25
1 files changed, 17 insertions, 8 deletions
diff --git a/src/Text/Pandoc/App/Opt.hs b/src/Text/Pandoc/App/Opt.hs
index 3fe7cadf1..2c6c3c703 100644
--- a/src/Text/Pandoc/App/Opt.hs
+++ b/src/Text/Pandoc/App/Opt.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
@@ -31,16 +32,29 @@ import Text.Pandoc.Options (TopLevelDivision (TopLevelDefault),
ObfuscationMethod (NoObfuscation),
CiteMethod (Citeproc))
import Text.Pandoc.Shared (camelCaseToHyphenated)
+import qualified Data.Text as T
+import Data.Aeson (defaultOptions, Options(..), FromJSON(..), ToJSON(..),
+ Value(..))
#ifdef DERIVE_JSON_VIA_TH
-import Data.Aeson.TH (deriveJSON, defaultOptions, Options(..))
+import Data.Aeson.TH (deriveJSON)
#else
-import Data.Aeson (FromJSON (..), ToJSON (..), Options(..)
- defaultOptions, genericToEncoding)
+import Data.Aeson (genericToEncoding)
#endif
-- | The type of line-endings to be used when writing plain-text.
data LineEnding = LF | CRLF | Native deriving (Show, Generic)
+instance ToJSON LineEnding
+
+instance FromJSON LineEnding where
+ parseJSON (String t) =
+ case T.toLower t of
+ "lf" -> return LF
+ "crlf" -> return CRLF
+ "native" -> return Native
+ _ -> fail "Expecting LF, CRLF, or Native"
+ parseJSON _ = fail "Expecting string"
+
-- | Data structure for command line options.
data Opt = Opt
{ optTabStop :: Int -- ^ Number of spaces per tab
@@ -191,15 +205,10 @@ defaultOpts = Opt
#ifdef DERIVE_JSON_VIA_TH
-- see https://github.com/jgm/pandoc/pull/4083
-- using generic deriving caused long compilation times
-$(deriveJSON defaultOptions ''LineEnding)
$(deriveJSON
defaultOptions{ fieldLabelModifier =
camelCaseToHyphenated . drop 3 } ''Opt)
#else
-instance ToJSON LineEnding where
- toEncoding = genericToEncoding defaultOptions
-instance FromJSON LineEnding
-
instance ToJSON Opt where
toEncoding = genericToEncoding
defaultOptions{ fieldLabelModifier =