Clean unneeded stuff separating the monadic type constraint from the actual monad stack used, one more step towrds MonadFail -> MonadError
This commit is contained in:
parent
a9d3e5d326
commit
40475a3093
2 changed files with 12 additions and 12 deletions
|
@ -1,6 +1,8 @@
|
|||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
|
||||
import Control.Monad.Fail (MonadFail(..))
|
||||
import Control.Monad.Reader (ReaderT, runReaderT)
|
||||
import Data.ByteString.Lazy.Char8 (ByteString)
|
||||
import qualified Data.ByteString.Char8 as BS (readFile)
|
||||
|
@ -10,15 +12,22 @@ import PDF.Box (Box(..))
|
|||
import PDF.Layer (Layer(..), unify)
|
||||
import PDF.Object (Object(..))
|
||||
import PDF.Object.Navigation (
|
||||
Clear(..), Error(..), Raw(..), (//), objectById, origin
|
||||
Clear(..), Raw(..), (//), objectById, origin
|
||||
)
|
||||
import PDF.Output (ObjectId(..), Output)
|
||||
import qualified PDF.Output as Output (render)
|
||||
import Prelude hiding (fail)
|
||||
import System.Environment (getArgs, getProgName)
|
||||
import System.Exit (die)
|
||||
import Text.Printf (printf)
|
||||
import Text.Read (readMaybe)
|
||||
|
||||
newtype Error a = Error {
|
||||
runError :: Either String a
|
||||
} deriving (Functor, Applicative, Monad)
|
||||
instance MonadFail Error where
|
||||
fail = Error . Left
|
||||
|
||||
decodedStream :: Object -> Object
|
||||
decodedStream object =
|
||||
maybe object id $ r Clear object >>= flip (w Raw) object
|
||||
|
|
|
@ -1,13 +1,11 @@
|
|||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE ConstraintKinds #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
module PDF.Object.Navigation (
|
||||
Error(..)
|
||||
Clear(..)
|
||||
, PDFContent
|
||||
, Clear(..)
|
||||
, Raw(..)
|
||||
, (./)
|
||||
, (//)
|
||||
|
@ -21,8 +19,6 @@ module PDF.Object.Navigation (
|
|||
) where
|
||||
|
||||
import Codec.Compression.Zlib (compress, decompress)
|
||||
import Control.Applicative (Alternative(..))
|
||||
import Control.Monad (MonadPlus(..))
|
||||
import Control.Monad.Reader (MonadReader(..))
|
||||
import Control.Monad.Fail (MonadFail(..))
|
||||
import Data.ByteString (ByteString)
|
||||
|
@ -39,12 +35,7 @@ import PDF.Output (ObjectId)
|
|||
import Prelude hiding (fail)
|
||||
import Text.Printf (printf)
|
||||
|
||||
type PDFContent m = (Alternative m, MonadReader Layer m, MonadFail m)
|
||||
newtype Error a = Error {
|
||||
runError :: Either String a
|
||||
} deriving (Alternative, Functor, Applicative, Monad, MonadPlus)
|
||||
instance MonadFail Error where
|
||||
fail = Error . Left
|
||||
type PDFContent m = (MonadReader Layer m, MonadFail m)
|
||||
type Component = String
|
||||
|
||||
getDictionary :: PDFContent m => Object -> m Dictionary
|
||||
|
|
Loading…
Reference in a new issue