module UVMHS.Lib.Pretty.Annotation where
import UVMHS.Core
import UVMHS.Lib.Pretty.Color
data Format =
FG Color
| NOFG
| BG Color
| NOBG
| UL
| NOUL
| BD
| NOBD
| IT
| NOIT
deriving (Format -> Format -> Bool
(Format -> Format -> Bool)
-> (Format -> Format -> Bool) -> Eq Format
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Format -> Format -> Bool
== :: Format -> Format -> Bool
$c/= :: Format -> Format -> Bool
/= :: Format -> Format -> Bool
Eq, Eq Format
Eq Format =>
(Format -> Format -> Ordering)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Format)
-> (Format -> Format -> Format)
-> Ord Format
Format -> Format -> Bool
Format -> Format -> Ordering
Format -> Format -> Format
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Format -> Format -> Ordering
compare :: Format -> Format -> Ordering
$c< :: Format -> Format -> Bool
< :: Format -> Format -> Bool
$c<= :: Format -> Format -> Bool
<= :: Format -> Format -> Bool
$c> :: Format -> Format -> Bool
> :: Format -> Format -> Bool
$c>= :: Format -> Format -> Bool
>= :: Format -> Format -> Bool
$cmax :: Format -> Format -> Format
max :: Format -> Format -> Format
$cmin :: Format -> Format -> Format
min :: Format -> Format -> Format
Ord,Int -> Format -> ShowS
[Format] -> ShowS
Format -> String
(Int -> Format -> ShowS)
-> (Format -> String) -> ([Format] -> ShowS) -> Show Format
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Format -> ShowS
showsPrec :: Int -> Format -> ShowS
$cshow :: Format -> String
show :: Format -> String
$cshowList :: [Format] -> ShowS
showList :: [Format] -> ShowS
Show)
data Formats = Formats
{ Formats -> 𝑂 Color
fgFormats ∷ 𝑂 Color
, Formats -> 𝑂 Color
bgFormats ∷ 𝑂 Color
, Formats -> 𝑂 Bool
ulFormats ∷ 𝑂 𝔹
, Formats -> 𝑂 Bool
bdFormats ∷ 𝑂 𝔹
, Formats -> 𝑂 Bool
itFormats ∷ 𝑂 𝔹
} deriving (Formats -> Formats -> Bool
(Formats -> Formats -> Bool)
-> (Formats -> Formats -> Bool) -> Eq Formats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Formats -> Formats -> Bool
== :: Formats -> Formats -> Bool
$c/= :: Formats -> Formats -> Bool
/= :: Formats -> Formats -> Bool
Eq,Eq Formats
Eq Formats =>
(Formats -> Formats -> Ordering)
-> (Formats -> Formats -> Bool)
-> (Formats -> Formats -> Bool)
-> (Formats -> Formats -> Bool)
-> (Formats -> Formats -> Bool)
-> (Formats -> Formats -> Formats)
-> (Formats -> Formats -> Formats)
-> Ord Formats
Formats -> Formats -> Bool
Formats -> Formats -> Ordering
Formats -> Formats -> Formats
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Formats -> Formats -> Ordering
compare :: Formats -> Formats -> Ordering
$c< :: Formats -> Formats -> Bool
< :: Formats -> Formats -> Bool
$c<= :: Formats -> Formats -> Bool
<= :: Formats -> Formats -> Bool
$c> :: Formats -> Formats -> Bool
> :: Formats -> Formats -> Bool
$c>= :: Formats -> Formats -> Bool
>= :: Formats -> Formats -> Bool
$cmax :: Formats -> Formats -> Formats
max :: Formats -> Formats -> Formats
$cmin :: Formats -> Formats -> Formats
min :: Formats -> Formats -> Formats
Ord,Int -> Formats -> ShowS
[Formats] -> ShowS
Formats -> String
(Int -> Formats -> ShowS)
-> (Formats -> String) -> ([Formats] -> ShowS) -> Show Formats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Formats -> ShowS
showsPrec :: Int -> Formats -> ShowS
$cshow :: Formats -> String
show :: Formats -> String
$cshowList :: [Formats] -> ShowS
showList :: [Formats] -> ShowS
Show)
instance Null Formats where null :: Formats
null = 𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats 𝑂 Color
forall a. 𝑂 a
None 𝑂 Color
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None
instance Append Formats where
Formats 𝑂 Color
fg₁ 𝑂 Color
bg₁ 𝑂 Bool
ul₁ 𝑂 Bool
bd₁ 𝑂 Bool
it₁ ⧺ :: Formats -> Formats -> Formats
⧺ Formats 𝑂 Color
fg₂ 𝑂 Color
bg₂ 𝑂 Bool
ul₂ 𝑂 Bool
bd₂ 𝑂 Bool
it₂ =
𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats (𝑂 Color -> 𝑂 Color -> 𝑂 Color
forall a. 𝑂 a -> 𝑂 a -> 𝑂 a
first 𝑂 Color
fg₁ 𝑂 Color
fg₂) (𝑂 Color -> 𝑂 Color -> 𝑂 Color
forall a. 𝑂 a -> 𝑂 a -> 𝑂 a
first 𝑂 Color
bg₁ 𝑂 Color
bg₂) (𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool
forall a. 𝑂 a -> 𝑂 a -> 𝑂 a
first 𝑂 Bool
ul₁ 𝑂 Bool
ul₂) (𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool
forall a. 𝑂 a -> 𝑂 a -> 𝑂 a
first 𝑂 Bool
bd₁ 𝑂 Bool
bd₂) (𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool
forall a. 𝑂 a -> 𝑂 a -> 𝑂 a
first 𝑂 Bool
it₁ 𝑂 Bool
it₂)
instance Monoid Formats
format ∷ Format → Formats
format :: Format -> Formats
format (FG Color
c) = 𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats (Color -> 𝑂 Color
forall a. a -> 𝑂 a
Some Color
c) 𝑂 Color
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None
format Format
NOFG = 𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats (Color -> 𝑂 Color
forall a. a -> 𝑂 a
Some (Color3Bit -> Color
Color Color3Bit
DefaultColor)) 𝑂 Color
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None
format (BG Color
c) = 𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats 𝑂 Color
forall a. 𝑂 a
None (Color -> 𝑂 Color
forall a. a -> 𝑂 a
Some Color
c) 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None
format Format
NOBG = 𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats 𝑂 Color
forall a. 𝑂 a
None (Color -> 𝑂 Color
forall a. a -> 𝑂 a
Some (Color3Bit -> Color
Color Color3Bit
DefaultColor)) 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None
format Format
UL = 𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats 𝑂 Color
forall a. 𝑂 a
None 𝑂 Color
forall a. 𝑂 a
None (Bool -> 𝑂 Bool
forall a. a -> 𝑂 a
Some Bool
True) 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None
format Format
NOUL = 𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats 𝑂 Color
forall a. 𝑂 a
None 𝑂 Color
forall a. 𝑂 a
None (Bool -> 𝑂 Bool
forall a. a -> 𝑂 a
Some Bool
False) 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None
format Format
BD = 𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats 𝑂 Color
forall a. 𝑂 a
None 𝑂 Color
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None (Bool -> 𝑂 Bool
forall a. a -> 𝑂 a
Some Bool
True) 𝑂 Bool
forall a. 𝑂 a
None
format Format
NOBD = 𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats 𝑂 Color
forall a. 𝑂 a
None 𝑂 Color
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None (Bool -> 𝑂 Bool
forall a. a -> 𝑂 a
Some Bool
False) 𝑂 Bool
forall a. 𝑂 a
None
format Format
IT = 𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats 𝑂 Color
forall a. 𝑂 a
None 𝑂 Color
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None (Bool -> 𝑂 Bool
forall a. a -> 𝑂 a
Some Bool
True)
format Format
NOIT = 𝑂 Color -> 𝑂 Color -> 𝑂 Bool -> 𝑂 Bool -> 𝑂 Bool -> Formats
Formats 𝑂 Color
forall a. 𝑂 a
None 𝑂 Color
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None 𝑂 Bool
forall a. 𝑂 a
None (Bool -> 𝑂 Bool
forall a. a -> 𝑂 a
Some Bool
False)
formats ∷ (ToIter Format t) ⇒ t → Formats
formats :: forall t. ToIter Format t => t -> Formats
formats = 𝐼 Formats -> Formats
forall a t. (Monoid a, ToIter a t) => t -> a
concat (𝐼 Formats -> Formats)
-> (𝐼 Format -> 𝐼 Formats) -> 𝐼 Format -> Formats
forall b c a. (b -> c) -> (a -> b) -> a -> c
∘ (Format -> Formats) -> 𝐼 Format -> 𝐼 Formats
forall a b. (a -> b) -> 𝐼 a -> 𝐼 b
forall (t :: * -> *) a b. Functor t => (a -> b) -> t a -> t b
map Format -> Formats
format (𝐼 Format -> Formats) -> (t -> 𝐼 Format) -> t -> Formats
forall b c a. (b -> c) -> (a -> b) -> a -> c
∘ t -> 𝐼 Format
forall a t. ToIter a t => t -> 𝐼 a
iter
override ∷ 𝐿 Format
override :: 𝐿 Format
override = [Format] -> 𝐿 Format
forall a t. ToIter a t => t -> 𝐿 a
list [Format
NOFG,Format
NOBG,Format
NOUL,Format
NOBD,Format
NOIT]
data Annotation = Annotation
{ Annotation -> Formats
annotationFormats ∷ Formats
, Annotation -> 𝑂 (ℂ ∧ Formats)
annotationUndertag ∷ 𝑂 (ℂ ∧ Formats)
} deriving (Annotation -> Annotation -> Bool
(Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool) -> Eq Annotation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Annotation -> Annotation -> Bool
== :: Annotation -> Annotation -> Bool
$c/= :: Annotation -> Annotation -> Bool
/= :: Annotation -> Annotation -> Bool
Eq,Eq Annotation
Eq Annotation =>
(Annotation -> Annotation -> Ordering)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Annotation)
-> (Annotation -> Annotation -> Annotation)
-> Ord Annotation
Annotation -> Annotation -> Bool
Annotation -> Annotation -> Ordering
Annotation -> Annotation -> Annotation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Annotation -> Annotation -> Ordering
compare :: Annotation -> Annotation -> Ordering
$c< :: Annotation -> Annotation -> Bool
< :: Annotation -> Annotation -> Bool
$c<= :: Annotation -> Annotation -> Bool
<= :: Annotation -> Annotation -> Bool
$c> :: Annotation -> Annotation -> Bool
> :: Annotation -> Annotation -> Bool
$c>= :: Annotation -> Annotation -> Bool
>= :: Annotation -> Annotation -> Bool
$cmax :: Annotation -> Annotation -> Annotation
max :: Annotation -> Annotation -> Annotation
$cmin :: Annotation -> Annotation -> Annotation
min :: Annotation -> Annotation -> Annotation
Ord,Int -> Annotation -> ShowS
[Annotation] -> ShowS
Annotation -> String
(Int -> Annotation -> ShowS)
-> (Annotation -> String)
-> ([Annotation] -> ShowS)
-> Show Annotation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Annotation -> ShowS
showsPrec :: Int -> Annotation -> ShowS
$cshow :: Annotation -> String
show :: Annotation -> String
$cshowList :: [Annotation] -> ShowS
showList :: [Annotation] -> ShowS
Show)
instance Null Annotation where
null :: Annotation
null = Formats -> 𝑂 (ℂ ∧ Formats) -> Annotation
Annotation Formats
forall a. Null a => a
null 𝑂 (ℂ ∧ Formats)
forall a. 𝑂 a
None
instance Append Annotation where
Annotation Formats
a₁ 𝑂 (ℂ ∧ Formats)
u₁ ⧺ :: Annotation -> Annotation -> Annotation
⧺ Annotation Formats
a₂ 𝑂 (ℂ ∧ Formats)
u₂ = Formats -> 𝑂 (ℂ ∧ Formats) -> Annotation
Annotation (Formats
a₁ Formats -> Formats -> Formats
forall a. Append a => a -> a -> a
⧺ Formats
a₂) (𝑂 (ℂ ∧ Formats) -> 𝑂 (ℂ ∧ Formats) -> 𝑂 (ℂ ∧ Formats)
forall a. 𝑂 a -> 𝑂 a -> 𝑂 a
last 𝑂 (ℂ ∧ Formats)
u₁ 𝑂 (ℂ ∧ Formats)
u₂)
instance Monoid Annotation
formatAnnotation ∷ Formats → Annotation
formatAnnotation :: Formats -> Annotation
formatAnnotation Formats
fm = Formats -> 𝑂 (ℂ ∧ Formats) -> Annotation
Annotation Formats
fm 𝑂 (ℂ ∧ Formats)
forall a. 𝑂 a
None
undertagAnnotation ∷ ℂ → Formats → Annotation
undertagAnnotation :: ℂ -> Formats -> Annotation
undertagAnnotation ℂ
c Formats
fm = Formats -> 𝑂 (ℂ ∧ Formats) -> Annotation
Annotation Formats
forall a. Null a => a
null (𝑂 (ℂ ∧ Formats) -> Annotation) -> 𝑂 (ℂ ∧ Formats) -> Annotation
forall a b. (a -> b) -> a -> b
$ (ℂ ∧ Formats) -> 𝑂 (ℂ ∧ Formats)
forall a. a -> 𝑂 a
Some (ℂ
c ℂ -> Formats -> ℂ ∧ Formats
forall a b. a -> b -> a ∧ b
:* Formats
fm)