1 {-# LANGUAGE DeriveFunctor #-}
2 module Language.TCT.Cell where
4 import Data.Eq (Eq(..))
5 import Data.Function (($), (.))
6 import Data.Functor (Functor)
7 import Data.Maybe (Maybe(..))
8 import Data.Ord (Ord(..))
9 import Data.Semigroup (Semigroup(..))
10 import Data.Sequence (Seq, ViewL(..), ViewR(..))
11 import Data.TreeSeq.Strict (Tree(..))
13 import Text.Show (Show(..), showParen, showString, showChar)
14 import qualified Data.Sequence as Seq
17 -- | NOTE: every 'Cell' as a 'Pos',
18 -- which is useful to indicate matches/errors/warnings/whatever,
19 -- or outputing in a format somehow preserving
20 -- the original input style.
23 { posCell :: {-# UNPACK #-} !Pos
24 , posEndCell :: {-# UNPACK #-} !Pos
26 } deriving (Eq, Ord, Functor)
27 instance Show a => Show (Cell a) where
28 showsPrec p Cell{..} =
31 showChar ' ' . showsPrec 10 posCell .
32 showChar ' ' . showsPrec 10 posEndCell .
33 showChar ' ' . showsPrec 11 unCell
35 instance Semigroup a => Semigroup (Cell a) where
36 Cell bx ex x <> Cell by ey y =
37 Cell (bx`min`by) (ex`max`ey) (x<>y)
38 instance (Monoid a, Semigroup a) => Monoid (Cell a) where
39 mempty = Cell pos1 pos1 mempty
43 lineCell :: Cell a -> Line
44 lineCell = linePos . posCell
45 columnCell :: Cell a -> Column
46 columnCell = columnPos . posCell
49 cell0 = Cell pos0 pos0
51 cell1 = Cell pos1 pos1
53 posSeq :: Seq (Cell a) -> Maybe (Pos,Pos)
55 case Seq.viewl toks of
58 case Seq.viewr toks of
64 posTrees :: Seq (Trees (Cell k) a) -> Maybe (Pos,Pos)
66 case Seq.viewl trees of
70 Nothing -> posTrees ts
73 case Seq.viewr trees of
75 _ :> TreeN _ toks | iiiii->
77 TreeN (Cell bp _ep _) _ :< _ ->
78 case Seq.viewr trees of
80 _ :> TreeN _ toks | iiiii->
87 { linePos :: {-# UNPACK #-} !Line
88 , columnPos :: {-# UNPACK #-} !Column
90 instance Show Pos where
91 showsPrec _p pos = showsPrec 11 (linePos pos,columnPos pos)
92 instance Ord Pos where
93 Pos lx cx `compare` Pos ly cy =
97 posTree :: Tree (Cell k) (Cell a) -> Pos
98 posTree (TreeN c _) = posCell c
99 posTree (Tree0 c) = posCell c
101 posEndTree :: Tree (Cell k) (Cell a) -> Pos
102 posEndTree (TreeN c _) = posEndCell c
103 posEndTree (Tree0 c) = posEndCell c
111 -- | Line in the source file, counting from 1.
115 -- | Column in the source file, counting from 1.