module Language.Haskell.Formatter.Process.LineTool
(Shifter, Shift, countEmptyLines, createShifter, shiftCode) where
import qualified Data.Map.Strict as Map
import qualified Language.Haskell.Formatter.Location as Location
import qualified Language.Haskell.Formatter.Process.Code as Code
newtype Shifter = Shifter (Map.Map Location.Line Shift)
deriving (Shifter -> Shifter -> Bool
(Shifter -> Shifter -> Bool)
-> (Shifter -> Shifter -> Bool) -> Eq Shifter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Shifter -> Shifter -> Bool
$c/= :: Shifter -> Shifter -> Bool
== :: Shifter -> Shifter -> Bool
$c== :: Shifter -> Shifter -> Bool
Eq, Eq Shifter
Eq Shifter
-> (Shifter -> Shifter -> Ordering)
-> (Shifter -> Shifter -> Bool)
-> (Shifter -> Shifter -> Bool)
-> (Shifter -> Shifter -> Bool)
-> (Shifter -> Shifter -> Bool)
-> (Shifter -> Shifter -> Shifter)
-> (Shifter -> Shifter -> Shifter)
-> Ord Shifter
Shifter -> Shifter -> Bool
Shifter -> Shifter -> Ordering
Shifter -> Shifter -> Shifter
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 :: Shifter -> Shifter -> Shifter
$cmin :: Shifter -> Shifter -> Shifter
max :: Shifter -> Shifter -> Shifter
$cmax :: Shifter -> Shifter -> Shifter
>= :: Shifter -> Shifter -> Bool
$c>= :: Shifter -> Shifter -> Bool
> :: Shifter -> Shifter -> Bool
$c> :: Shifter -> Shifter -> Bool
<= :: Shifter -> Shifter -> Bool
$c<= :: Shifter -> Shifter -> Bool
< :: Shifter -> Shifter -> Bool
$c< :: Shifter -> Shifter -> Bool
compare :: Shifter -> Shifter -> Ordering
$ccompare :: Shifter -> Shifter -> Ordering
$cp1Ord :: Eq Shifter
Ord, Int -> Shifter -> ShowS
[Shifter] -> ShowS
Shifter -> String
(Int -> Shifter -> ShowS)
-> (Shifter -> String) -> ([Shifter] -> ShowS) -> Show Shifter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Shifter] -> ShowS
$cshowList :: [Shifter] -> ShowS
show :: Shifter -> String
$cshow :: Shifter -> String
showsPrec :: Int -> Shifter -> ShowS
$cshowsPrec :: Int -> Shifter -> ShowS
Show)
type Shift = Int
countEmptyLines :: Location.Line -> Location.Line -> Int
countEmptyLines :: Line -> Line -> Int
countEmptyLines Line
endLine Line
startLine = Int -> Int
forall a. Enum a => a -> a
pred Int
lineDifference
where lineDifference :: Int
lineDifference = Line -> Line -> Int
forall a b. (Natural a, Num b) => a -> a -> b
Location.minus Line
startLine Line
endLine
createShifter :: Map.Map Location.Line Shift -> Shifter
createShifter :: Map Line Int -> Shifter
createShifter Map Line Int
relativeShifter = Map Line Int -> Shifter
Shifter Map Line Int
absoluteShifter
where (Int
_, Map Line Int
absoluteShifter) = (Int -> Int -> (Int, Int))
-> Int -> Map Line Int -> (Int, Map Line Int)
forall a b c k. (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
Map.mapAccum Int -> Int -> (Int, Int)
forall b. Num b => b -> b -> (b, b)
accumulate Int
noShift Map Line Int
relativeShifter
accumulate :: b -> b -> (b, b)
accumulate b
absoluteShift b
relativeShift
= (b
absoluteShift', b
absoluteShift')
where absoluteShift' :: b
absoluteShift' = b
absoluteShift b -> b -> b
forall a. Num a => a -> a -> a
+ b
relativeShift
noShift :: Shift
noShift :: Int
noShift = Int
0
shiftCode :: Shifter -> Code.LocatableCode -> Code.LocatableCode
shiftCode :: Shifter -> LocatableCode -> LocatableCode
shiftCode Shifter
shifter = (SrcSpanInfo -> SrcSpanInfo) -> LocatableCode -> LocatableCode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((SrcSpanInfo -> SrcSpanInfo) -> LocatableCode -> LocatableCode)
-> (SrcSpanInfo -> SrcSpanInfo) -> LocatableCode -> LocatableCode
forall a b. (a -> b) -> a -> b
$ Shifter -> SrcSpanInfo -> SrcSpanInfo
shiftNestedPortion Shifter
shifter
where shiftNestedPortion :: Shifter -> SrcSpanInfo -> SrcSpanInfo
shiftNestedPortion = (Line -> Line) -> SrcSpanInfo -> SrcSpanInfo
Location.replaceNestedPortionLines ((Line -> Line) -> SrcSpanInfo -> SrcSpanInfo)
-> (Shifter -> Line -> Line)
-> Shifter
-> SrcSpanInfo
-> SrcSpanInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Shifter -> Line -> Line
shiftLine
shiftLine :: Shifter -> Location.Line -> Location.Line
shiftLine :: Shifter -> Line -> Line
shiftLine Shifter
shifter Line
line = Int -> Line -> Line
forall a b. (Natural a, Integral b) => b -> a -> a
Location.plus Int
shift Line
line
where shift :: Int
shift = Line -> Shifter -> Int
lookupShift Line
line Shifter
shifter
lookupShift :: Location.Line -> Shifter -> Shift
lookupShift :: Line -> Shifter -> Int
lookupShift Line
line (Shifter Map Line Int
shifter)
= case Line -> Map Line Int -> Maybe (Line, Int)
forall k v. Ord k => k -> Map k v -> Maybe (k, v)
Map.lookupLE Line
line Map Line Int
shifter of
Maybe (Line, Int)
Nothing -> Int
noShift
Just (Line
_, Int
shift) -> Int
shift