[Chart] Deploying with font SVGs

Bjorn Buckwalter bjorn at buckwalter.se
Fri Feb 7 20:32:42 GMT 2014


Hi Jan (et al),

With your pointers I worked it out. Here is what I ended up with:

~~~~~~~~~~~~~~~~8<~~~~~~~~~~~~~~~~~~~~~~
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}

-- | The backend to render charts with the diagrams library.
module LocalFonts (localFonts) where

import qualified Data.Map as M
import Graphics.Rendering.Chart.Backend.Types
import System.FilePath (replaceFileName)


localFonts :: FilePath -> M.Map (String, FontSlant, FontWeight) FilePath
localFonts exec = let
    serifR   = replaceFileName exec "fonts/LinLibertine_R.svg"
    serifRB  = replaceFileName exec "fonts/LinLibertine_RB.svg"
    serifRBI = replaceFileName exec "fonts/LinLibertine_RBI.svg"
    serifRI  = replaceFileName exec "fonts/LinLibertine_RI.svg"
    sansR    = replaceFileName exec "fonts/SourceSansPro_R.svg"
    sansRB   = replaceFileName exec "fonts/SourceSansPro_RB.svg"
    sansRBI  = replaceFileName exec "fonts/SourceSansPro_RBI.svg"
    sansRI   = replaceFileName exec "fonts/SourceSansPro_RI.svg"
    monoR    = replaceFileName exec "fonts/SourceCodePro_R.svg"
    monoRB   = replaceFileName exec "fonts/SourceCodePro_RB.svg"
  in M.fromList
    [ ( ("serif"     , FontSlantNormal , FontWeightNormal) , serifR   )
    , ( ("serif"     , FontSlantNormal , FontWeightBold  ) , serifRB  )
    , ( ("serif"     , FontSlantItalic , FontWeightNormal) , serifRI  )
    , ( ("serif"     , FontSlantOblique, FontWeightNormal) , serifRI  )
    , ( ("serif"     , FontSlantItalic , FontWeightBold  ) , serifRBI )
    , ( ("serif"     , FontSlantOblique, FontWeightBold  ) , serifRBI )

    , ( ("sans-serif", FontSlantNormal , FontWeightNormal) , sansR    )
    , ( ("sans-serif", FontSlantNormal , FontWeightBold  ) , sansRB   )
    , ( ("sans-serif", FontSlantItalic , FontWeightNormal) , sansRI   )
    , ( ("sans-serif", FontSlantOblique, FontWeightNormal) , sansRI   )
    , ( ("sans-serif", FontSlantItalic , FontWeightBold  ) , sansRBI  )
    , ( ("sans-serif", FontSlantOblique, FontWeightBold  ) , sansRBI  )

    , ( ("monospace" , FontSlantNormal , FontWeightNormal) , monoR    )
    , ( ("monospace" , FontSlantNormal , FontWeightBold  ) , monoRB   )
    , ( ("monospace" , FontSlantItalic , FontWeightNormal) , monoR    )
    , ( ("monospace" , FontSlantOblique, FontWeightNormal) , monoR    )
    , ( ("monospace" , FontSlantItalic , FontWeightBold  ) , monoRB   )
    , ( ("monospace" , FontSlantOblique, FontWeightBold  ) , monoRB   )
    ]

~~~~~~~~~~~~~~~~8<~~~~~~~~~~~~~~~~~~~~~~

In my application code I use localFonts with something like

  exec <- getExecutablePath  -- from System.Environment
  renderableToFile (localFO exec) ...
  where
    localFO = FileOptions (width opts, height opts) SVG_EMBEDDED .
localFonts

Then, when installing in production I copy the fonts directory from
charts-diagrams into the same directory as the executable. Works well
enough for me. :)

Would localFonts be useful for a general audience with my problem? If
anyone thinks so I could submit a pull request (feel free to suggest a
better name and location if not in
Graphics.Rendering.Chart.Backend.Diagrams).

Thanks,
Bjorn



On Tue, Feb 4, 2014 at 11:07 AM, Jan Bracker <jan.bracker at googlemail.com>wrote:

> Hi Bjorn,
>
> die Diagrams backend offers the possibility to supply custom fonts [1]. If
> you copy the fonts delivered with cabal to a custom (relative) location you
> can reconfigure all standard fonts through this mechanism. To see how the
> standard fonts are wired look here [2].
>
> I hope this helps.
>
> Jan
>
> [1]:
> http://hackage.haskell.org/package/Chart-diagrams-1.2/docs/Graphics-Rendering-Chart-Backend-Diagrams.html#v:customFontEnv
> [2]:
> http://hackage.haskell.org/package/Chart-diagrams-1.2/docs/src/Graphics-Rendering-Chart-Backend-Diagrams.html#defaultFonts
>
>
> 2014-02-04 Bjorn Buckwalter <bjorn at buckwalter.se>:
>
>>  Hi,
>>
>> I need to deploy applications in a Windows environment (Window XP to be
>> specific) where my deployment options are pretty much limited to copying a
>> .exe or possibly a folder structure. This seemed very hairy/impossible with
>> the old Cairo backend, but the new(ish) Diagrams backend seemed perfect for
>> this scenario.
>>
>> However, I soon found out that an application built with the Diagrams
>> backend references data files (the font SVGs) with absolute paths, which in
>> this case are buried deep in a .cabal-sandbox directory on my development
>> computer. Needless to say this doesn't work too well when the executable is
>> copied to the production workstation.
>>
>> Is there a pretty and non-fragile solution to this problem? (I think I
>> could hack it by move the repo to, e.g., C:\myrepo\ on my dev comp, build
>> it there, and then make sure to copy the relevent files into
>> C:\myrepo\.cabal-sandbox on the production workstation, but is that ever
>> ugly and fragile!)
>>
>> Perhaps this is cabal question rather than a Chart question; I might try
>> posting in a cabal forum too.
>>
>> Thanks,
>> Bjorn
>>
>>
>> _______________________________________________
>> Chart mailing list
>> Chart at projects.haskell.org
>> http://projects.haskell.org/cgi-bin/mailman/listinfo/chart
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://projects.haskell.org/pipermail/chart/attachments/20140207/9c354c8a/attachment.htm>


More information about the Chart mailing list