module Haskeme ( IndentedLine (..)
, toIndentedLine
, Program (..)
, stringToProgram
, progToSExprs
) where
tabSize = 4
type Indent = Int
data IndentedLine = IndLine Indent String
deriving (Eq)
instance Show IndentedLine where
show (IndLine n line) = [ ' ' | _ <- [1..n] ] ++ line
indent :: IndentedLine -> Indent
indent (IndLine n _) = n
toIndentedLine :: String -> IndentedLine
toIndentedLine line
| null line = IndLine 0 ""
| head line == ' ' = toIndentedLineSpace (IndLine 0 line)
| head line == '\t' = toIndentedLineTab (IndLine 0 line)
| otherwise = IndLine 0 line
toIndentedLineSpace :: IndentedLine -> IndentedLine
toIndentedLineSpace (IndLine n line)
| null line = IndLine 0 ""
| head line == ' ' = toIndentedLineSpace (IndLine (n + 1) (tail line))
| head line == '\t' = error $ "Mixed indentation found in the line containing: '" ++
show (toIndentedLineTab (IndLine (n + tabSize) (tail line))) ++ "'"
| otherwise = (IndLine n line)
toIndentedLineTab :: IndentedLine -> IndentedLine
toIndentedLineTab (IndLine n line)
| null line = IndLine 0 ""
| head line == ' ' = error $ "Mixed indentation found in the line containing: '" ++
show (toIndentedLineSpace (IndLine (n + 1) (tail line))) ++ "'"
| head line == '\t' = toIndentedLineTab (IndLine (n + tabSize) (tail line))
| otherwise = (IndLine n line)
isEmptyIndentedLine :: IndentedLine -> Bool
isEmptyIndentedLine (IndLine _ line) = null line
data Program = Prog [Expression]
deriving (Eq)
instance Show Program where
show (Prog []) = ""
show (Prog (x:xs)) = show x ++ "\n" ++ show (Prog xs)
data Expression = Expr IndentedLine [Expression]
| ExprDeeper Expression
| ExprsDeeper [Expression]
deriving (Eq)
instance Show Expression where
show (Expr x ys) = show x ++ "\n" ++ (concat $ map (\ l -> l ++ "\n") $ map show ys)
show (ExprDeeper x) = show x ++ "\n"
show (ExprsDeeper xs) = concat $ map (\ x -> x ++ "\n") $ map show xs
stringToProgram :: String -> Program
stringToProgram s = p1
where ls = filter isNotEmptyIndentedLine $ map toIndentedLine $ lines s
where isNotEmptyIndentedLine = not . isEmptyIndentedLine
p0 = Prog $ toExpressions 0 ls []
p1 = extendProgramDeeper p0
toExpressions :: Indent -> [IndentedLine] -> [IndentedLine] -> [Expression]
toExpressions _ [] [] = []
toExpressions _ [] (y:ys) = [ Expr y (toExpressions (nextIndent ys) ys []) ]
toExpressions n (x:xs) []
| n == ind = toExpressions n xs [ x ]
| n < ind = toExpressions n xs [ x ]
| n > ind = toExpressions ind xs [ x ]
where ind = indent x :: Indent
toExpressions n (x:xs) (y:ys)
| n == ind = Expr y (toExpressions (nextIndent ys) ys []) : toExpressions n xs [ x ]
| n < ind = toExpressions n xs ((y:ys) ++ [ x ])
| n > ind = ExprDeeper (Expr y (toExpressions (nextIndent ys) ys [])) : toExpressions ind xs [ x ]
where ind = indent x :: Indent
nextIndent :: [IndentedLine] -> Indent
nextIndent [] = -1
nextIndent (l:ls) = indent l
extendProgramDeeper :: Program -> Program
extendProgramDeeper p = mapProg (\ x -> extendExprDeeper x []) p
where mapProg :: ([Expression] -> [Expression]) -> Program -> Program
mapProg f (Prog xs) = Prog (map (mapExprs f) xs)
mapExprs :: ([Expression] -> [Expression]) -> Expression -> Expression
mapExprs f (Expr x ys) = Expr x (f $ map (mapExprs f) ys)
mapExprs f (ExprDeeper y) = ExprDeeper (head $ f $ [ mapExprs f y ])
mapExprs f (ExprsDeeper ys) = ExprsDeeper (f $ map (mapExprs f) ys)
extendExprDeeper :: [Expression] -> [Expression] -> [Expression]
extendExprDeeper [] ys = ys
extendExprDeeper ((ExprDeeper x):xs) ys = extendExprDeeper xs [ deepX ]
where deepX = (ExprsDeeper (ys ++ [ x ]))
extendExprDeeper ((ExprsDeeper xs):_) _ = error $ "Deeper Expression already extended upwards at: '" ++
show (ExprsDeeper xs)
extendExprDeeper (x :xs) ys = extendExprDeeper xs (ys ++ [ x ])
progToSExprs :: Program -> String
progToSExprs (Prog []) = ""
progToSExprs (Prog (x:xs)) = exprToSExpr x ++ "\n" ++ progToSExprs (Prog xs)
exprToSExpr :: Expression -> String
exprToSExpr (Expr (IndLine _ f) xs) = "(" ++ f ++ (concat $ map ((" "++) . exprToSExpr) xs) ++ ")"
exprToSExpr (ExprDeeper x) = "(" ++ exprToSExpr x ++ ") "
exprToSExpr (ExprsDeeper (x:xs)) = "(" ++ exprToSExpr x ++
(concat $ map ((" "++) . exprToSExpr) xs) ++ ")"