Add a simple Box instance that exposes IndexedInstructions within a Content

This commit is contained in:
Tissevert 2020-03-05 17:44:38 +01:00
parent 90348c57d6
commit 6e245189fd
1 changed files with 10 additions and 1 deletions

View File

@ -2,6 +2,9 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module PDF.Content (
Content(..)
, ContentUnit(..)
@ -20,13 +23,14 @@ import Data.Attoparsec.ByteString.Char8 (sepBy)
import Data.ByteString (ByteString)
import Data.Map (Map, (!))
import qualified Data.Map as Map (empty, insert, size)
import PDF.Box (Box(..))
import PDF.Content.Operator (Instruction, operator)
import PDF.Object (blank, directObject)
import PDF.Output (Output(..), line)
import PDF.Parser (MonadParser, evalParser, string)
newtype InstructionId = InstructionId Int deriving (Eq, Ord, Show)
data Instructions = Instructions
type IndexedInstructions = Map InstructionId Instruction
data GraphicContextUnit =
@ -45,6 +49,11 @@ data Content = Content {
type InstructionParser m = (MonadParser m, MonadState IndexedInstructions m)
instance Monad m => Box m Instructions Content IndexedInstructions where
r Instructions = return . indexedInstructions
w Instructions indexedInstructions someContent =
return $ someContent {indexedInstructions}
register :: MonadState IndexedInstructions m => Instruction -> m InstructionId
register newInstruction = do
newInstructionID <- gets (InstructionId . Map.size)