Move Error type from Pages to Navigation as a candidate for MonadFail required by PDFContent defined there

This commit is contained in:
Tissevert 2020-02-15 10:22:42 +01:00
parent 923d1800b0
commit 4a6dbda7d3
2 changed files with 14 additions and 12 deletions

View File

@ -1,8 +1,10 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module PDF.Object.Navigation (
(//)
Error(..)
, (//)
, dictionaryById
, getDictionary
, getField
@ -13,6 +15,8 @@ module PDF.Object.Navigation (
) where
import Codec.Compression.Zlib (decompress)
import Control.Applicative (Alternative(..))
import Control.Monad (MonadPlus(..))
import Control.Monad.Reader (MonadReader(..))
import Control.Monad.Fail (MonadFail(..))
import Data.ByteString (ByteString)
@ -27,7 +31,12 @@ import PDF.Output (ObjectId)
import Prelude hiding (fail)
import Text.Printf (printf)
type PDFContent m = (MonadReader Content m, MonadFail m)
type PDFContent m = (Alternative m, MonadReader Content m, MonadFail m)
newtype Error a = Error {
runError :: Either String a
} deriving (Alternative, Functor, Applicative, Monad, MonadPlus)
instance MonadFail Error where
fail = Error . Left
castDictionary :: MonadFail m => Object -> m Dictionary
castDictionary (Direct (Dictionary aDict)) = return aDict

View File

@ -1,13 +1,12 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module PDF.Pages (
Page(..)
, get
, getAll
) where
import Control.Applicative (Alternative(..), (<|>))
import Control.Monad (MonadPlus(..), foldM)
import Control.Applicative ((<|>))
import Control.Monad (foldM)
import Control.Monad.Fail (MonadFail(..))
import Control.Monad.RWS (RWST(..), evalRWST, modify)
import qualified Control.Monad.RWS as RWS (get)
@ -24,25 +23,19 @@ import PDF.Object (
, Name(..)
,)
import PDF.Object.Navigation (
(//), dictionaryById, getDictionary, getField, follow, openStream, origin
Error(..), (//), dictionaryById, getDictionary, getField, follow, openStream, origin
)
import PDF.Output (ObjectId(..))
import Prelude hiding (fail)
import Text.Printf (printf)
type CachedFonts = Map ObjectId Font
newtype Error a = Error {
runError :: Either String a
} deriving (Alternative, Functor, Applicative, Monad, MonadPlus)
type T = RWST Content () CachedFonts Error
data Page = Page {
contents :: [Text]
, source :: ObjectId
}
instance MonadFail Error where
fail = Error . Left
getFontDictionary :: Dictionary -> T Dictionary
getFontDictionary pageDict =
((pageDict // ["Resources", "Font"]) >>= getDictionary)