module Data.String.Interpolate.Whitespace where
import Data.List ( intercalate )
import Data.String.Interpolate.Types
collapseWhitespace :: Lines -> Line
collapseWhitespace :: Lines -> Line
collapseWhitespace Lines
lines =
let oneliner :: Line
oneliner = forall a. [a] -> [[a]] -> [a]
intercalate [Int -> InterpSegment
Spaces Int
1] Lines
lines
in Line -> Line
removeSurroundingWS forall a b. (a -> b) -> a -> b
$ Line -> Line
toSingleSpace Line
oneliner
toSingleSpace :: Line -> Line
toSingleSpace :: Line -> Line
toSingleSpace [] = []
toSingleSpace (InterpSegment
x:InterpSegment
y:Line
xs) | InterpSegment -> Bool
isSpace InterpSegment
x Bool -> Bool -> Bool
&& InterpSegment -> Bool
isSpace InterpSegment
y =
Line -> Line
toSingleSpace (Int -> InterpSegment
Spaces Int
1 forall a. a -> [a] -> [a]
: Line
xs)
toSingleSpace (InterpSegment
x:Line
xs) | InterpSegment -> Bool
isSpace InterpSegment
x =
Int -> InterpSegment
Spaces Int
1 forall a. a -> [a] -> [a]
: Line -> Line
toSingleSpace Line
xs
toSingleSpace (InterpSegment
x:Line
xs) =
InterpSegment
x forall a. a -> [a] -> [a]
: Line -> Line
toSingleSpace Line
xs
removeSurroundingWS :: Line -> Line
removeSurroundingWS :: Line -> Line
removeSurroundingWS =
forall a. (a -> Bool) -> [a] -> [a]
dropWhile InterpSegment -> Bool
isSpace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
dropWhile InterpSegment -> Bool
isSpace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse
isSpace :: InterpSegment -> Bool
isSpace :: InterpSegment -> Bool
isSpace (Spaces Int
_) = Bool
True
isSpace (Tabs Int
_) = Bool
True
isSpace InterpSegment
_other = Bool
False