module Data.Geometry.Ipe.IpeGeometry( RunWith(..) , runSimple , runSimple' , runSimpleIO , runSimpleIO' ) where import Data.Monoid import Data.Geometry.Ipe.IpeTypes import Data.Geometry.Ipe.IpeView import Data.Geometry.Ipe.IGC(IGC) import Data.Geometry.Ipe.ReadIpeGeometry import Data.Geometry.Ipe.WriteIpeGeometry import Data.Geometry.Ipe.Pickle -- | A class expressing that we can run a computation on the data stored in -- this part of the ipe drawing. A minimum implementation implements -- replaceIGC and extend. class IsConvertableToIGC c => RunWith c where -- | given a IGC, replace whatever I'm storing with the contents of the IGC replaceIGC :: Eq a => IGC a -> c a -> c a -- | add everything from the given IGC to whatever I'm storing allready. extend :: Eq a => IGC a -> c a -> c a -- | Given a function, run the function on my contents, and replace my contents -- with the results. runAndReplace :: Eq a => (IGC a -> IGC a) -> c a -> c a runAndReplace f o = let gc' = f . toIGC $ o in replaceIGC gc' o -- | Given a function, run the computation on my contents, and replace my contents -- with te results. runWith :: Eq a => (IGC a -> IGC a) -> c a -> c a runWith = runAndReplace -- | Given a function, run the computation on my contents, and store the result -- together with the stuff I'm allready storing. runAndExtend :: Eq a => (IGC a -> IGC a) -> c a -> c a runAndExtend f o = let gc = toIGC o gc' = f gc in extend (gc `mappend` gc') o instance RunWith Layer where replaceIGC gc (Layer n _) = Layer n gc -- | we do not really add stuff to this layer, but create a copy containing -- our stuff together with the new stuff. extend gc (Layer n _) = Layer (n++"'") gc instance RunWith ViewInstance where -- | replace the contents from the first layer, and drop the rest of the layers replaceIGC gc v = let l@(Layer n _) = head . layers $ v in ViewInstance (ViewDefinition [n] n) [replaceIGC gc l] extend gc v = let l = head . layers $ v in addLayer (extend gc l) v instance RunWith Page where replaceIGC gc _ = Page [] [] (toIpeObjects' gc) extend gc p = let v = head . ipeViews $ p in addToPage (extend gc v) p instance RunWith IpeDrawing where replaceIGC gc (Ipe pre sty []) = Ipe pre sty [extend gc emptyPage] replaceIGC gc (Ipe pre sty (p:_)) = Ipe pre sty [replaceIGC gc p] extend gc (Ipe pre sty []) = Ipe pre sty [extend gc emptyPage] extend gc (Ipe pre sty (p:pgs)) = Ipe pre sty $ extend gc p : pgs -- | shorthand to run a computation on a given drawing, and extend the input -- drawing with the results runSimple :: Eq a => (IGC a -> IGC a) -> IpeDrawing a -> IpeDrawing a runSimple = runAndExtend -- | Run a computation on an Ipe drawing runSimple' :: (IGC a -> b) -> IpeDrawing a -> b runSimple' f = f . toIGC -- | Load an drawing from a file path, and run the given computation on it. runSimpleIO :: (Eq a, Coordinate a) => (IGC a -> IGC a) -> FilePath -> IO (IpeDrawing a) runSimpleIO f = fmap (runSimple f) . loadDrawing -- | runSimpleIO' f inPath outPath runs loads a drawing from inPath, runs -- function f on it, extending the drawing with the result. The resulting -- drawing is stored in as outPath. runSimpleIO' :: (Eq a, Coordinate a) => (IGC a -> IGC a) -> FilePath -> FilePath -> IO () runSimpleIO' f inPath outPath = do d <- loadDrawing inPath storeDrawing (runSimple f d) outPath