Remove useless code equivalent to the identity in the right monad (IO)

This commit is contained in:
Tissevert 2020-04-17 12:26:07 +02:00
parent 266032950e
commit a64224d119
1 changed files with 8 additions and 15 deletions

View File

@ -1,14 +1,11 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module Main where
import Control.Monad.State (execState, execStateT)
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as BS (readFile, split, intercalate)
import qualified Data.ByteString.Lazy.Char8 as Lazy (writeFile)
import PDF (Layers(..), Document(..), UnifiedLayers(..), parseDocument, render)
import PDF.Box (Index(..), Maybe_(..), at, atAll, edit)
import PDF.Box (Index(..), Maybe_(..), at, atAll)
import PDF.Layer (Layer, Objects(..))
import PDF.Object.Navigation (StreamContent(..))
import PDF.TextRendering (TextRendering(..), update)
@ -29,18 +26,14 @@ revealLayer =
.atAll (Maybe_ StreamContent) $
return . revealText
reveal :: Document -> Document
reveal = execState $
edit .at UnifiedLayers $ revealLayer
reveal :: Document -> IO Document
reveal = at UnifiedLayers $ revealLayer
revealFirst :: Document -> Document
revealFirst document = maybe document id $ execStateT (
edit .at Layers .at(Index 0) $ revealLayer
) document
revealFirst :: Document -> IO Document
revealFirst = at Layers .at(Index 0) $ revealLayer
deepReveal :: Document -> Document
deepReveal = execState $
edit .atAll Layers $ revealLayer
deepReveal :: Document -> IO Document
deepReveal = atAll Layers $ revealLayer
main :: IO ()
main = do
@ -48,4 +41,4 @@ main = do
result <- parseDocument <$> BS.readFile inputPath
case result of
Left parseError -> hPutStrLn stderr $ show parseError
Right doc -> Lazy.writeFile outputPath . render $ reveal doc
Right doc -> Lazy.writeFile outputPath . render =<< reveal doc