How to define a Diagrams backend that combines several primitive backends

129 Views Asked by At

I would like to make the same program use two different Diagrams backends, notably diagrams-rasterific to generate PNGs, and diagrams-svg to generate SVGs, from the same diagram. Since Diagrams seems to be designed around using a single backend, I'm trying to define a composed backend, but am running into trouble defining renderToTree for the Backend instance:

import Diagrams.Core
import Diagrams.Core.Types

import qualified Diagrams.Backend.Rasterific as BackendA
import qualified Diagrams.Backend.SVG as BackendB

tokenA :: BackendA.B
tokenA = BackendA.Rasterific

tokenB :: BackendB.B
tokenB = BackendB.SVG

data Multi = Multi
  deriving (Eq, Ord, Read, Show)

type B = Multi

data MultiResult n = MultiResult (Result BackendA.B V2 n) (Result BackendB.B V2 n)
-- alternatively:
-- data MultiResult n =
--     ResultA (Result BackendA.B V2 n)
--   | ResultB (Result BackendB.B V2 n)

type instance V Multi = V2
type instance N Multi = Double

instance (TypeableFloat n, Show n) => Backend Multi V2 n where
  data Render Multi V2 n =
      RenderMulti
          { renderA :: Render BackendA.B V2 n
          , renderB :: Render BackendB.B V2 n
          }
  -- alternatively:
  -- data Render Multi V2 n =
  --     RenderA (renderA :: Render BackendA.B V2 n)
  --   | RenderB (renderB :: Render BackendB.B V2 n)

  type Result Multi V2 n = MultiResult n

  data Options Multi V2 n = MultiOptions

  renderRTree _ o tree = MultiResult
      (renderRTree tokenA (toOptA o) (treeToA tree))
      (renderRTree tokenB (toOptB o) (treeToB tree))

I'm unclear of how to defer to the individual backend implementations' renderRTree functions here. In either alternative structure (with the Render and Result types as sums or products), I'm failing to make the types match up. Concretely, in this approach, I'm stuck at

treeToA :: RTree Multi V2 n a -> RTree BackendA.B V2 n a
treeToA = fmap f
  where
    f (RAnnot a) = RAnnot a
    f (RStyle s) = RStyle s
    f REmpty = REmpty
    f (RPrim x) = RPrim (toA x)

toA :: Prim Multi V2 n -> Prim BackendA.B V2 n
toA = ???

but I'm not that confident this is even the way to go.

toOptA, toOptB aren't a problem, I can fill those in once they're needed. I can also provide Renderable instance for this backend with either approach, e.g.

instance (Show n, TypeableFloat n) => Renderable (Path V2 n) Multi where
  render _ x = RenderMulti (render tokenA x) (render tokenB x)
1

There are 1 best solutions below

3
On

I agree with other-Daniel about keeping the Diagram polymorphic and using it at two types. Something like:

dia :: forall b. (Renderable (Path V2 Double) b, V b ~ V2, N b ~ Double) => Diagram b
dia = circle 1

The type sigs will only get worse as you add primitive types, so I'd probably define a constraint for all the primitives I want:

type Back b = (V b ~ V2, N b ~ Double, 
    Renderable (Path V2 Double) b, Renderable (Text Double) b)

dia2 :: Back b => Diagram b
dia2 = circle 1 # fc blue

I don't think we can write renderRTree for your Multi and have it type-check. We expect that all the instances of Renderable _ Multi will be of the form (Renderable p SVG, Renderable p Rasterific) => Renderable p Multi, which should be enough to write toA. But we can't (AFAIK) promise this to GHC, because Renderable is an open type class.