module Main where import Graphics.PS import Graphics.PS.Cairo drawPath :: (GS -> a -> b) -> Double -> a -> b drawPath m g p = m (greyGS g) p drawCircle :: Pt -> Double -> Image drawCircle p r = let c = arc p r 0 (2 * pi) in drawPath Stroke 0.2 c drawRectangle :: Pt -> Double -> Double -> Double -> Image drawRectangle p w h a = let r = rectangle p w h in drawPath Fill 0.4 (rotate a r) drawText :: Pt -> [Glyph] -> Double -> Image drawText p t n = let t' = Text (Font "Times" n) t in drawPath Stroke 0.2 (MoveTo p +++ t') showCoords :: Image showCoords = let to_n n = [0::Int,100..n] cs = [(x, y) | x <- to_n 800, y <- to_n 500] i = fromIntegral f (x,y) = drawText (Pt (i x) (i y)) (show (x,y)) 12 in foldl1 over (map f cs) scena :: Double -> [Image] scena n = let p = Pt 250 250 r = map (\a -> drawRectangle p 25 35 (pi/12*n*a)) [0..4] in [ showCoords , drawCircle p (25 * n) , drawCircle p (65 * n) , drawText p "Some text" (24 * n) ] ++ r main :: IO () main = cg "test.ps" (Paper 900 600) (scena 1.0)