1 {-# LANGUAGE DeriveFunctor #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 module Language.TCT.Cell where
6 import Control.Monad (Monad(..))
7 import Data.Eq (Eq(..))
8 import Data.Function (($), (.))
9 import Data.Functor (Functor)
10 import Data.Monoid (Monoid(..))
11 import Data.Ord (Ord(..))
12 import Data.Semigroup (Semigroup(..))
13 import Data.Text (Text)
14 import Prelude (Int, Num(..), fromIntegral)
15 import Text.Show (Show(..), showParen, showString, showChar)
16 import qualified Data.Text as Text
17 import qualified Data.Text.Lazy as TL
19 import Language.TCT.Debug
22 -- | Relative position
25 { pos_line :: {-# UNPACK #-} !LineNum
26 , pos_column :: {-# UNPACK #-} !ColNum
28 instance Semigroup Pos where
29 Pos lx cx <> Pos ly cy =
31 instance Monoid Pos where
34 instance Show Pos where
35 showsPrec _p Pos{..} =
36 showsPrec 11 pos_line .
38 showsPrec 11 pos_column
53 { cell_begin :: {-# UNPACK #-} !Pos
54 , cell_end :: {-# UNPACK #-} !Pos
56 } deriving (Eq, Functor)
57 instance Show a => Show (Cell a) where
58 showsPrec p Cell{..} =
61 showChar ' ' . showsPrec 10 cell_begin .
62 showChar ' ' . showsPrec 10 cell_end .
63 showChar ' ' . showsPrec 11 unCell
64 instance Pretty a => Pretty (Cell a) where
65 pretty (Cell bp ep m) = do
67 return $ "Cell "<>show bp<>":"<>show ep<>" "<>s
68 instance (FromPad a, Semigroup a) => Semigroup (Cell a) where
69 Cell bx ex x <> Cell by ey y =
71 x<>fromPad (Pos lines columns)<>y
73 lines = pos_line by - pos_line ex
74 columns = pos_column by - pos_column (if lines <= 0 then ex else bx)
76 instance (FromPad a, Semigroup a, Monoid a) => Monoid (Cell a) where
82 cell0 = Cell mempty mempty
87 instance FromPad Text where
89 Text.replicate pos_line "\n" <>
90 Text.replicate pos_column " "
91 instance FromPad TL.Text where
93 TL.replicate (fromIntegral pos_line) "\n" <>
94 TL.replicate (fromIntegral pos_column) " "