{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Nix.Expr.Strings where
import Data.List ( intercalate
, dropWhileEnd
, inits
)
import Data.Text ( Text )
import qualified Data.Text as T
import Data.Tuple ( swap )
import Nix.Expr
mergePlain :: [Antiquoted Text r] -> [Antiquoted Text r]
mergePlain :: [Antiquoted Text r] -> [Antiquoted Text r]
mergePlain [] = []
mergePlain (Plain a :: Text
a : EscapedNewline : Plain b :: Text
b : xs :: [Antiquoted Text r]
xs) =
[Antiquoted Text r] -> [Antiquoted Text r]
forall r. [Antiquoted Text r] -> [Antiquoted Text r]
mergePlain (Text -> Antiquoted Text r
forall v r. v -> Antiquoted v r
Plain (Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
b) Antiquoted Text r -> [Antiquoted Text r] -> [Antiquoted Text r]
forall a. a -> [a] -> [a]
: [Antiquoted Text r]
xs)
mergePlain (Plain a :: Text
a : Plain b :: Text
b : xs :: [Antiquoted Text r]
xs) = [Antiquoted Text r] -> [Antiquoted Text r]
forall r. [Antiquoted Text r] -> [Antiquoted Text r]
mergePlain (Text -> Antiquoted Text r
forall v r. v -> Antiquoted v r
Plain (Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
b) Antiquoted Text r -> [Antiquoted Text r] -> [Antiquoted Text r]
forall a. a -> [a] -> [a]
: [Antiquoted Text r]
xs)
mergePlain (x :: Antiquoted Text r
x : xs :: [Antiquoted Text r]
xs) = Antiquoted Text r
x Antiquoted Text r -> [Antiquoted Text r] -> [Antiquoted Text r]
forall a. a -> [a] -> [a]
: [Antiquoted Text r] -> [Antiquoted Text r]
forall r. [Antiquoted Text r] -> [Antiquoted Text r]
mergePlain [Antiquoted Text r]
xs
removePlainEmpty :: [Antiquoted Text r] -> [Antiquoted Text r]
removePlainEmpty :: [Antiquoted Text r] -> [Antiquoted Text r]
removePlainEmpty = (Antiquoted Text r -> Bool)
-> [Antiquoted Text r] -> [Antiquoted Text r]
forall a. (a -> Bool) -> [a] -> [a]
filter Antiquoted Text r -> Bool
forall a r. (Eq a, Monoid a) => Antiquoted a r -> Bool
f where
f :: Antiquoted a r -> Bool
f (Plain x :: a
x) = a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
forall a. Monoid a => a
mempty
f _ = Bool
True
runAntiquoted :: v -> (v -> a) -> (r -> a) -> Antiquoted v r -> a
runAntiquoted :: v -> (v -> a) -> (r -> a) -> Antiquoted v r -> a
runAntiquoted _ f :: v -> a
f _ (Plain v :: v
v) = v -> a
f v
v
runAntiquoted nl :: v
nl f :: v -> a
f _ EscapedNewline = v -> a
f v
nl
runAntiquoted _ _ k :: r -> a
k (Antiquoted r :: r
r) = r -> a
k r
r
splitLines :: [Antiquoted Text r] -> [[Antiquoted Text r]]
splitLines :: [Antiquoted Text r] -> [[Antiquoted Text r]]
splitLines = ([[Antiquoted Text r]]
-> [Antiquoted Text r] -> [[Antiquoted Text r]])
-> ([[Antiquoted Text r]], [Antiquoted Text r])
-> [[Antiquoted Text r]]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (([Antiquoted Text r]
-> [[Antiquoted Text r]] -> [[Antiquoted Text r]])
-> [[Antiquoted Text r]]
-> [Antiquoted Text r]
-> [[Antiquoted Text r]]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (:)) (([[Antiquoted Text r]], [Antiquoted Text r])
-> [[Antiquoted Text r]])
-> ([Antiquoted Text r]
-> ([[Antiquoted Text r]], [Antiquoted Text r]))
-> [Antiquoted Text r]
-> [[Antiquoted Text r]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Antiquoted Text r] -> ([[Antiquoted Text r]], [Antiquoted Text r])
forall r.
[Antiquoted Text r] -> ([[Antiquoted Text r]], [Antiquoted Text r])
go where
go :: [Antiquoted Text r] -> ([[Antiquoted Text r]], [Antiquoted Text r])
go (Plain t :: Text
t : xs :: [Antiquoted Text r]
xs) = (Text -> Antiquoted Text r
forall v r. v -> Antiquoted v r
Plain Text
l Antiquoted Text r -> [Antiquoted Text r] -> [Antiquoted Text r]
forall a. a -> [a] -> [a]
:) ([Antiquoted Text r] -> [Antiquoted Text r])
-> ([[Antiquoted Text r]], [Antiquoted Text r])
-> ([[Antiquoted Text r]], [Antiquoted Text r])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text
-> ([[Antiquoted Text r]], [Antiquoted Text r])
-> ([[Antiquoted Text r]], [Antiquoted Text r]))
-> ([[Antiquoted Text r]], [Antiquoted Text r])
-> [Text]
-> ([[Antiquoted Text r]], [Antiquoted Text r])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Text
-> ([[Antiquoted Text r]], [Antiquoted Text r])
-> ([[Antiquoted Text r]], [Antiquoted Text r])
forall v r a.
v
-> ([[Antiquoted v r]], [Antiquoted v r])
-> ([[Antiquoted v r]], [a])
f ([Antiquoted Text r] -> ([[Antiquoted Text r]], [Antiquoted Text r])
go [Antiquoted Text r]
xs) [Text]
ls where
(l :: Text
l : ls :: [Text]
ls) = (Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '\n') Text
t
f :: v
-> ([[Antiquoted v r]], [Antiquoted v r])
-> ([[Antiquoted v r]], [a])
f prefix :: v
prefix (finished :: [[Antiquoted v r]]
finished, current :: [Antiquoted v r]
current) = ((v -> Antiquoted v r
forall v r. v -> Antiquoted v r
Plain v
prefix Antiquoted v r -> [Antiquoted v r] -> [Antiquoted v r]
forall a. a -> [a] -> [a]
: [Antiquoted v r]
current) [Antiquoted v r] -> [[Antiquoted v r]] -> [[Antiquoted v r]]
forall a. a -> [a] -> [a]
: [[Antiquoted v r]]
finished, [])
go (Antiquoted a :: r
a : xs :: [Antiquoted Text r]
xs) = (r -> Antiquoted Text r
forall v r. r -> Antiquoted v r
Antiquoted r
a Antiquoted Text r -> [Antiquoted Text r] -> [Antiquoted Text r]
forall a. a -> [a] -> [a]
:) ([Antiquoted Text r] -> [Antiquoted Text r])
-> ([[Antiquoted Text r]], [Antiquoted Text r])
-> ([[Antiquoted Text r]], [Antiquoted Text r])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Antiquoted Text r] -> ([[Antiquoted Text r]], [Antiquoted Text r])
go [Antiquoted Text r]
xs
go (EscapedNewline : xs :: [Antiquoted Text r]
xs) = (Antiquoted Text r
forall v r. Antiquoted v r
EscapedNewline Antiquoted Text r -> [Antiquoted Text r] -> [Antiquoted Text r]
forall a. a -> [a] -> [a]
:) ([Antiquoted Text r] -> [Antiquoted Text r])
-> ([[Antiquoted Text r]], [Antiquoted Text r])
-> ([[Antiquoted Text r]], [Antiquoted Text r])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Antiquoted Text r] -> ([[Antiquoted Text r]], [Antiquoted Text r])
go [Antiquoted Text r]
xs
go [] = ([], [])
unsplitLines :: [[Antiquoted Text r]] -> [Antiquoted Text r]
unsplitLines :: [[Antiquoted Text r]] -> [Antiquoted Text r]
unsplitLines = [Antiquoted Text r] -> [[Antiquoted Text r]] -> [Antiquoted Text r]
forall a. [a] -> [[a]] -> [a]
intercalate [Text -> Antiquoted Text r
forall v r. v -> Antiquoted v r
Plain "\n"]
stripIndent :: [Antiquoted Text r] -> NString r
stripIndent :: [Antiquoted Text r] -> NString r
stripIndent [] = Int -> [Antiquoted Text r] -> NString r
forall r. Int -> [Antiquoted Text r] -> NString r
Indented 0 []
stripIndent xs :: [Antiquoted Text r]
xs =
Int -> [Antiquoted Text r] -> NString r
forall r. Int -> [Antiquoted Text r] -> NString r
Indented Int
minIndent
([Antiquoted Text r] -> NString r)
-> ([[Antiquoted Text r]] -> [Antiquoted Text r])
-> [[Antiquoted Text r]]
-> NString r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Antiquoted Text r] -> [Antiquoted Text r]
forall r. [Antiquoted Text r] -> [Antiquoted Text r]
removePlainEmpty
([Antiquoted Text r] -> [Antiquoted Text r])
-> ([[Antiquoted Text r]] -> [Antiquoted Text r])
-> [[Antiquoted Text r]]
-> [Antiquoted Text r]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Antiquoted Text r] -> [Antiquoted Text r]
forall r. [Antiquoted Text r] -> [Antiquoted Text r]
mergePlain
([Antiquoted Text r] -> [Antiquoted Text r])
-> ([[Antiquoted Text r]] -> [Antiquoted Text r])
-> [[Antiquoted Text r]]
-> [Antiquoted Text r]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Maybe (Antiquoted Text r), Antiquoted Text r)
-> Antiquoted Text r)
-> [(Maybe (Antiquoted Text r), Antiquoted Text r)]
-> [Antiquoted Text r]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe (Antiquoted Text r), Antiquoted Text r) -> Antiquoted Text r
forall a b. (a, b) -> b
snd
([(Maybe (Antiquoted Text r), Antiquoted Text r)]
-> [Antiquoted Text r])
-> ([[Antiquoted Text r]]
-> [(Maybe (Antiquoted Text r), Antiquoted Text r)])
-> [[Antiquoted Text r]]
-> [Antiquoted Text r]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Maybe (Antiquoted Text r), Antiquoted Text r) -> Bool)
-> [(Maybe (Antiquoted Text r), Antiquoted Text r)]
-> [(Maybe (Antiquoted Text r), Antiquoted Text r)]
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd (Maybe (Antiquoted Text r), Antiquoted Text r) -> Bool
forall r r. (Maybe (Antiquoted Text r), Antiquoted Text r) -> Bool
cleanup
([(Maybe (Antiquoted Text r), Antiquoted Text r)]
-> [(Maybe (Antiquoted Text r), Antiquoted Text r)])
-> ([[Antiquoted Text r]]
-> [(Maybe (Antiquoted Text r), Antiquoted Text r)])
-> [[Antiquoted Text r]]
-> [(Maybe (Antiquoted Text r), Antiquoted Text r)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\ys :: [Antiquoted Text r]
ys -> [Maybe (Antiquoted Text r)]
-> [Antiquoted Text r]
-> [(Maybe (Antiquoted Text r), Antiquoted Text r)]
forall a b. [a] -> [b] -> [(a, b)]
zip
(([Antiquoted Text r] -> Maybe (Antiquoted Text r))
-> [[Antiquoted Text r]] -> [Maybe (Antiquoted Text r)]
forall a b. (a -> b) -> [a] -> [b]
map
(\case
[] -> Maybe (Antiquoted Text r)
forall a. Maybe a
Nothing
x :: [Antiquoted Text r]
x -> Antiquoted Text r -> Maybe (Antiquoted Text r)
forall a. a -> Maybe a
Just ([Antiquoted Text r] -> Antiquoted Text r
forall a. [a] -> a
last [Antiquoted Text r]
x)
)
([Antiquoted Text r] -> [[Antiquoted Text r]]
forall a. [a] -> [[a]]
inits [Antiquoted Text r]
ys)
)
[Antiquoted Text r]
ys
)
([Antiquoted Text r]
-> [(Maybe (Antiquoted Text r), Antiquoted Text r)])
-> ([[Antiquoted Text r]] -> [Antiquoted Text r])
-> [[Antiquoted Text r]]
-> [(Maybe (Antiquoted Text r), Antiquoted Text r)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Antiquoted Text r]] -> [Antiquoted Text r]
forall r. [[Antiquoted Text r]] -> [Antiquoted Text r]
unsplitLines
([[Antiquoted Text r]] -> NString r)
-> [[Antiquoted Text r]] -> NString r
forall a b. (a -> b) -> a -> b
$ [[Antiquoted Text r]]
ls'
where
ls :: [[Antiquoted Text r]]
ls = [[Antiquoted Text r]] -> [[Antiquoted Text r]]
forall r. [[Antiquoted Text r]] -> [[Antiquoted Text r]]
stripEmptyOpening ([[Antiquoted Text r]] -> [[Antiquoted Text r]])
-> [[Antiquoted Text r]] -> [[Antiquoted Text r]]
forall a b. (a -> b) -> a -> b
$ [Antiquoted Text r] -> [[Antiquoted Text r]]
forall r. [Antiquoted Text r] -> [[Antiquoted Text r]]
splitLines [Antiquoted Text r]
xs
ls' :: [[Antiquoted Text r]]
ls' = ([Antiquoted Text r] -> [Antiquoted Text r])
-> [[Antiquoted Text r]] -> [[Antiquoted Text r]]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> [Antiquoted Text r] -> [Antiquoted Text r]
forall r. Int -> [Antiquoted Text r] -> [Antiquoted Text r]
dropSpaces Int
minIndent) [[Antiquoted Text r]]
ls
minIndent :: Int
minIndent = case [[Antiquoted Text r]] -> [[Antiquoted Text r]]
forall r. [[Antiquoted Text r]] -> [[Antiquoted Text r]]
stripEmptyLines [[Antiquoted Text r]]
ls of
[] -> 0
nonEmptyLs :: [[Antiquoted Text r]]
nonEmptyLs -> [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ ([Antiquoted Text r] -> Int) -> [[Antiquoted Text r]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Antiquoted Text r] -> Int
forall r. [Antiquoted Text r] -> Int
countSpaces ([Antiquoted Text r] -> Int)
-> ([Antiquoted Text r] -> [Antiquoted Text r])
-> [Antiquoted Text r]
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Antiquoted Text r] -> [Antiquoted Text r]
forall r. [Antiquoted Text r] -> [Antiquoted Text r]
mergePlain) [[Antiquoted Text r]]
nonEmptyLs
stripEmptyLines :: [[Antiquoted Text r]] -> [[Antiquoted Text r]]
stripEmptyLines = ([Antiquoted Text r] -> Bool)
-> [[Antiquoted Text r]] -> [[Antiquoted Text r]]
forall a. (a -> Bool) -> [a] -> [a]
filter (([Antiquoted Text r] -> Bool)
-> [[Antiquoted Text r]] -> [[Antiquoted Text r]])
-> ([Antiquoted Text r] -> Bool)
-> [[Antiquoted Text r]]
-> [[Antiquoted Text r]]
forall a b. (a -> b) -> a -> b
$ \case
[Plain t :: Text
t] -> Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Bool
T.null (Text -> Bool) -> Text -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip Text
t
_ -> Bool
True
stripEmptyOpening :: [[Antiquoted Text r]] -> [[Antiquoted Text r]]
stripEmptyOpening ([Plain t :: Text
t] : ts :: [[Antiquoted Text r]]
ts) | Text -> Bool
T.null (Text -> Text
T.strip Text
t) = [[Antiquoted Text r]]
ts
stripEmptyOpening ts :: [[Antiquoted Text r]]
ts = [[Antiquoted Text r]]
ts
countSpaces :: [Antiquoted Text r] -> Int
countSpaces (Antiquoted _ : _) = 0
countSpaces (EscapedNewline : _) = 0
countSpaces (Plain t :: Text
t : _) = Text -> Int
T.length (Text -> Int) -> (Text -> Text) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== ' ') (Text -> Int) -> Text -> Int
forall a b. (a -> b) -> a -> b
$ Text
t
countSpaces [] = 0
dropSpaces :: Int -> [Antiquoted Text r] -> [Antiquoted Text r]
dropSpaces 0 x :: [Antiquoted Text r]
x = [Antiquoted Text r]
x
dropSpaces n :: Int
n (Plain t :: Text
t : cs :: [Antiquoted Text r]
cs) = Text -> Antiquoted Text r
forall v r. v -> Antiquoted v r
Plain (Int -> Text -> Text
T.drop Int
n Text
t) Antiquoted Text r -> [Antiquoted Text r] -> [Antiquoted Text r]
forall a. a -> [a] -> [a]
: [Antiquoted Text r]
cs
dropSpaces _ _ = [Char] -> [Antiquoted Text r]
forall a. HasCallStack => [Char] -> a
error "stripIndent: impossible"
cleanup :: (Maybe (Antiquoted Text r), Antiquoted Text r) -> Bool
cleanup (Nothing, Plain y :: Text
y) = (Char -> Bool) -> Text -> Bool
T.all (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== ' ') Text
y
cleanup (Just (Plain x :: Text
x), Plain y :: Text
y) | "\n" Text -> Text -> Bool
`T.isSuffixOf` Text
x = (Char -> Bool) -> Text -> Bool
T.all (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== ' ') Text
y
cleanup _ = Bool
False
escapeCodes :: [(Char, Char)]
escapeCodes :: [(Char, Char)]
escapeCodes =
[('\n', 'n'), ('\r', 'r'), ('\t', 't'), ('\\', '\\'), ('$', '$'), ('"', '"')]
fromEscapeCode :: Char -> Maybe Char
fromEscapeCode :: Char -> Maybe Char
fromEscapeCode = (Char -> [(Char, Char)] -> Maybe Char
forall a b. Eq a => a -> [(a, b)] -> Maybe b
`lookup` ((Char, Char) -> (Char, Char)) -> [(Char, Char)] -> [(Char, Char)]
forall a b. (a -> b) -> [a] -> [b]
map (Char, Char) -> (Char, Char)
forall a b. (a, b) -> (b, a)
swap [(Char, Char)]
escapeCodes)
toEscapeCode :: Char -> Maybe Char
toEscapeCode :: Char -> Maybe Char
toEscapeCode = (Char -> [(Char, Char)] -> Maybe Char
forall a b. Eq a => a -> [(a, b)] -> Maybe b
`lookup` [(Char, Char)]
escapeCodes)