diff options
| author | John MacFarlane <jgm@berkeley.edu> | 2017-05-25 22:48:27 +0200 | 
|---|---|---|
| committer | John MacFarlane <jgm@berkeley.edu> | 2017-05-25 22:48:27 +0200 | 
| commit | cb7b0a69859cbf838519c5ad5f35d40ffd4f4246 (patch) | |
| tree | 6b4449b94e0f218598b430ce1cf6e13a35e67b0f /src/Text/Pandoc | |
| parent | 708973a33a0ce425bb21a5ffa06fbdab465d3fb8 (diff) | |
| download | pandoc-cb7b0a69859cbf838519c5ad5f35d40ffd4f4246.tar.gz | |
Allow em for image height/width in HTML, LaTeX.
- Export `inEm` from ImageSize [API change].
- Change `showFl` and `show` instance for `Dimension` so
  extra decimal places are omitted.
- Added `Em` as a constructor of `Dimension` [API change].
- Allow `em`, `cm`, `in` to pass through without conversion
  in HTML, LaTeX.
Closes #3450.
Diffstat (limited to 'src/Text/Pandoc')
| -rw-r--r-- | src/Text/Pandoc/ImageSize.hs | 20 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 7 | 
2 files changed, 21 insertions, 6 deletions
| diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs index 4d914a10c..eec8658c5 100644 --- a/src/Text/Pandoc/ImageSize.hs +++ b/src/Text/Pandoc/ImageSize.hs @@ -43,6 +43,7 @@ module Text.Pandoc.ImageSize ( ImageType(..)                               , inInch                               , inPixel                               , inPoints +                             , inEm                               , numUnit                               , showInInch                               , showInPixel @@ -80,12 +81,14 @@ data Dimension = Pixel Integer                 | Centimeter Double                 | Inch Double                 | Percent Double +               | Em Double  instance Show Dimension where    show (Pixel a)      = show   a ++ "px"    show (Centimeter a) = showFl a ++ "cm"    show (Inch a)       = showFl a ++ "in"    show (Percent a)    = show   a ++ "%" +  show (Em a)         = showFl a ++ "em"  data ImageSize = ImageSize{                       pxX   :: Integer @@ -97,7 +100,13 @@ instance Default ImageSize where    def = ImageSize 300 200 72 72  showFl :: (RealFloat a) => a -> String -showFl a = showFFloat (Just 5) a "" +showFl a = removeExtra0s $ showFFloat (Just 5) a "" + +removeExtra0s :: String -> String +removeExtra0s s = +  case dropWhile (=='0') $ reverse s of +       '.':xs -> reverse xs +       xs     -> reverse xs  imageType :: ByteString -> Maybe ImageType  imageType img = case B.take 4 img of @@ -167,6 +176,9 @@ desiredSizeInPoints opts attr s =  inPoints :: WriterOptions -> Dimension -> Double  inPoints opts dim = 72 * inInch opts dim +inEm :: WriterOptions -> Dimension -> Double +inEm opts dim = (64/11) * inInch opts dim +  inInch :: WriterOptions -> Dimension -> Double  inInch opts dim =    case dim of @@ -174,6 +186,7 @@ inInch opts dim =      (Centimeter a) -> a * 0.3937007874      (Inch a)       -> a      (Percent _)    -> 0 +    (Em a)         -> a * (11/64)  inPixel :: WriterOptions -> Dimension -> Integer  inPixel opts dim = @@ -181,7 +194,8 @@ inPixel opts dim =      (Pixel a)      -> a      (Centimeter a) -> floor $ dpi * a * 0.3937007874 :: Integer      (Inch a)       -> floor $ dpi * a :: Integer -    _              -> 0 +    (Percent _)    -> 0 +    (Em a)         -> floor $ dpi * a * (11/64) :: Integer    where      dpi = fromIntegral $ writerDpi opts @@ -213,6 +227,7 @@ scaleDimension factor dim =          Centimeter x -> Centimeter (factor * x)          Inch x       -> Inch (factor * x)          Percent x    -> Percent (factor * x) +        Em x         -> Em (factor * x)  -- | Read a Dimension from an Attr attribute.  -- `dimension Width attr` might return `Just (Pixel 3)` or for example `Just (Centimeter 2.0)`, etc. @@ -236,6 +251,7 @@ lengthToDim s = numUnit s >>= uncurry toDim      toDim a ""     = Just $ Pixel (floor a::Integer)      toDim a "pt"   = Just $ Inch (a / 72)      toDim a "pc"   = Just $ Inch (a / 6) +    toDim a "em"   = Just $ Em a      toDim _ _      = Nothing  epsSize :: ByteString -> Maybe ImageSize diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 63e839684..2a72f6f3d 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -533,10 +533,9 @@ dimensionsToAttrList :: WriterOptions -> Attr -> [(String, String)]  dimensionsToAttrList opts attr = (go Width) ++ (go Height)    where      go dir = case (dimension dir attr) of -               (Just (Percent a)) -> [("style", show dir ++ ":" ++ show (Percent a))] -               (Just dim)         -> [(show dir, showInPixel opts dim)] -               _ -> [] - +               (Just (Pixel a))  -> [(show dir, show a)] +               (Just x)          -> [("style", show dir ++ ":" ++ show x)] +               Nothing           -> []  imageExts :: [String]  imageExts = [ "art", "bmp", "cdr", "cdt", "cpt", "cr2", "crw", "djvu", "erf", | 
