M src/Data/Text/ParagraphLayout/Internal/Break.hs => src/Data/Text/ParagraphLayout/Internal/Break.hs +1 -1
@@ 47,7 47,7 @@ locale lang lb = Locale $ (clean lang) ++ (lbKeyword lb)
-- including case changes and converting hyphens to underscores.
--
-- This filter is here just to stop syntactically incorrect input.
- clean = takeWhile (`elem` ['A'..'Z'] ++ ['a'..'z'] ++ "_-")
+ clean = takeWhile (`elem` ['A' .. 'Z'] ++ ['a' .. 'z'] ++ "_-")
-- | List of all breaks in the given text, with offsets in descending order,
-- including the status of the break if applicable.
M => +2 -2
@@ 186,9 186,9 @@ splitsWithTotal ls = zeroSplit :| splits
splitsWithTotal' :: Line a => Int32 -> [a] -> [a] -> [(Int32, ([a], [a]))]
splitsWithTotal' _ _ [] = []
splitsWithTotal' total closed (x:xs) = split : splits
splitsWithTotal' total closed (x : xs) = split : splits
where
split = (newTotal, (reverse newClosed, xs))
splits = splitsWithTotal' newTotal newClosed xs
newClosed = x:closed
newClosed = x : closed
newTotal = total + lineHeight x
M src/Data/Text/ParagraphLayout/Internal/ParagraphConstruction.hs => src/Data/Text/ParagraphLayout/Internal/ParagraphConstruction.hs +1 -1
@@ 34,7 34,7 @@ infixr 5 >|<
(>|<) :: (SpanOptions, String) -> (Lazy.Text, [Span]) -> (Lazy.Text, [Span])
(spanLanguage, spanText) >|< (oldText, oldSpans) = (newText, newSpans)
where
- newSpans = newSpan:oldSpans
+ newSpans = newSpan : oldSpans
newSpan = Span (lengthWord8 packedSpanText) spanLanguage
newText = chunk packedSpanText oldText
packedSpanText = pack spanText
M src/Data/Text/ParagraphLayout/Internal/Plain.hs => src/Data/Text/ParagraphLayout/Internal/Plain.hs +2 -2
@@ 83,7 83,7 @@ layoutAndAlignLines maxWidth runs = frags
-- is preserved even across runs.
canonicalOrder :: [WithSpan PF.ProtoFragment] -> [WithSpan PF.ProtoFragment]
canonicalOrder [] = []
-canonicalOrder pfs@((WithSpan _ headPF):_) = case PF.direction headPF of
+canonicalOrder pfs@((WithSpan _ headPF) : _) = case PF.direction headPF of
-- TODO: Update for bidi.
Just DirLTR -> pfs
Just DirRTL -> reverse pfs
@@ 285,7 285,7 @@ resolveSpans p@(Paragraph arr pStart spans pOpts) = do
let sLengths = map spanLength spans
(i, s, sStart, sLen) <- getZipList $ (,,,)
- <$> ZipList [0..]
+ <$> ZipList [0 ..]
<*> ZipList spans
<*> ZipList sStarts
<*> ZipList sLengths
M src/Data/Text/ParagraphLayout/Internal/ResolvedSpan.hs => src/Data/Text/ParagraphLayout/Internal/ResolvedSpan.hs +1 -1
@@ 49,7 49,7 @@ instance SeparableTextContainer a => SeparableTextContainer (WithSpan a) where
dropWhileEnd p (WithSpan rs c) = WithSpan rs (dropWhileEnd p c)
splitBySpanIndex :: [WithSpan a] -> [[a]]
-splitBySpanIndex xs = [getBySpanIndex i xs | i <- [0..]]
+splitBySpanIndex xs = [getBySpanIndex i xs | i <- [0 ..]]
getBySpanIndex :: Int -> [WithSpan a] -> [a]
getBySpanIndex idx xs = map contents $ filter matchingIndex $ xs
M src/Data/Text/ParagraphLayout/Internal/Run.hs => src/Data/Text/ParagraphLayout/Internal/Run.hs +1 -1
@@ 96,7 96,7 @@ protoRuns' curZipper curRuns = case considerNext curZipper of
Nothing -> curRuns
Just choice ->
let headRun@(nextZipper, _, _) :| tailRuns = foldRun choice curRuns
- in protoRuns' nextZipper (headRun:tailRuns)
+ in protoRuns' nextZipper (headRun : tailRuns)
foldRun :: ZipperChoice -> [ProtoRun] -> NonEmpty ProtoRun
M src/Data/Text/ParagraphLayout/Internal/TextContainer.hs => src/Data/Text/ParagraphLayout/Internal/TextContainer.hs +7 -7
@@ 71,8 71,8 @@ splitTextsBy breakFunc tcs =
splitTextsBy' :: SeparableTextContainer a =>
(a -> [Int]) -> [a] -> [a] -> [([a], [a])]
splitTextsBy' _ _ [] = []
-splitTextsBy' breakFunc closed (tc:tcs) =
- fullSplits ++ splitTextsBy' breakFunc (tc:closed) tcs
+splitTextsBy' breakFunc closed (tc : tcs) =
+ fullSplits ++ splitTextsBy' breakFunc (tc : closed) tcs
where
fullSplits = map mergeWithRest tcSplits
mergeWithRest (x1, x2) =
@@ 96,7 96,7 @@ nonEmptyPair (xs, ys) = case (nonEmpty xs, nonEmpty ys) of
collapse :: SeparableTextContainer a => NonEmpty a -> [a]
collapse (tc :| tcs)
| Text.null (getText tc) = tcs
- | otherwise = tc:tcs
+ | otherwise = tc : tcs
-- | Treat a list of text containers as a contiguous sequence,
-- and remove a prefix of characters that match the given predicate.
@@ 142,17 142,17 @@ trimTextsEndPreserve p tcs =
trimTextsStart' :: SeparableTextContainer a => (Char -> Bool) -> [a] -> [a]
trimTextsStart' _ [] = []
-trimTextsStart' p (tc:tcs)
+trimTextsStart' p (tc : tcs)
| Text.null (getText trimmed) = trimTextsStart' p tcs
- | otherwise = trimmed:tcs
+ | otherwise = trimmed : tcs
where
trimmed = dropWhileStart p tc
trimTextsEnd' :: SeparableTextContainer a => (Char -> Bool) -> [a] -> [a]
trimTextsEnd' _ [] = []
-trimTextsEnd' p (tc:tcs)
+trimTextsEnd' p (tc : tcs)
| Text.null (getText trimmed) = trimTextsEnd' p tcs
- | otherwise = reverse $ trimmed:tcs
+ | otherwise = reverse $ trimmed : tcs
where
trimmed = dropWhileEnd p tc
M src/Data/Text/ParagraphLayout/Internal/Zipper.hs => src/Data/Text/ParagraphLayout/Internal/Zipper.hs +1 -1
@@ 133,4 133,4 @@ takeWord8 m (Text arr off _) = Text arr off m
-- Requires that @m@ be within the bounds of the `Text`, not at the beginning
-- or at the end, and not inside a code point.
dropWord8 :: Int -> Text -> Text
-dropWord8 m (Text arr off len) = Text arr (off+m) (len-m)
+dropWord8 m (Text arr off len) = Text arr (off + m) (len - m)
M test/Data/Text/ParagraphLayout/Internal/TextContainerSpec.hs => test/Data/Text/ParagraphLayout/Internal/TextContainerSpec.hs +1 -1
@@ 68,7 68,7 @@ exampleBreakPoints c =
d = cOffset c
isSpace :: Char -> Bool
-isSpace = (==' ')
+isSpace = (== ' ')
spec :: Spec
spec = do
M test/Data/Text/ParagraphLayout/Internal/ZipperSpec.hs => test/Data/Text/ParagraphLayout/Internal/ZipperSpec.hs +6 -6
@@ 98,8 98,8 @@ spec = do
Zipper.atEnd z `shouldBe` False
it ("preceding text has length " ++ show n) $ do
Text.length (Zipper.preceding z) `shouldBe` n
- it ("following text has length " ++ show (sampleLength-n)) $ do
- Text.length (Zipper.following z) `shouldBe` (sampleLength-n)
+ it ("following text has length " ++ show (sampleLength - n)) $ do
+ Text.length (Zipper.following z) `shouldBe` (sampleLength - n)
it "recombines into original text" $ do
Zipper.recombine z `shouldBe` sampleText
@@ 110,10 110,10 @@ spec = do
Zipper.atStart z `shouldBe` False
it "is not at end" $ do
Zipper.atEnd z `shouldBe` False
- it ("preceding text has length " ++ show (n+1)) $ do
- Text.length (Zipper.preceding z) `shouldBe` (n+1)
- it ("following text has length " ++ show (sampleLength-n-1)) $ do
- Text.length (Zipper.following z) `shouldBe` (sampleLength-n-1)
+ it ("preceding text has length " ++ show (n + 1)) $ do
+ Text.length (Zipper.preceding z) `shouldBe` (n + 1)
+ it ("following text has length " ++ show (sampleLength - n - 1)) $ do
+ Text.length (Zipper.following z) `shouldBe` (sampleLength - n - 1)
it "recombines into original text" $ do
Zipper.recombine z `shouldBe` sampleText
M test/Data/Text/ParagraphLayoutSpec.hs => test/Data/Text/ParagraphLayoutSpec.hs +4 -4
@@ 117,19 117,19 @@ indentedList :: String -> [String] -> [String]
indentedList indent items = prefixTail indent $ suffixInit commaNewline items
suffixInit :: String -> [String] -> [String]
-suffixInit suffix = mapInit (++suffix)
+suffixInit suffix = mapInit (++ suffix)
mapInit :: (a -> a) -> [a] -> [a]
mapInit _ [] = []
mapInit _ [x] = [x]
-mapInit f (x:y:ys) = f x : mapInit f (y:ys)
+mapInit f (x : y : ys) = f x : mapInit f (y : ys)
prefixTail :: String -> [String] -> [String]
-prefixTail prefix = mapTail (prefix++)
+prefixTail prefix = mapTail (prefix ++)
mapTail :: (a -> a) -> [a] -> [a]
mapTail _ [] = []
-mapTail f (x:xs) = x:(map f xs)
+mapTail f (x : xs) = x : (map f xs)
indent0 :: String
indent0 = ""