module Language.Haskell.Formatter.CommentCore
(CommentCore, kind, content, Kind(..), DocumentationDisplacement(..),
create, wrappedLineCount, documentationDisplacement)
where
import qualified Data.Char as Char
import qualified Data.Monoid as Monoid
import qualified Language.Haskell.Formatter.Internal.Newline as Newline
import qualified Language.Haskell.Formatter.Toolkit.ListTool as ListTool
data = {CommentCore -> Kind
kind :: Kind, CommentCore -> String
content :: String}
deriving (CommentCore -> CommentCore -> Bool
(CommentCore -> CommentCore -> Bool)
-> (CommentCore -> CommentCore -> Bool) -> Eq CommentCore
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommentCore -> CommentCore -> Bool
$c/= :: CommentCore -> CommentCore -> Bool
== :: CommentCore -> CommentCore -> Bool
$c== :: CommentCore -> CommentCore -> Bool
Eq, Eq CommentCore
Eq CommentCore
-> (CommentCore -> CommentCore -> Ordering)
-> (CommentCore -> CommentCore -> Bool)
-> (CommentCore -> CommentCore -> Bool)
-> (CommentCore -> CommentCore -> Bool)
-> (CommentCore -> CommentCore -> Bool)
-> (CommentCore -> CommentCore -> CommentCore)
-> (CommentCore -> CommentCore -> CommentCore)
-> Ord CommentCore
CommentCore -> CommentCore -> Bool
CommentCore -> CommentCore -> Ordering
CommentCore -> CommentCore -> CommentCore
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
min :: CommentCore -> CommentCore -> CommentCore
$cmin :: CommentCore -> CommentCore -> CommentCore
max :: CommentCore -> CommentCore -> CommentCore
$cmax :: CommentCore -> CommentCore -> CommentCore
>= :: CommentCore -> CommentCore -> Bool
$c>= :: CommentCore -> CommentCore -> Bool
> :: CommentCore -> CommentCore -> Bool
$c> :: CommentCore -> CommentCore -> Bool
<= :: CommentCore -> CommentCore -> Bool
$c<= :: CommentCore -> CommentCore -> Bool
< :: CommentCore -> CommentCore -> Bool
$c< :: CommentCore -> CommentCore -> Bool
compare :: CommentCore -> CommentCore -> Ordering
$ccompare :: CommentCore -> CommentCore -> Ordering
$cp1Ord :: Eq CommentCore
Ord)
data Kind = Ordinary
| Nested
deriving (Kind -> Kind -> Bool
(Kind -> Kind -> Bool) -> (Kind -> Kind -> Bool) -> Eq Kind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Kind -> Kind -> Bool
$c/= :: Kind -> Kind -> Bool
== :: Kind -> Kind -> Bool
$c== :: Kind -> Kind -> Bool
Eq, Eq Kind
Eq Kind
-> (Kind -> Kind -> Ordering)
-> (Kind -> Kind -> Bool)
-> (Kind -> Kind -> Bool)
-> (Kind -> Kind -> Bool)
-> (Kind -> Kind -> Bool)
-> (Kind -> Kind -> Kind)
-> (Kind -> Kind -> Kind)
-> Ord Kind
Kind -> Kind -> Bool
Kind -> Kind -> Ordering
Kind -> Kind -> Kind
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
min :: Kind -> Kind -> Kind
$cmin :: Kind -> Kind -> Kind
max :: Kind -> Kind -> Kind
$cmax :: Kind -> Kind -> Kind
>= :: Kind -> Kind -> Bool
$c>= :: Kind -> Kind -> Bool
> :: Kind -> Kind -> Bool
$c> :: Kind -> Kind -> Bool
<= :: Kind -> Kind -> Bool
$c<= :: Kind -> Kind -> Bool
< :: Kind -> Kind -> Bool
$c< :: Kind -> Kind -> Bool
compare :: Kind -> Kind -> Ordering
$ccompare :: Kind -> Kind -> Ordering
$cp1Ord :: Eq Kind
Ord, Int -> Kind -> ShowS
[Kind] -> ShowS
Kind -> String
(Int -> Kind -> ShowS)
-> (Kind -> String) -> ([Kind] -> ShowS) -> Show Kind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Kind] -> ShowS
$cshowList :: [Kind] -> ShowS
show :: Kind -> String
$cshow :: Kind -> String
showsPrec :: Int -> Kind -> ShowS
$cshowsPrec :: Int -> Kind -> ShowS
Show)
data DocumentationDisplacement = BeforeActualCode
| AfterActualCode
| None
deriving (DocumentationDisplacement -> DocumentationDisplacement -> Bool
(DocumentationDisplacement -> DocumentationDisplacement -> Bool)
-> (DocumentationDisplacement -> DocumentationDisplacement -> Bool)
-> Eq DocumentationDisplacement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
$c/= :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
== :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
$c== :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
Eq, Eq DocumentationDisplacement
Eq DocumentationDisplacement
-> (DocumentationDisplacement
-> DocumentationDisplacement -> Ordering)
-> (DocumentationDisplacement -> DocumentationDisplacement -> Bool)
-> (DocumentationDisplacement -> DocumentationDisplacement -> Bool)
-> (DocumentationDisplacement -> DocumentationDisplacement -> Bool)
-> (DocumentationDisplacement -> DocumentationDisplacement -> Bool)
-> (DocumentationDisplacement
-> DocumentationDisplacement -> DocumentationDisplacement)
-> (DocumentationDisplacement
-> DocumentationDisplacement -> DocumentationDisplacement)
-> Ord DocumentationDisplacement
DocumentationDisplacement -> DocumentationDisplacement -> Bool
DocumentationDisplacement -> DocumentationDisplacement -> Ordering
DocumentationDisplacement
-> DocumentationDisplacement -> DocumentationDisplacement
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
min :: DocumentationDisplacement
-> DocumentationDisplacement -> DocumentationDisplacement
$cmin :: DocumentationDisplacement
-> DocumentationDisplacement -> DocumentationDisplacement
max :: DocumentationDisplacement
-> DocumentationDisplacement -> DocumentationDisplacement
$cmax :: DocumentationDisplacement
-> DocumentationDisplacement -> DocumentationDisplacement
>= :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
$c>= :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
> :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
$c> :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
<= :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
$c<= :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
< :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
$c< :: DocumentationDisplacement -> DocumentationDisplacement -> Bool
compare :: DocumentationDisplacement -> DocumentationDisplacement -> Ordering
$ccompare :: DocumentationDisplacement -> DocumentationDisplacement -> Ordering
$cp1Ord :: Eq DocumentationDisplacement
Ord, Int -> DocumentationDisplacement -> ShowS
[DocumentationDisplacement] -> ShowS
DocumentationDisplacement -> String
(Int -> DocumentationDisplacement -> ShowS)
-> (DocumentationDisplacement -> String)
-> ([DocumentationDisplacement] -> ShowS)
-> Show DocumentationDisplacement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocumentationDisplacement] -> ShowS
$cshowList :: [DocumentationDisplacement] -> ShowS
show :: DocumentationDisplacement -> String
$cshow :: DocumentationDisplacement -> String
showsPrec :: Int -> DocumentationDisplacement -> ShowS
$cshowsPrec :: Int -> DocumentationDisplacement -> ShowS
Show)
instance Show CommentCore where
show :: CommentCore -> String
show CommentCore
comment
= case CommentCore -> Kind
kind CommentCore
comment of
Kind
Ordinary -> String -> ShowS
forall a. Monoid a => a -> a -> a
Monoid.mappend String
"--" String
rawContent
Kind
Nested -> [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"{-", String
rawContent, String
"-}"]
where rawContent :: String
rawContent = CommentCore -> String
content CommentCore
comment
create :: Kind -> String -> CommentCore
create :: Kind -> String -> CommentCore
create Kind
rawKind String
rawContent = CommentCore :: Kind -> String -> CommentCore
CommentCore{kind :: Kind
kind = Kind
rawKind, content :: String
content = String
rawContent}
wrappedLineCount :: CommentCore -> Int
wrappedLineCount :: CommentCore -> Int
wrappedLineCount = [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([String] -> Int)
-> (CommentCore -> [String]) -> CommentCore -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
Newline.splitSeparatedLines (String -> [String])
-> (CommentCore -> String) -> CommentCore -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommentCore -> String
forall a. Show a => a -> String
show
documentationDisplacement :: CommentCore -> DocumentationDisplacement
documentationDisplacement :: CommentCore -> DocumentationDisplacement
documentationDisplacement CommentCore
comment
= case String
unwrappedContent of
(Char
'|' : String
_) -> DocumentationDisplacement
BeforeActualCode
(Char
'^' : String
_) -> DocumentationDisplacement
AfterActualCode
String
_ -> DocumentationDisplacement
None
where unwrappedContent :: String
unwrappedContent
= (Char -> Bool) -> Int -> ShowS
forall a. (a -> Bool) -> Int -> [a] -> [a]
ListTool.dropWhileAtMost Char -> Bool
Char.isSpace Int
spaceLimit ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ CommentCore -> String
content CommentCore
comment
spaceLimit :: Int
spaceLimit = Int
1