diff options
author | Jesse Rosenthal <jrosenthal@jhu.edu> | 2016-11-18 20:39:26 -0500 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2017-01-25 17:07:39 +0100 |
commit | f404412331bc6cf06c2cc248266f769391a57479 (patch) | |
tree | 7a226fffcacfeabec93304014e89be775511af3c /src/Text | |
parent | 2ea3e77172837505f021ae014c898a244bd9c436 (diff) | |
download | pandoc-f404412331bc6cf06c2cc248266f769391a57479.tar.gz |
Free: Add Typeable instance to PandocActionError
Diffstat (limited to 'src/Text')
-rw-r--r-- | src/Text/Pandoc/Free.hs | 5 |
1 files changed, 3 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Free.hs b/src/Text/Pandoc/Free.hs index 12ab95898..33cb50c88 100644 --- a/src/Text/Pandoc/Free.hs +++ b/src/Text/Pandoc/Free.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFunctor, DeriveDataTypeable #-} {- Copyright (C) 2016 Jesse Rosenthal <jrosenthal@jhu.edu> @@ -90,6 +90,7 @@ import qualified System.FilePath.Glob as IO (glob) import Control.Monad.State hiding (fail) import Control.Monad.Reader hiding (fail) import Data.Word (Word8) +import Data.Typeable data PandocActionF nxt = LookupEnv String (Maybe String -> nxt) @@ -219,7 +220,7 @@ data TestEnv = TestEnv { envEnv :: [(String, String)] } data TestException = TestException - deriving (Show) + deriving (Show, Typeable) instance E.Exception TestException |