module Converter.Internal where
import Data.Data (Data (toConstr), showConstr)
import Data.List (dropWhileEnd)
import Data.Text qualified as T
newtype Pretty a = Pretty String
instance Show a => Show (Pretty a) where
show :: Pretty a -> String
show :: Pretty a -> String
show (Pretty String
s) = String
s
class Show a => PrettyPrint a where
pp :: a -> Pretty String
instance PrettyPrint String where
pp :: String -> Pretty String
pp :: String -> Pretty String
pp = forall a. String -> Pretty a
Pretty forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd (forall a. Eq a => a -> a -> Bool
== Char
'\n')
instance PrettyPrint T.Text where
pp :: T.Text -> Pretty String
pp :: Text -> Pretty String
pp = forall a. PrettyPrint a => a -> Pretty String
pp forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
escapedHash :: T.Text
escapedHash :: Text
escapedHash = Text
"\\#"
hash :: T.Text
hash :: Text
hash = Text
"#"
dropLen :: T.Text -> T.Text -> T.Text
dropLen :: Text -> Text -> Text
dropLen Text
x Text
y = Int -> Text -> Text
T.drop (Text -> Int
T.length Text
x) Text
y
startsWith :: T.Text -> T.Text -> Bool
startsWith :: Text -> Text -> Bool
startsWith = forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Text -> Bool
T.isPrefixOf
endsWith :: T.Text -> T.Text -> Bool
endsWith :: Text -> Text -> Bool
endsWith = forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Text -> Bool
T.isSuffixOf
stripEnds :: T.Text -> T.Text -> T.Text -> T.Text
stripEnds :: Text -> Text -> Text -> Text
stripEnds Text
prefix Text
suffix Text
x = Int -> Text -> Text
T.dropEnd (Text -> Int
T.length Text
suffix) (Text -> Text -> Text
dropLen Text
prefix (Text -> Text
stripSpaces Text
x))
stripSpaces :: T.Text -> T.Text
stripSpaces :: Text -> Text
stripSpaces = Text -> Text
T.strip
stripList :: Eq a => a -> [a] -> [a]
stripList :: forall a. Eq a => a -> [a] -> [a]
stripList a
x = forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd (forall a. Eq a => a -> a -> Bool
== a
x) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
== a
x)
indentN :: Int -> T.Text -> T.Text
indentN :: Int -> Text -> Text
indentN Int
x Text
s = [Text] -> Text
T.concat (forall a. Int -> a -> [a]
replicate Int
x Text
" ") forall a. Semigroup a => a -> a -> a
<> Text
s
constructorName :: Data a => a -> String
constructorName :: forall a. Data a => a -> String
constructorName a
x = Constr -> String
showConstr (forall a. Data a => a -> Constr
toConstr a
x)
stripEmpties :: [T.Text] -> [T.Text]
stripEmpties :: [Text] -> [Text]
stripEmpties = forall a. Eq a => a -> [a] -> [a]
stripList Text
T.empty
dropEmpties :: [T.Text] -> [T.Text]
dropEmpties :: [Text] -> [Text]
dropEmpties = forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
== Text
T.empty)
isEnclosedWith :: T.Text -> T.Text -> T.Text -> Bool
isEnclosedWith :: Text -> Text -> Text -> Bool
isEnclosedWith Text
start Text
end (Text -> Text
stripSpaces -> Text
x) = Text
x Text -> Text -> Bool
`startsWith` Text
start Bool -> Bool -> Bool
&& Text
x Text -> Text -> Bool
`endsWith` Text
end
countSpaces :: T.Text -> Int
countSpaces :: Text -> Int
countSpaces Text
x = Text -> Int
T.length forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.takeWhile (forall a. Eq a => a -> a -> Bool
== Char
' ') Text
x
errorEmptyCommentAt :: Show a1 => a1 -> a2
a1
lineNumber =
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$
(String
"Expected a 'Comment' at line " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show a1
lineNumber forall a. Semigroup a => a -> a -> a
<> String
".\n\n")
forall a. Semigroup a => a -> a -> a
<> String
"However, there are no characters after '{- '.\n\n"
forall a. Semigroup a => a -> a -> a
<> String
"Please, write there something after '{- '."
prependTexComment :: T.Text -> T.Text
Text
l
| Text
l forall a. Eq a => a -> a -> Bool
== Text
T.empty = Text
l
| Bool
otherwise = Text
texCommentSpace forall a. Semigroup a => a -> a -> a
<> Text
l
dropTexComment :: Show a => T.Text -> a -> T.Text
Text
l a
lineNumber
| Text
l Text -> Text -> Bool
`startsWith` Text
texCommentSpace = Text -> Text -> Text
dropLen Text
texCommentSpace Text
l
| Text
l forall a. Eq a => a -> a -> Bool
== Text
T.empty = Text
l
| Bool
otherwise =
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$
String
"Lines in a 'Disabled' block must either be empty or start with '% '\n\n"
forall a. Semigroup a => a -> a -> a
<> String
"Note that each 'Disabled' block must have at least one line starting with '% ' and having nonempty text after '% ' "
forall a. Semigroup a => a -> a -> a
<> (String
"The line " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show a
lineNumber forall a. Semigroup a => a -> a -> a
<> String
" must either be empty or start with '% '")
texComment :: T.Text
= Text
"%"
texCommentSpace :: T.Text
= Text
texComment forall a. Semigroup a => a -> a -> a
<> Text
" "
lhsComment :: T.Text
= Text
"%"
lhsCommentSpace :: T.Text
= Text
lhsComment forall a. Semigroup a => a -> a -> a
<> Text
" "
lhsHsCode :: T.Text
lhsHsCode :: Text
lhsHsCode = Text
">"
lhsHsCodeSpace :: T.Text
lhsHsCodeSpace :: Text
lhsHsCodeSpace = Text
lhsHsCode forall a. Semigroup a => a -> a -> a
<> Text
" "
prependLhsComment :: T.Text -> T.Text
Text
l
| Text
l forall a. Eq a => a -> a -> Bool
== Text
T.empty = Text
l
| Bool
otherwise = Text
texCommentSpace forall a. Semigroup a => a -> a -> a
<> Text
l
dropLhsComment :: Show a => T.Text -> a -> T.Text
Text
l a
lineNumber
| Text
l Text -> Text -> Bool
`startsWith` Text
lhsCommentSpace = Text -> Text -> Text
dropLen Text
lhsCommentSpace Text
l
| Text
l forall a. Eq a => a -> a -> Bool
== Text
T.empty = Text
l
| Bool
otherwise = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"The line " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show a
lineNumber forall a. Semigroup a => a -> a -> a
<> String
" must either be empty or start with '% '"
lhsUnescapeHash :: T.Text -> T.Text
lhsUnescapeHash :: Text -> Text
lhsUnescapeHash Text
x = if Text
x Text -> Text -> Bool
`startsWith` Text
escapedHash then Text
hash forall a. Semigroup a => a -> a -> a
<> (Text -> Text -> Text
dropLen Text
escapedHash Text
x) else Text
x
lhsEscapeHash :: T.Text -> T.Text
lhsEscapeHash :: Text -> Text
lhsEscapeHash Text
x = if Text
x Text -> Text -> Bool
`startsWith` Text
hash then Text
escapedHash forall a. Semigroup a => a -> a -> a
<> (Text -> Text -> Text
dropLen Text
hash Text
x) else Text
x
mdCommentOpen :: T.Text
= Text
"<!--"
mdCommentClose :: T.Text
= Text
"-->"
mdCommentOpenSpace :: T.Text
= Text
mdCommentOpen forall a. Semigroup a => a -> a -> a
<> Text
" "
mdCommentCloseSpace :: T.Text
= Text
" " forall a. Semigroup a => a -> a -> a
<> Text
mdCommentClose
stripMdComment :: T.Text -> T.Text
= Text -> Text -> Text -> Text
stripEnds Text
mdCommentOpenSpace Text
mdCommentCloseSpace
isMdComment :: T.Text -> Bool
= Text -> Text -> Text -> Bool
isEnclosedWith Text
mdCommentOpenSpace Text
mdCommentCloseSpace
hsCommentOpen :: T.Text
= Text
"{-"
hsCommentOpenSpace :: T.Text
= Text
hsCommentOpen forall a. Semigroup a => a -> a -> a
<> Text
" "
hsCommentClose :: T.Text
= Text
"-}"
hsCommentCloseSpace :: T.Text
= Text
" " forall a. Semigroup a => a -> a -> a
<> Text
hsCommentClose
stripHsComment :: T.Text -> T.Text
= Text -> Text -> Text -> Text
stripEnds Text
hsCommentOpenSpace Text
hsCommentCloseSpace
isHsComment :: T.Text -> Bool
= Text -> Text -> Text -> Bool
isEnclosedWith Text
hsCommentOpenSpace Text
hsCommentCloseSpace