{-# LANGUAGE OverloadedStrings #-}
module Text.IndentToBrace
( i2b
) where
import Control.Monad.Trans.Writer (execWriter, tell, Writer)
import Data.List (isInfixOf)
import qualified Data.Text as T
i2b :: String -> String
i2b :: String -> String
i2b = (forall a b. (a -> b) -> a -> b
$ [])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w a. Writer w a -> w
execWriter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Nest -> Writer (String -> String) ()
unnest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Nest -> Nest
addClosingCount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Either String Line] -> [Nest]
nest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map String -> Either String Line
toL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
stripComments
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= Char
'\r')
stripComments :: [String] -> [String]
=
forall a b. (a -> b) -> [a] -> [b]
map Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> [Text] -> [Text]
go Bool
False forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map String -> Text
T.pack
where
go :: Bool -> [Text] -> [Text]
go Bool
_ [] = []
go Bool
False (Text
l:[Text]
ls) =
let (Text
before, Text
after') = HasCallStack => Text -> Text -> (Text, Text)
T.breakOn Text
"/*" Text
l
in case Text -> Text -> Maybe Text
T.stripPrefix Text
"/*" Text
after' of
Maybe Text
Nothing -> Text
l forall a. a -> [a] -> [a]
: Bool -> [Text] -> [Text]
go Bool
False [Text]
ls
Just Text
after ->
let (Text
x:[Text]
xs) = Bool -> [Text] -> [Text]
go Bool
True forall a b. (a -> b) -> a -> b
$ Text
after forall a. a -> [a] -> [a]
: [Text]
ls
in Text
before Text -> Text -> Text
`T.append` Text
x forall a. a -> [a] -> [a]
: [Text]
xs
go Bool
True (Text
l:[Text]
ls) =
let (Text
_, Text
after') = HasCallStack => Text -> Text -> (Text, Text)
T.breakOn Text
"*/" Text
l
in case Text -> Text -> Maybe Text
T.stripPrefix Text
"*/" Text
after' of
Maybe Text
Nothing -> Text
T.empty forall a. a -> [a] -> [a]
: Bool -> [Text] -> [Text]
go Bool
True [Text]
ls
Just Text
after -> Bool -> [Text] -> [Text]
go Bool
False forall a b. (a -> b) -> a -> b
$ Text
after forall a. a -> [a] -> [a]
: [Text]
ls
data Line = Line
{ Line -> Int
lineIndent :: Int
, Line -> String
lineContent :: String
}
deriving (Int -> Line -> String -> String
[Line] -> String -> String
Line -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Line] -> String -> String
$cshowList :: [Line] -> String -> String
show :: Line -> String
$cshow :: Line -> String
showsPrec :: Int -> Line -> String -> String
$cshowsPrec :: Int -> Line -> String -> String
Show, Line -> Line -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Line -> Line -> Bool
$c/= :: Line -> Line -> Bool
== :: Line -> Line -> Bool
$c== :: Line -> Line -> Bool
Eq)
data Nest = Nest Line Int [Nest]
| Blank String
deriving (Int -> Nest -> String -> String
[Nest] -> String -> String
Nest -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Nest] -> String -> String
$cshowList :: [Nest] -> String -> String
show :: Nest -> String
$cshow :: Nest -> String
showsPrec :: Int -> Nest -> String -> String
$cshowsPrec :: Int -> Nest -> String -> String
Show, Nest -> Nest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Nest -> Nest -> Bool
$c/= :: Nest -> Nest -> Bool
== :: Nest -> Nest -> Bool
$c== :: Nest -> Nest -> Bool
Eq)
isBlank :: Nest -> Bool
isBlank :: Nest -> Bool
isBlank Blank{} = Bool
True
isBlank Nest
_ = Bool
False
addClosingCount :: Nest -> Nest
addClosingCount :: Nest -> Nest
addClosingCount (Blank String
x) = String -> Nest
Blank String
x
addClosingCount (Nest Line
l Int
c [Nest]
children) =
Line -> Int -> [Nest] -> Nest
Nest Line
l Int
c forall a b. (a -> b) -> a -> b
$ [Nest] -> [Nest]
increment forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Nest -> Nest
addClosingCount [Nest]
children
where
increment :: [Nest] -> [Nest]
increment
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Nest -> Bool
isBlank) [Nest]
children = [Nest] -> [Nest]
increment'
| Bool
otherwise = forall a. a -> a
id
increment' :: [Nest] -> [Nest]
increment' [] = forall a. HasCallStack => String -> a
error String
"should never happen"
increment' (Blank String
x:[Nest]
rest) = String -> Nest
Blank String
x forall a. a -> [a] -> [a]
: [Nest] -> [Nest]
increment' [Nest]
rest
increment' (n :: Nest
n@(Nest Line
l' Int
c' [Nest]
children'):[Nest]
rest)
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Nest -> Bool
isBlank) [Nest]
rest = Nest
n forall a. a -> [a] -> [a]
: [Nest] -> [Nest]
increment' [Nest]
rest
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Nest -> Bool
isBlank) [Nest]
children' = Line -> Int -> [Nest] -> Nest
Nest Line
l' Int
c' ([Nest] -> [Nest]
increment' [Nest]
children') forall a. a -> [a] -> [a]
: [Nest]
rest
| Bool
otherwise = Line -> Int -> [Nest] -> Nest
Nest Line
l' (Int
c' forall a. Num a => a -> a -> a
+ Int
1) [Nest]
children' forall a. a -> [a] -> [a]
: [Nest]
rest
toL :: String -> Either String Line
toL :: String -> Either String Line
toL String
s
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
y = forall a b. a -> Either a b
Left String
s
| Bool
otherwise = forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ Int -> String -> Line
Line (forall (t :: * -> *) a. Foldable t => t a -> Int
length String
x) String
y
where
(String
x, String
y) = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Eq a => a -> a -> Bool
== Char
' ') String
s
nest :: [Either String Line] -> [Nest]
nest :: [Either String Line] -> [Nest]
nest [] = []
nest (Left String
x:[Either String Line]
rest) = String -> Nest
Blank String
x forall a. a -> [a] -> [a]
: [Either String Line] -> [Nest]
nest [Either String Line]
rest
nest (Right Line
l:[Either String Line]
rest) =
Line -> Int -> [Nest] -> Nest
Nest Line
l Int
0 ([Either String Line] -> [Nest]
nest [Either String Line]
inside) forall a. a -> [a] -> [a]
: [Either String Line] -> [Nest]
nest [Either String Line]
outside
where
([Either String Line]
inside, [Either String Line]
outside) = forall a. (a -> Bool) -> [a] -> ([a], [a])
span forall {a}. Either a Line -> Bool
isNested [Either String Line]
rest
isNested :: Either a Line -> Bool
isNested Left{} = Bool
True
isNested (Right Line
l2) = Line -> Int
lineIndent Line
l2 forall a. Ord a => a -> a -> Bool
> Line -> Int
lineIndent Line
l
tell' :: String -> Writer (String -> String) ()
tell' :: String -> Writer (String -> String) ()
tell' String
s = forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell (String
s forall a. [a] -> [a] -> [a]
++)
unnest :: Nest -> Writer (String -> String) ()
unnest :: Nest -> Writer (String -> String) ()
unnest (Blank String
x) = do
String -> Writer (String -> String) ()
tell' String
x
String -> Writer (String -> String) ()
tell' String
"\n"
unnest (Nest Line
l Int
count [Nest]
inside) = do
String -> Writer (String -> String) ()
tell' forall a b. (a -> b) -> a -> b
$ forall a. Int -> a -> [a]
replicate (Line -> Int
lineIndent Line
l) Char
' '
String -> Writer (String -> String) ()
tell' forall a b. (a -> b) -> a -> b
$ Line -> String
lineContent Line
l
String -> Writer (String -> String) ()
tell' forall a b. (a -> b) -> a -> b
$
case () of
()
| Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Nest -> Bool
isBlank [Nest]
inside -> String
" {"
| String
";" forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` Line -> String
lineContent Line
l -> String
""
| Bool
otherwise -> String
";"
String -> Writer (String -> String) ()
tell' forall a b. (a -> b) -> a -> b
$ forall a. Int -> a -> [a]
replicate Int
count Char
'}'
String -> Writer (String -> String) ()
tell' String
"\n"
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Nest -> Writer (String -> String) ()
unnest [Nest]
inside