Fix Dim.
authorJulien Moutinho <julm+symantic@autogeree.net>
Fri, 23 Jun 2017 11:20:54 +0000 (13:20 +0200)
committerJulien Moutinho <julm+symantic@autogeree.net>
Fri, 23 Jun 2017 11:20:54 +0000 (13:20 +0200)
symantic-document/Language/Symantic/Document/Dim.hs

index edf18b48ddeb8525da56afc84c3ec642bfbbd3d7..21aa02a5fed5a2410300bf16101f092788827a15 100644 (file)
@@ -1,5 +1,6 @@
 module Language.Symantic.Document.Dim where
 
+import Data.Eq (Eq)
 import Data.Foldable (Foldable(..))
 import Data.Function (($), id)
 import Data.Functor ((<$>))
@@ -8,9 +9,9 @@ import Data.Monoid (Monoid(..))
 import Data.Ord (Ord(..))
 import Data.Semigroup (Semigroup(..))
 import Data.String (IsString(..))
-import Prelude (min, max, Num(..), toInteger)
+import Prelude (max, Num(..), toInteger)
 import Text.Show (Show(..))
-import qualified Data.List as List
+import qualified Data.List as L
 import qualified Data.Text as T
 import qualified Data.Text.Lazy as TL
 
@@ -19,50 +20,48 @@ import Language.Symantic.Document.Sym
 -- * Type 'Dim'
 data Dim
  =   Dim
- { width       :: Int
- , height      :: Int
- , width_first :: Int
- , width_last  :: Int
- } deriving (Show)
+ { width       :: Int -- ^ Maximun line length.
+ , height      :: Int -- ^ Number of newlines.
+ , width_first :: Int -- ^ Length of the first line.
+ , width_last  :: Int -- ^ Length of the last line.
+ } deriving (Eq, Show)
 instance IsString Dim where
        fromString [] = Dim 0 0 0 0
        fromString s =
                Dim
                 { width       = maximum ws
                 , height      = length ls
-                , width_first = List.head ws
-                , width_last  = List.last ws
+                , width_first = if null ws then 0 else L.head ws
+                , width_last  = if null ws then 0 else L.last ws
                 }
                where
-               ls = lines s
+               ls = L.lines s
                ws = length <$> ls
 
 dim :: Dim -> Dim
 dim = id
 
 instance Semigroup Dim where
-       x@(Dim wx hx wfx wlx) <> y@(Dim wy hy wfy wly) =
-               let w = max (wlx + wfy) (max wx wy) in
-               let h = max 0 $ hx + hy - 1 in
+       Dim wx hx wfx wlx <> Dim wy hy wfy wly =
+               let h = hx + hy in
                case (hx, hy) of
-                (0, _) -> y
-                (_, 0) -> x
-                (1, 1) -> let v = wlx + wfy in Dim w h v v
-                (1, _) -> Dim w h (wfx + wfy) wly
-                (_, 1) -> Dim w h wfx (wlx + wfy)
-                _      -> Dim w h wfx wly
+                (0, 0) -> let w = wx  + wy  in Dim w h w w
+                (0, _) -> let v = wfx + wfy in Dim (max v (wx + wy)) h v wly
+                (_, 0) -> let v = wlx + wfy in Dim (max v (wx + wy)) h wfx v
+                _      -> Dim (max wx wy) h wfx wly
 instance Monoid Dim where
        mempty  = empty
        mappend = (<>)
 instance Doc_Text Dim where
-       spaces    i   = Dim i 1 i i
+       spaces    i   = Dim i 0 i i
        replicate i d = if i <= 0 then empty else d <> replicate (i - 1) d
        int       i   = fromString $ show i
        integer   i   = fromString $ show i
-       charH     _c  = Dim 1 1 1 1
-       stringH   t   = Dim l h l l where h = min 1 l; l = length t
-       textH     t   = Dim l h l l where h = min 1 l; l = T.length t
-       ltextH    t   = Dim l h l l where h = min 1 l; l = fromInteger $ toInteger $ TL.length t
+       charH     _c  = Dim 1 0 1 1
+       stringH   t   = Dim l 0 l l where l = length t
+       textH     t   = Dim l 0 l l where l = T.length t
+       ltextH    t   = Dim l 0 l l where l = fromInteger $ toInteger $ TL.length t
+                                           -- XXX: conversion may overflow
 instance Doc_Color Dim where
        reverse     = id
        black       = id