module Graphics.EasyRender.Internal where
import Graphics.EasyRender.Auxiliary
import Codec.Compression.Zlib
import Control.Monad.State
import qualified Data.ByteString.Lazy as ByteString
import Data.Char
import Data.List
import qualified Data.Map as Map
import Data.Map (Map)
import System.IO
import Text.Printf
import Control.Applicative (Applicative(..))
import Control.Monad (liftM, ap)
type X = Double
type Y = Double
data Color =
Color_RGB Double Double Double
| Color_Gray Double
deriving (Show)
data Basefont = TimesRoman | Helvetica
deriving (Show)
type Fontmetric = (Double, Map Char Double)
metric :: Basefont -> Fontmetric
metric TimesRoman = metric_timesroman
metric Helvetica = metric_helvetica
metric_timesroman :: Fontmetric
metric_timesroman = (0.5, m) where
m = Map.fromList $ map (\(n,w) -> (chr n, w))
[(32,0.25), (33,0.332031), (34,0.40625), (37,0.832031), (38,0.777344),
(39,0.332031), (40,0.332031), (41,0.332031), (44,0.25), (45,0.332031),
(46,0.25), (47,0.277344), (58,0.277344), (59,0.277344), (63,0.441406),
(64,0.917969), (65,0.71875), (66,0.664062), (67,0.664062), (68,0.71875),
(69,0.609375), (71,0.71875), (72,0.71875), (73,0.332031), (74,0.386719),
(75,0.71875), (76,0.609375), (77,0.886719), (78,0.71875), (79,0.71875),
(81,0.71875), (82,0.664062), (84,0.609375), (85,0.71875), (86,0.71875),
(87,0.941406), (88,0.71875), (89,0.71875), (90,0.609375), (91,0.332031),
(92,0.277344), (93,0.332031), (94,0.46875), (96,0.332031),
(97,0.441406), (99,0.441406), (101,0.441406), (102,0.332031),
(105,0.277344), (106,0.277344), (108,0.277344), (109,0.777344),
(114,0.332031), (115,0.386719), (116,0.277344), (119,0.71875),
(122,0.441406), (123,0.476562), (124,0.199219), (125,0.476562),
(161,0.332031), (164,0.164062), (169,0.179688), (170,0.441406),
(172,0.332031), (173,0.332031), (180,0.25), (182,0.449219),
(183,0.347656), (184,0.332031), (185,0.441406), (186,0.441406),
(188,1.0), (189,1.0), (191,0.441406), (193,0.332031), (194,0.332031),
(195,0.332031), (196,0.332031), (197,0.332031), (198,0.332031),
(199,0.332031), (200,0.332031), (202,0.332031), (203,0.332031),
(205,0.332031), (206,0.332031), (207,0.332031), (208,1.0),
(225,0.886719), (227,0.273438), (232,0.609375), (233,0.71875),
(234,0.886719), (241,0.664062), (245,0.277344), (248,0.277344),
(250,0.71875)]
metric_helvetica :: Fontmetric
metric_helvetica = (0.277344, m) where
m = Map.fromList $ map (\(n,w) -> (chr n, w))
[(34,0.351562), (35,0.554688), (36,0.554688), (37,0.886719),
(38,0.664062), (39,0.21875), (40,0.332031), (41,0.332031), (42,0.386719),
(43,0.582031), (45,0.332031), (48,0.554688), (49,0.554688),
(50,0.554688), (51,0.554688), (52,0.554688), (53,0.554688),
(54,0.554688), (55,0.554688), (56,0.554688), (57,0.554688),
(60,0.582031), (61,0.582031), (62,0.582031), (63,0.554688), (64,1.01172),
(65,0.664062), (66,0.664062), (67,0.71875), (68,0.71875), (69,0.664062),
(70,0.609375), (71,0.777344), (72,0.71875), (74,0.5), (75,0.664062),
(76,0.554688), (77,0.832031), (78,0.71875), (79,0.777344), (80,0.664062),
(81,0.777344), (82,0.71875), (83,0.664062), (84,0.609375), (85,0.71875),
(86,0.664062), (87,0.941406), (88,0.664062), (89,0.664062),
(90,0.609375), (94,0.46875), (95,0.554688), (96,0.21875), (97,0.554688),
(98,0.554688), (99,0.5), (100,0.554688), (101,0.554688), (103,0.554688),
(104,0.554688), (105,0.21875), (106,0.21875), (107,0.5), (108,0.21875),
(109,0.832031), (110,0.554688), (111,0.554688), (112,0.554688),
(113,0.554688), (114,0.332031), (115,0.5), (117,0.554688), (118,0.5),
(119,0.71875), (120,0.5), (121,0.5), (122,0.5), (123,0.332031),
(124,0.257812), (125,0.332031), (126,0.582031), (161,0.332031),
(162,0.554688), (163,0.554688), (164,0.164062), (165,0.554688),
(166,0.554688), (167,0.554688), (168,0.554688), (169,0.1875),
(170,0.332031), (171,0.554688), (172,0.332031), (173,0.332031),
(174,0.5), (175,0.5), (177,0.554688), (178,0.554688), (179,0.554688),
(182,0.535156), (183,0.347656), (184,0.21875), (185,0.332031),
(186,0.332031), (187,0.554688), (188,1.0), (189,1.0), (191,0.609375),
(193,0.332031), (194,0.332031), (195,0.332031), (196,0.332031),
(197,0.332031), (198,0.332031), (199,0.332031), (200,0.332031),
(202,0.332031), (203,0.332031), (205,0.332031), (206,0.332031),
(207,0.332031), (208,1.0), (225,1.0), (227,0.367188), (232,0.554688),
(233,0.777344), (234,1.0), (235,0.363281), (241,0.886719), (248,0.21875),
(249,0.609375), (250,0.941406), (251,0.609375)]
char_metric :: Fontmetric -> Char -> Double
char_metric (d, m) c = case Map.lookup c m of
Nothing -> d
Just w -> w
string_metric :: Fontmetric -> String -> Double
string_metric metric s = sum [ char_metric metric c | c <- s ]
data Font = Font Basefont Double
deriving (Show)
nominalsize :: Font -> Double
nominalsize (Font basefont pointsize) = pointsize
text_width :: Font -> String -> Double
text_width (Font basefont pointsize) s = pointsize * string_metric m s
where
m = metric basefont
type Alignment = Double
align_left :: Alignment
align_left = 0.0
align_center :: Alignment
align_center = 0.5
align_right :: Alignment
align_right = 1.0
data Document a =
Document_Return a
| Document_Page X Y (Draw (Document a))
| Document_Page_defer (Draw (X, Y, Document a))
instance Monad Document where
return a = Document_Return a
f >>= g = case f of
Document_Return a -> g a
Document_Page x y draw -> Document_Page x y draw' where
draw' = do
f' <- draw
return (f' >>= g)
Document_Page_defer draw -> Document_Page_defer draw' where
draw' = do
(x, y, f') <- draw
return (x, y, f' >>= g)
instance Applicative Document where
pure = return
(<*>) = ap
instance Functor Document where
fmap = liftM
document_skip :: Document a -> a
document_skip (Document_Return a) = a
document_skip (Document_Page x y draw) = document_skip a where
a = draw_skip draw
document_skip (Document_Page_defer draw) = document_skip a where
(x, y, a) = draw_skip draw
newpage :: X -> Y -> Draw a -> Document a
newpage x y draw =
Document_Page x y draw' where
draw' = do
a <- draw
return (Document_Return a)
newpage_defer :: Draw (X, Y, a) -> Document a
newpage_defer draw =
Document_Page_defer draw' where
draw' = do
(x, y, a) <- draw
return (x, y, Document_Return a)
endpage :: X -> Y -> Draw (X, Y, ())
endpage x y = do
return (x, y, ())
data DrawCommand =
Newpath
| Moveto X Y
| Lineto X Y
| Curveto X Y X Y X Y
| Closepath
| Clip
| Stroke
| Fill Color
| FillStroke Color
| TextBox Alignment Font Color X Y X Y Double String
| SetLineWidth Double
| SetColor Color
| Translate X Y
| Scale X Y
| Rotate Double
| Comment String
| Subroutine (Draw ()) [CustomDef]
deriving (Show)
data Draw a =
Draw_Return a
| Draw_Write DrawCommand (Draw a)
| Draw_Block (Draw (Draw a))
deriving (Show)
instance Monad Draw where
return a = Draw_Return a
f >>= g = case f of
Draw_Return a -> g a
Draw_Write cmd f' -> Draw_Write cmd (f' >>= g)
Draw_Block draw -> Draw_Block draw' where
draw' = do
f' <- draw
return (f' >>= g)
instance Applicative Draw where
pure = return
(<*>) = ap
instance Functor Draw where
fmap = liftM
draw_write :: DrawCommand -> Draw ()
draw_write cmd =
Draw_Write cmd (Draw_Return ())
draw_subroutine :: [CustomDef] -> Draw () -> Draw ()
draw_subroutine alt draw =
draw_write (Subroutine draw alt)
draw_block :: Draw a -> Draw a
draw_block draw =
Draw_Block draw' where
draw' = do
a <- draw
return (Draw_Return a)
draw_skip :: Draw a -> a
draw_skip (Draw_Return x) = x
draw_skip (Draw_Write cmd cont) = draw_skip cont
draw_skip (Draw_Block f) = draw_skip (draw_skip f)
newpath :: Draw ()
newpath = draw_write (Newpath)
moveto :: X -> Y -> Draw ()
moveto x y = draw_write (Moveto x y)
lineto :: X -> Y -> Draw ()
lineto x y = draw_write (Lineto x y)
curveto :: X -> Y -> X -> Y -> X -> Y -> Draw ()
curveto x1 y1 x2 y2 x y = draw_write (Curveto x1 y1 x2 y2 x y)
closepath :: Draw ()
closepath = draw_write (Closepath)
clip :: Draw ()
clip = draw_write (Clip)
stroke :: Draw ()
stroke = draw_write (Stroke)
fill :: Color -> Draw ()
fill color = draw_write (Fill color)
fillstroke :: Color -> Draw ()
fillstroke color = draw_write (FillStroke color)
textbox :: Alignment -> Font -> Color -> X -> Y -> X -> Y -> Double -> String -> Draw ()
textbox a f c x0 y0 x1 y1 b s = draw_write (TextBox a f c x0 y0 x1 y1 b s)
setlinewidth :: Double -> Draw ()
setlinewidth x = draw_write (SetLineWidth x)
setcolor :: Color -> Draw ()
setcolor color = draw_write (SetColor color)
translate :: X -> Y -> Draw ()
translate x y = draw_write (Translate x y)
scale :: X -> Y -> Draw ()
scale x y = draw_write (Scale x y)
rotate :: Double -> Draw ()
rotate angle = draw_write (Rotate angle)
comment :: String -> Draw ()
comment s = draw_write (Comment s)
block :: Draw a -> Draw a
block = draw_block
arc :: X -> Y -> Double -> Double -> Double -> Draw ()
arc x y r a1 a2 = draw_subroutine alt $ do
arc_internal False x y r r a1 a2
where
alt = [custom_ps $ printf "%f %f moveto\n" x0 y0 ++ printf "%f %f %f %f %f %s\n" x y r a1 a2 (if a1 <= a2 then "arc" else "arcn"),
custom_ascii $ printf "Arc %f %f %f %f %f\n" x y r a1 a2]
x0 = x + r * cos (pi/180 * a1)
y0 = y + r * sin (pi/180 * a1)
arc_append :: X -> Y -> Double -> Double -> Double -> Draw ()
arc_append x y r a1 a2 = draw_subroutine alt $ do
arc_internal True x y r r a1 a2
where
alt = [custom_ps $ printf "%f %f %f %f %f %s\n" x y r a1 a2 (if a1 <= a2 then "arc" else "arcn"),
custom_ascii $ printf "Arc_append %f %f %f %f %f\n" x y r a1 a2]
oval :: X -> Y -> X -> Y -> Draw ()
oval x y rx ry = draw_subroutine alt $ do
arc_internal False x y rx ry 0 360
closepath
where
alt = [custom_ps $ printf "%f %f %f %f oval\n" x y rx ry,
custom_ascii $ printf "Oval %f %f %f %f\n" x y rx ry]
arc_internal :: Bool -> X -> Y -> Double -> Double -> Double -> Double -> Draw ()
arc_internal connect x y rx ry a1 a2 = do
if connect then lineto x0 y0 else moveto x0 y0
sequence_ [ aux a | i <- [0..n1], let a = a1 + (fromIntegral i)*phi ]
where
(x0, y0) = point rx ry a1
n = int_ceiling (abs(a2 a1) / 90)
phi = if n > 0 then (a2 a1) / (fromIntegral n) else 0
alpha = 4/3 * c / (1+c)
c = cos' (phi/2)
point rx ry a = (x + rx * cos' a, y + ry * sin' a)
cos' x = cos (pi/180 * x)
sin' x = sin (pi/180 * x)
along (x0,y0) (x1,y1) alpha = (x0 + alpha * (x1x0), y0 + alpha * (y1y0))
aux a = curveto x1 y1 x2 y2 x3 y3
where
(x0, y0) = point rx ry a
(x3, y3) = point rx ry (a + phi)
(xp, yp) = point (rx/c) (ry/c) (a + phi/2)
(x1, y1) = along (x0, y0) (xp, yp) alpha
(x2, y2) = along (x3, y3) (xp, yp) alpha
rectangle :: X -> Y -> X -> Y -> Draw ()
rectangle x y w h = draw_subroutine alt def where
def = do
moveto x y
lineto x (y+h)
lineto (x+w) (y+h)
lineto (x+w) y
closepath
alt = [
custom_pdf $ printf "%f %f %f %f re\n" x y w h,
custom_ascii $ printf "Rectangle %f %f %f %f\n" x y w h
]
data Language =
Language_PS
| Language_PDF
| Language_ASCII
deriving (Show, Eq, Ord)
data CustomDef = CustomDef Language String
deriving (Show)
custom_ps :: String -> CustomDef
custom_ps s = CustomDef Language_PS s
custom_pdf :: String -> CustomDef
custom_pdf s = CustomDef Language_PDF s
custom_ascii :: String -> CustomDef
custom_ascii s = CustomDef Language_ASCII s
custom_lookup :: Language -> [CustomDef] -> Maybe String
custom_lookup lang defs =
case find (\(CustomDef l _) -> l==lang) defs of
Nothing -> Nothing
Just (CustomDef l s) -> Just s
data Custom = Custom {
creator :: String,
ps_defs :: String
}
custom :: Custom
custom = Custom {
creator = "",
ps_defs = ""
}
class Monad m => WriterMonad m where
wPutChar :: Char -> m ()
wPutChar c = wPutStr [c]
wPutStr :: String -> m ()
wPutStr s = sequence_ [ wPutChar c | c <- s ]
wPutStrLn :: (WriterMonad m) => String -> m ()
wPutStrLn s = do
wPutStr s
wPutChar '\n'
wprint :: (WriterMonad m, Show a) => a -> m ()
wprint x = wPutStrLn (show x)
instance WriterMonad IO where
wPutChar = putChar
wPutStr = putStr
data Writer a =
Writer_Return a
| Writer_PutChar Char (Writer a)
| Writer_PutStr String (Writer a)
instance Monad Writer where
return a = Writer_Return a
f >>= g = case f of
Writer_Return a -> g a
Writer_PutChar c f' -> Writer_PutChar c (f' >>= g)
Writer_PutStr s f' -> Writer_PutStr s (f' >>= g)
instance Applicative Writer where
pure = return
(<*>) = ap
instance Functor Writer where
fmap = liftM
instance WriterMonad Writer where
wPutChar c = Writer_PutChar c (Writer_Return ())
wPutStr s = Writer_PutStr s (Writer_Return ())
writer_to_pair :: Writer a -> (String, a)
writer_to_pair (Writer_Return a) = ("", a)
writer_to_pair (Writer_PutChar c cont) = (c:t, a) where
(t, a) = writer_to_pair cont
writer_to_pair (Writer_PutStr s cont) = (s ++ t, a) where
(t, a) = writer_to_pair cont
pair_to_writer :: (String, a) -> Writer a
pair_to_writer (s, a) = do
wPutStr s
return a
run_writer :: (WriterMonad m) => Writer a -> m a
run_writer (Writer_Return a) = return a
run_writer (Writer_PutChar c cont) = do
wPutChar c
run_writer cont
run_writer (Writer_PutStr s cont) = do
wPutStr s
run_writer cont
writer_to_file :: Handle -> Writer a -> IO a
writer_to_file h (Writer_Return a) = return a
writer_to_file h (Writer_PutChar c cont) = do
hPutChar h c
writer_to_file h cont
writer_to_file h (Writer_PutStr s cont) = do
hPutStr h s
writer_to_file h cont
writer_to_string :: Writer a -> String
writer_to_string = fst . writer_to_pair
newtype Boxed m a = Boxed (m a)
unbox :: Boxed m a -> m a
unbox (Boxed x) = x
instance Monad m => Monad (Boxed m) where
return a = Boxed (return a)
f >>= g = Boxed (unbox f >>= (unbox . g))
instance Applicative m => Applicative (Boxed m) where
pure a = Boxed (pure a)
f <*> x = Boxed (unbox f <*> unbox x)
instance Functor m => Functor (Boxed m) where
fmap f x = Boxed (fmap f (unbox x))
instance WriterMonad m => WriterMonad (Boxed m) where
wPutChar c = Boxed (wPutChar c)
wPutStr c = Boxed (wPutStr c)
instance MonadState s m => MonadState s (Boxed m) where
get = Boxed get
put s = Boxed (put s)
class Boxed_Curry fun args m res | fun -> args res m, args res m -> fun where
boxed_curry :: (args -> Boxed m res) -> fun
boxed_uncurry :: fun -> (args -> Boxed m res)
instance Boxed_Curry (Boxed m a) () m a where
boxed_curry g = g ()
boxed_uncurry x = const x
instance Boxed_Curry fun args m res => Boxed_Curry (a -> fun) (a, args) m res where
boxed_curry g x = boxed_curry (\xs -> g (x,xs))
boxed_uncurry f (x,xs) = boxed_uncurry (f x) xs
wprintf :: (Boxed_Curry fun args m (), WriterMonad m, Curry fun' args String, PrintfType fun') => String -> fun
wprintf fmt = g where
g = boxed_curry g'
g' args = wPutStr (f' args)
f' = muncurry f
f = printf fmt
with_printf :: (WriterMonad m) => Boxed m a -> m a
with_printf = unbox
with_filter :: (WriterMonad m) => (String -> String) -> Writer a -> m a
with_filter encoding = run_writer . pair_to_writer . (\(x,y) -> (encoding x, y)) . writer_to_pair
flate_filter :: String -> String
flate_filter = map chr . map fromIntegral . ByteString.unpack . compress . ByteString.pack . map fromIntegral . map ord
ensure_nl :: String -> String
ensure_nl "" = ""
ensure_nl s =
if last s == '\n' then s else s++"\n"
draw_to_ascii :: Draw a -> Writer a
draw_to_ascii (Draw_Return x) = return x
draw_to_ascii (Draw_Write cmd cont) = do
command_to_ascii cmd
draw_to_ascii cont
draw_to_ascii (Draw_Block f) = do
wPutStrLn "begin"
cont <- draw_to_ascii f
wPutStrLn "end"
draw_to_ascii cont
command_to_ascii :: DrawCommand -> Writer ()
command_to_ascii (Subroutine draw alt) =
case custom_lookup Language_ASCII alt of
Just out -> wPutStr (ensure_nl out)
Nothing -> draw_to_ascii draw
command_to_ascii cmd =
wprint cmd
document_to_ascii :: Document a -> Writer a
document_to_ascii (Document_Return x) = return x
document_to_ascii (Document_Page x y draw) = do
wPutStrLn $ "startpage " ++ show x ++ " " ++ show y
cont <- draw_to_ascii draw
wPutStrLn "endpage"
document_to_ascii cont
document_to_ascii (Document_Page_defer draw) = do
wPutStrLn "startpage (atend)"
(x, y, cont) <- draw_to_ascii draw
wPutStrLn $ "endpage " ++ show x ++ " " ++ show y
document_to_ascii cont
render_ascii :: Document a -> Writer a
render_ascii = document_to_ascii
ps_escape :: String -> String
ps_escape [] = []
ps_escape ('\\' : t) = '\\' : '\\' : ps_escape t
ps_escape ('(' : t) = '\\' : '(' : ps_escape t
ps_escape (')' : t) = '\\' : ')' : ps_escape t
ps_escape (h : t) = h : ps_escape t
remove_nl :: String -> String
remove_nl = map f where
f '\n' = ' '
f '\r' = ' '
f x = x
type Page = Integer
data PS_State = PS_State !X !Y !Page
ps_state_empty :: PS_State
ps_state_empty = PS_State 0 0 0
type PSWriter = Boxed (StateT PS_State Writer)
instance WriterMonad (StateT PS_State Writer) where
wPutChar c = lift (wPutChar c)
wPutStr s = lift (wPutStr s)
pswriter_run :: PSWriter a -> Writer a
pswriter_run f = evalStateT (unbox f) ps_state_empty
ps_get_bbox :: PSWriter (X, Y)
ps_get_bbox = do
PS_State x y _ <- get
return (x, y)
ps_add_bbox :: X -> Y -> PSWriter ()
ps_add_bbox x y = do
PS_State x' y' p <- get
put (PS_State (x `max` x') (y `max` y') p)
ps_get_pagecount :: PSWriter Page
ps_get_pagecount = do
PS_State _ _ p <- get
return p
ps_next_page :: PSWriter Page
ps_next_page = do
PS_State x y p <- get
put (PS_State x y (p+1))
return (p+1)
draw_to_ps :: Draw a -> PSWriter a
draw_to_ps (Draw_Return x) = return x
draw_to_ps (Draw_Write cmd cont) = do
command_to_ps cmd
draw_to_ps cont
draw_to_ps (Draw_Block body) = do
wPutStrLn "gsave"
cont <- draw_to_ps body
wPutStrLn "grestore"
draw_to_ps cont
color_to_ps :: Color -> PSWriter ()
color_to_ps (Color_RGB r g b) = do
wprintf "%f %f %f setrgbcolor\n" r g b
color_to_ps (Color_Gray v) = do
wprintf "%f setgray\n" v
font_to_ps :: Font -> PSWriter ()
font_to_ps (Font TimesRoman pt) = do
wprintf "/Times-Roman findfont %f scalefont setfont\n" pt
font_to_ps (Font Helvetica pt) = do
wprintf "/Helvetica findfont %f scalefont setfont\n" pt
command_to_ps :: DrawCommand -> PSWriter ()
command_to_ps (Newpath) = do
wPutStrLn "newpath"
command_to_ps (Moveto x y) = do
wprintf "%f %f moveto\n" x y
command_to_ps (Lineto x y) = do
wprintf "%f %f lineto\n" x y
command_to_ps (Curveto x1 y1 x2 y2 x y) = do
wprintf "%f %f %f %f %f %f curveto\n" x1 y1 x2 y2 x y
command_to_ps (Closepath) = do
wPutStrLn "closepath"
command_to_ps (Stroke) = do
wPutStrLn "stroke"
command_to_ps (Clip) = do
wPutStrLn "clip"
wPutStrLn "newpath"
command_to_ps (Fill color) = do
wPutStrLn "gsave"
color_to_ps color
wPutStrLn "fill"
wPutStrLn "grestore"
wPutStrLn "newpath"
command_to_ps (FillStroke color) = do
wPutStrLn "gsave"
color_to_ps color
wPutStrLn "fill"
wPutStrLn "grestore"
wPutStrLn "stroke"
command_to_ps (TextBox align font color x0 y0 x1 y1 b s) = do
wPutStrLn "gsave"
font_to_ps font
color_to_ps color
wprintf "(%s) %f %f %f %f %f %f textbox\n" (ps_escape s) x0 y0 x1 y1 align yshift
wPutStrLn "grestore"
where
yshift = b * nominalsize font
command_to_ps (SetLineWidth x) = do
wprintf "%f setlinewidth\n" x
command_to_ps (SetColor color) = do
color_to_ps color
command_to_ps (Translate x y) = do
wprintf "%f %f translate\n" x y
command_to_ps (Scale x y) = do
wprintf "%f %f scale\n" x y
command_to_ps (Rotate angle) = do
wprintf "%f rotate\n" angle
command_to_ps (Comment s) = do
wprintf "%% %s\n" (remove_nl s)
command_to_ps (Subroutine draw alt) =
case custom_lookup Language_PS alt of
Just out -> wprintf "%s" (ensure_nl out)
Nothing -> draw_to_ps draw
document_to_ps :: Custom -> Document a -> PSWriter a
document_to_ps custom document = do
wPutStrLn "%!PS-Adobe-3.0"
wPutStrLn "%%LanguageLevel: 2"
when (creator custom /= "") $ do
wprintf "%%%%Creator: %s\n" (creator custom)
wPutStrLn "%%BoundingBox: (atend)"
wPutStrLn "%%HiResBoundingBox: (atend)"
wPutStrLn "%%Pages: (atend)"
wPutStrLn "%%EndComments"
wPutStrLn "%%BeginSetup"
wprintf "%s" global_ps_defs
when (ps_defs custom /= "") $ do
wprintf "%s" (ensure_nl $ ps_defs custom)
wPutStrLn "%%EndSetup"
a <- pages_to_ps document
(x, y) <- ps_get_bbox
pagecount <- ps_get_pagecount
wPutStrLn "%%Trailer"
wprintf "%%%%BoundingBox: 0 0 %d %d\n" (int_ceiling x) (int_ceiling y)
wprintf "%%%%HiResBoundingBox: 0 0 %f %f\n" x y
wprintf "%%%%Pages: %d\n" pagecount
wPutStrLn "%%EOF"
return a
global_ps_defs :: String
global_ps_defs = "/textbox { /b exch def /align exch def /y1 exch def /x1 exch def /y0 exch def /x0 exch def /dx x1 x0 sub def /dy y1 y0 sub def /d dx dx mul dy dy mul add sqrt def dup stringwidth pop /w exch def /fontscale w d le {d} {w} ifelse def gsave [dx dy dy neg dx x0 y0] concat 1 fontscale div dup scale fontscale w sub align mul b moveto show grestore } bind def\n"
++
"/oval { /ry exch def /rx exch def /y exch def /x exch def /a 0.552285 def x rx add y moveto x rx add y a ry mul add x rx a mul add y ry add x y ry add curveto x rx a mul sub y ry add x rx sub y ry a mul add x rx sub y curveto x rx sub y a ry mul sub x rx a mul sub y ry sub x y ry sub curveto x rx a mul add y ry sub x rx add y ry a mul sub x rx add y curveto closepath } bind def\n"
pages_to_ps :: Document a -> PSWriter a
pages_to_ps (Document_Return a) = return a
pages_to_ps (Document_Page x y draw) = do
page <- ps_next_page
ps_add_bbox x y
wprintf "%%%%Page: %d %d\n" page page
wprintf "%%%%PageBoundingBox: 0 0 %d %d\n" (int_ceiling x) (int_ceiling y)
wprintf "%%%%PageHiResBoundingBox: 0 0 %f %f\n" x y
wPutStrLn "save"
cont <- draw_to_ps draw
wPutStrLn "showpage"
wPutStrLn "restore"
pages_to_ps cont
pages_to_ps (Document_Page_defer draw) = do
page <- ps_next_page
wprintf "%%%%Page: %d %d\n" page page
wPutStrLn "%%PageBoundingBox: (atend)"
wPutStrLn "%%PageHiResBoundingBox: (atend)"
(x, y, cont) <- draw_to_ps draw
wPutStrLn "showpage"
wPutStrLn "%%PageTrailer"
wprintf "%%%%PageBoundingBox: 0 0 %d %d\n" (int_ceiling x) (int_ceiling y)
wprintf "%%%%PageHiResBoundingBox: 0 0 %f %f\n" x y
ps_add_bbox x y
pages_to_ps cont
render_ps_custom :: Custom -> Document a -> Writer a
render_ps_custom custom doc =
pswriter_run (document_to_ps custom doc)
document_to_eps :: Custom -> Page -> Document a -> PSWriter a
document_to_eps custom page (Document_Return a) =
error "document_to_eps: requested page does not exist"
document_to_eps custom page (Document_Page x y draw)
| page == 1 = do
wPutStrLn "%!PS-Adobe-3.0 EPSF-3.0"
wPutStrLn "%%LanguageLevel: 2"
when (creator custom /= "") $ do
wprintf "%%%%Creator: %s\n" (creator custom)
wprintf "%%%%BoundingBox: 0 0 %d %d\n" (int_ceiling x) (int_ceiling y)
wprintf "%%%%HiResBoundingBox: 0 0 %f %f\n" x y
wPutStrLn "%%Pages: 1"
wPutStrLn "%%EndComments"
wPutStrLn "%%Page: 1 1"
wPutStrLn "save"
wprintf "%s" global_ps_defs
when (ps_defs custom /= "") $ do
wprintf "%s" (ensure_nl $ ps_defs custom)
cont <- draw_to_ps draw
wPutStrLn "restore"
wPutStrLn "%%EOF"
let a = document_skip cont
return a
| otherwise = do
let cont = draw_skip draw
document_to_eps custom (page1) cont
document_to_eps custom page (Document_Page_defer draw)
| page == 1 = do
wPutStrLn "%!PS-Adobe-3.0 EPSF-3.0"
wPutStrLn "%%LanguageLevel: 2"
when (creator custom /= "") $ do
wprintf "%%%%Creator: %s\n" (creator custom)
wPutStrLn "%%BoundingBox: (atend)"
wPutStrLn "%%HiResBoundingBox: (atend)"
wPutStrLn "%%Pages: 1"
wPutStrLn "%%EndComments"
wPutStrLn "%%Page: 1 1"
wPutStrLn "save"
wprintf "%s" global_ps_defs
when (ps_defs custom /= "") $ do
wprintf "%s" (ensure_nl $ ps_defs custom)
(x, y, cont) <- draw_to_ps draw
wPutStrLn "restore"
wPutStrLn "%%Trailer"
wprintf "%%%%BoundingBox: 0 0 %d %d\n" (int_ceiling x) (int_ceiling y)
wprintf "%%%%HiResBoundingBox: 0 0 %f %f\n" x y
wPutStrLn "%%EOF"
let a = document_skip cont
return a
| otherwise = do
let (_, _, cont) = draw_skip draw
document_to_eps custom (page1) cont
render_eps_custom :: Custom -> Page -> Document a -> Writer a
render_eps_custom custom page doc =
pswriter_run (document_to_eps custom page doc)
pdf_escape :: String -> String
pdf_escape [] = []
pdf_escape ('\\' : t) = '\\' : '\\' : pdf_escape t
pdf_escape ('(' : t) = '\\' : '(' : pdf_escape t
pdf_escape (')' : t) = '\\' : ')' : pdf_escape t
pdf_escape (h : t) = h : pdf_escape t
type Filepos = Integer
type Object = Integer
data PDF_State = PDF_State {
pdf_filepos :: !Filepos,
pdf_obj :: !Object,
pdf_xref :: !(Map Object Filepos),
pdf_page :: !Page,
pdf_pagetable :: !(Map Page Object),
pdf_font :: !Integer,
pdf_fonttable :: !(Map String String)
}
pdf_state_empty :: PDF_State
pdf_state_empty = PDF_State {
pdf_filepos = 0,
pdf_obj = 0,
pdf_xref = Map.empty,
pdf_page = 0,
pdf_pagetable = Map.empty,
pdf_font = 0,
pdf_fonttable = Map.empty
}
type RawPDFWriter = StateT PDF_State Writer
instance WriterMonad RawPDFWriter where
wPutChar c = do
lift (wPutChar c)
pdf_inc_filepos 1
wPutStr s = do
lift (wPutStr s)
pdf_inc_filepos (toInteger $ length s)
type PDFWriter = Boxed RawPDFWriter
pdfwriter_run :: PDFWriter a -> Writer a
pdfwriter_run f = do
evalStateT (unbox f) pdf_state_empty
pdf_get_filepos :: PDFWriter Filepos
pdf_get_filepos = do
s <- get
return $ pdf_filepos s
pdf_inc_filepos :: Integer -> RawPDFWriter ()
pdf_inc_filepos n = do
s <- get
let p = pdf_filepos s
put s { pdf_filepos = p+n }
pdf_get_objcount :: PDFWriter Object
pdf_get_objcount = do
s <- get
return $ pdf_obj s
pdf_next_object :: PDFWriter Object
pdf_next_object = do
s <- get
let o = pdf_obj s
put s { pdf_obj = o+1 }
return $ o+1
pdf_add_xref :: Object -> Filepos -> PDFWriter ()
pdf_add_xref obj pos = do
s <- get
let xref = pdf_xref s
put s { pdf_xref = Map.insert obj pos xref }
pdf_get_xref :: PDFWriter (Map Object Filepos)
pdf_get_xref = do
s <- get
return $ pdf_xref s
pdf_get_pagecount :: PDFWriter Page
pdf_get_pagecount = do
s <- get
return $ pdf_page s
pdf_next_page :: PDFWriter Page
pdf_next_page = do
s <- get
let p = pdf_page s
put s { pdf_page = p+1 }
return $ p+1
pdf_add_pagetable :: Page -> Object -> PDFWriter ()
pdf_add_pagetable page obj = do
s <- get
let pagetable = pdf_pagetable s
put s { pdf_pagetable = Map.insert page obj pagetable }
pdf_get_pagetable :: PDFWriter (Map Page Object)
pdf_get_pagetable = do
s <- get
return $ pdf_pagetable s
pdf_find_font :: String -> PDFWriter String
pdf_find_font font = do
s <- get
let t = pdf_fonttable s
case Map.lookup font t of
Nothing -> do
let f = pdf_font s
let fontname = "F" ++ show f
put s { pdf_font = f+1, pdf_fonttable = Map.insert font fontname t }
return fontname
Just fontname -> return fontname
pdf_get_fonttable :: PDFWriter (Map String String)
pdf_get_fonttable = do
s <- get
return $ pdf_fonttable s
pdf_clear_fonttable :: PDFWriter ()
pdf_clear_fonttable = do
s <- get
put s { pdf_font = 0, pdf_fonttable = Map.empty }
with_filter_pdf :: (String -> String) -> PDFWriter a -> PDFWriter a
with_filter_pdf encoding body = do
s <- get
let s' = s { pdf_filepos = 0 }
(a, s'') <- with_filter encoding $ do
runStateT (unbox body) s'
pos <- pdf_get_filepos
put s'' { pdf_filepos = pos }
return a
pdf_deferred_object :: Object -> PDFWriter a -> PDFWriter a
pdf_deferred_object obj body = do
pos <- pdf_get_filepos
pdf_add_xref obj pos
wprintf "%d 0 obj\n" obj
a <- body
wprintf "endobj\n"
return a
pdf_define_object :: PDFWriter a -> PDFWriter Object
pdf_define_object body = do
obj <- pdf_next_object
pdf_deferred_object obj body
return obj
pdf_deferred_stream :: Object -> PDFWriter a -> PDFWriter a
pdf_deferred_stream obj body = do
length_obj <- pdf_next_object
(a, len) <- pdf_deferred_object obj $ do
wprintf "<</Length %s>>\n" (objref length_obj)
wPutStr "stream\n"
x0 <- pdf_get_filepos
a <- body
x1 <- pdf_get_filepos
wPutStr "\n"
wPutStr "endstream\n"
return (a, x1x0)
pdf_deferred_object length_obj $ do
wprintf "%d\n" len
return a
pdf_define_stream :: PDFWriter a -> PDFWriter Object
pdf_define_stream body = do
obj <- pdf_next_object
pdf_deferred_stream obj body
return obj
pdf_deferred_flate_stream :: Object -> PDFWriter a -> PDFWriter a
pdf_deferred_flate_stream obj body = do
length_obj <- pdf_next_object
(a, len) <- pdf_deferred_object obj $ do
wprintf "<</Length %s/Filter/FlateDecode>>\n" (objref length_obj)
wPutStr "stream\n"
x0 <- pdf_get_filepos
a <- with_filter_pdf flate_filter body
x1 <- pdf_get_filepos
wPutStr "\n"
wPutStr "endstream\n"
return (a, x1x0)
pdf_deferred_object length_obj $ do
wprintf "%d\n" len
return a
objref :: Object -> String
objref n =
show n ++ " 0 R"
wprintf_xref_entry :: Filepos -> Integer -> Char -> PDFWriter ()
wprintf_xref_entry pos gen c =
wprintf "%010u %05u %c \n" pos gen c
wprintf_xref :: PDFWriter Filepos
wprintf_xref = do
xref <- pdf_get_xref
n <- pdf_get_objcount
pos <- pdf_get_filepos
wprintf "xref\n"
wprintf "0 %d\n" (n+1)
wprintf_xref_entry 0 65535 'f'
sequence_ [ case Map.lookup obj xref of
Nothing -> wprintf_xref_entry 0 0 'f'
Just p -> wprintf_xref_entry p 0 'n' | obj <- [1..n] ]
return pos
fillcolor_to_pdf :: Color -> PDFWriter ()
fillcolor_to_pdf (Color_RGB r g b) = do
wprintf "%f %f %f rg\n" r g b
fillcolor_to_pdf (Color_Gray v) = do
wprintf "%f g\n" v
strokecolor_to_pdf :: Color -> PDFWriter ()
strokecolor_to_pdf (Color_RGB r g b) = do
wprintf "%f %f %f RG\n" r g b
strokecolor_to_pdf (Color_Gray v) = do
wprintf "%f G\n" v
font_to_pdf :: Font -> PDFWriter ()
font_to_pdf (Font TimesRoman pt) = do
fn <- pdf_find_font "Times-Roman"
wprintf "/%s %f Tf\n" fn pt
font_to_pdf (Font Helvetica pt) = do
fn <- pdf_find_font "Helvetica"
wprintf "/%s %f Tf\n" fn pt
command_to_pdf :: DrawCommand -> PDFWriter ()
command_to_pdf (Newpath) = do
wPutStr "n\n"
command_to_pdf (Moveto x y) = do
wprintf "%f %f m\n" x y
command_to_pdf (Lineto x y) = do
wprintf "%f %f l\n" x y
command_to_pdf (Curveto x1 y1 x2 y2 x y) = do
wprintf "%f %f %f %f %f %f c\n" x1 y1 x2 y2 x y
command_to_pdf (Closepath) = do
wPutStr "h\n"
command_to_pdf (Stroke) = do
wPutStr "S\n"
command_to_pdf (Clip) = do
wPutStr "W\n"
command_to_pdf (Fill color) = do
fillcolor_to_pdf color
wPutStr "f\n"
command_to_pdf (FillStroke color) = do
fillcolor_to_pdf color
wPutStr "B\n"
command_to_pdf (TextBox align font color x0 y0 x1 y1 b s) = do
let w = text_width font s
dx = x1 x0
dy = y1 y0
d = sqrt (dx*dx + dy*dy)
f = max w d
dxf = if f > 0 then dx/f else 1
dyf = if f > 0 then dy/f else 1
xshift = (fw) * align
yshift = b * nominalsize font
wPutStr "BT\n"
font_to_pdf font
wprintf "%f %f %f %f %f %f Tm\n" dxf dyf (dyf) dxf (x0 + xshift*dxf yshift*dyf) (y0 + xshift*dyf + yshift*dxf)
fillcolor_to_pdf color
wprintf "(%s) Tj\n" (pdf_escape s)
wPutStr "ET\n"
command_to_pdf (SetLineWidth x) = do
wprintf "%f w\n" x
command_to_pdf (SetColor color) = do
strokecolor_to_pdf color
command_to_pdf (Translate x y) = do
wprintf "1 0 0 1 %f %f cm\n" x y
command_to_pdf (Scale x y) = do
wprintf "%f 0 0 %f 0 0 cm\n" x y
command_to_pdf (Rotate angle) = do
wprintf "%f %f %f %f 0 0 cm\n" c s (s) c where
c = cos (pi/180 * angle)
s = sin (pi/180 * angle)
command_to_pdf (Comment s) = do
wprintf "%% %s\n" (remove_nl s)
command_to_pdf (Subroutine draw alt) = do
case custom_lookup Language_PDF alt of
Just out -> wprintf "%s" (ensure_nl out)
Nothing -> draw_to_pdf draw
draw_to_pdf :: Draw a -> PDFWriter a
draw_to_pdf (Draw_Return x) = return x
draw_to_pdf (Draw_Write cmd cont) = do
command_to_pdf cmd
draw_to_pdf cont
draw_to_pdf (Draw_Block body) = do
wprintf "q\n"
cont <- draw_to_pdf body
wprintf "Q\n"
draw_to_pdf cont
pages_to_pdf :: Object -> Document a -> PDFWriter a
pages_to_pdf pagetree_obj (Document_Return a) = return a
pages_to_pdf pagetree_obj (Document_Page x y draw) = do
let sc = 14328 / maximum [x, y, 14328]
page <- pdf_next_page
wprintf "%% Page %d\n" page
pdf_clear_fonttable
contents_obj <- pdf_next_object
cont <- pdf_deferred_flate_stream contents_obj $ do
when (sc /= 1.0) $ do
draw_to_pdf $ do
scale sc sc
draw_to_pdf draw
fonttable_obj <- pdf_define_object $ do
fonttable <- pdf_get_fonttable
wprintf "<<\n"
sequence_ [ wprintf "/%s<</Type/Font/Subtype/Type1/BaseFont/%s>>\n" x f | (f,x) <- Map.toList fonttable ]
wprintf ">>\n"
page_obj <- pdf_define_object $ do
wprintf "<</Type/Page/Parent %s/Resources<</ProcSet[/PDF]/Font %s>>/MediaBox[0 0 %f %f]/Contents %s>>\n" (objref pagetree_obj) (objref fonttable_obj) (x*sc) (y*sc) (objref contents_obj)
pdf_add_pagetable page page_obj
pages_to_pdf pagetree_obj cont
pages_to_pdf pagetree_obj (Document_Page_defer draw) = do
page <- pdf_next_page
wprintf "%% Page %d\n" page
pdf_clear_fonttable
contents_obj <- pdf_next_object
(x, y, cont) <- pdf_deferred_stream contents_obj $ do
draw_to_pdf draw
fonttable_obj <- pdf_define_object $ do
fonttable <- pdf_get_fonttable
wprintf "<<\n"
sequence_ [ wprintf "/%s<</Type/Font/Subtype/Type1/BaseFont/%s>>\n" x f | (f,x) <- Map.toList fonttable ]
wprintf ">>\n"
let sc = 14328 / maximum [x, y, 14328]
scaled_contents_obj <-
if sc == 1.0 then do
return contents_obj
else do
scale_obj <- pdf_define_stream $ do
draw_to_pdf $ do
scale sc sc
obj <- pdf_define_object $ do
wprintf "[%s %s]\n" (objref scale_obj) (objref contents_obj)
return obj
page_obj <- pdf_define_object $ do
wprintf "<</Type/Page/Parent %s/Resources<</ProcSet[/PDF]/Font %s>>/MediaBox[0 0 %f %f]/Contents %s>>\n" (objref pagetree_obj) (objref fonttable_obj) (x*sc) (y*sc) (objref scaled_contents_obj)
pdf_add_pagetable page page_obj
pages_to_pdf pagetree_obj cont
document_to_pdf :: Custom -> Document a -> PDFWriter a
document_to_pdf custom document = do
wprintf "%%PDF-1.3\n"
info_obj <- pdf_define_object $ do
if (creator custom /= "")
then wprintf "<</Creator(%s)>>\n" (pdf_escape $ creator custom)
else wprintf "<<>>\n"
pagetree_obj <- pdf_next_object
catalog_obj <- pdf_define_object $ do
wprintf "<</Type/Catalog/Pages %s>>\n" (objref pagetree_obj)
a <- pages_to_pdf pagetree_obj document
pages <- pdf_get_pagecount
pagetable <- pdf_get_pagetable
pdf_deferred_object pagetree_obj $ do
wprintf "<</Type/Pages/Count %d/Kids[\n" pages
sequence_ [ wprintf "%s\n" (objref o) | o <- Map.elems pagetable ]
wprintf "]>>\n"
xref_pos <- wprintf_xref
wprintf "trailer\n"
objcount <- pdf_get_objcount
wprintf "<</Size %d/Root %s/Info %s>>\n" objcount (objref catalog_obj) (objref info_obj)
wprintf "startxref\n"
wprintf "%d\n" xref_pos
wprintf "%%%%EOF\n"
return a
render_pdf_custom :: Custom -> Document a -> Writer a
render_pdf_custom custom doc = pdfwriter_run (document_to_pdf custom doc)
data RenderFormat =
Format_PS
| Format_PDF
| Format_EPS Integer
| Format_Debug
deriving Show
is_binary_format :: RenderFormat -> Bool
is_binary_format Format_PS = False
is_binary_format Format_PDF = True
is_binary_format (Format_EPS page) = False
is_binary_format Format_Debug = False
render_custom :: RenderFormat -> Custom -> Document a -> Writer a
render_custom Format_PS = render_ps_custom
render_custom Format_PDF = render_pdf_custom
render_custom (Format_EPS page) = (\c -> render_eps_custom c page)
render_custom Format_Debug = \c -> render_ascii
render_custom_file :: Handle -> RenderFormat -> Custom -> Document a -> IO a
render_custom_file h format custom d = do
when (is_binary_format format) $ do
hSetBinaryMode h True
writer_to_file h (render_custom format custom d)
render_custom_stdout :: RenderFormat -> Custom -> Document a -> IO a
render_custom_stdout = render_custom_file stdout
render_custom_string :: RenderFormat -> Custom -> Document a -> String
render_custom_string format custom d =
writer_to_string (render_custom format custom d)
render :: RenderFormat -> Document a -> Writer a
render format doc = render_custom format custom doc
render_file :: Handle -> RenderFormat -> Document a -> IO a
render_file h format doc = render_custom_file h format custom doc
render_stdout :: RenderFormat -> Document a -> IO a
render_stdout = render_file stdout
render_string :: RenderFormat -> Document a -> String
render_string format doc = render_custom_string format custom doc