{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
module Text.Pretty.Simple.Internal.ExprParser
where
import Text.Pretty.Simple.Internal.Expr (CommaSeparated(..), Expr(..))
import Control.Arrow (first)
import Data.Char (isAlpha, isDigit)
testString1 :: String
testString1 = "Just [TextInput {textInputClass = Just (Class {unClass = \"class\"}), textInputId = Just (Id {unId = \"id\"}), textInputName = Just (Name {unName = \"name\"}), textInputValue = Just (Value {unValue = \"value\"}), textInputPlaceholder = Just (Placeholder {unPlaceholder = \"placeholder\"})}, TextInput {textInputClass = Just (Class {unClass = \"class\"}), textInputId = Just (Id {unId = \"id\"}), textInputName = Just (Name {unName = \"name\"}), textInputValue = Just (Value {unValue = \"value\"}), textInputPlaceholder = Just (Placeholder {unPlaceholder = \"placeholder\"})}]"
testString2 :: String
testString2 = "some stuff (hello [\"dia\\x40iahello\", why wh, bye] ) (bye)"
expressionParse :: String -> [Expr]
expressionParse = fst . parseExprs
parseExpr :: String -> (Expr, String)
parseExpr ('(':rest) = first (Parens . CommaSeparated) $ parseCSep ')' rest
parseExpr ('[':rest) = first (Brackets . CommaSeparated) $ parseCSep ']' rest
parseExpr ('{':rest) = first (Braces . CommaSeparated) $ parseCSep '}' rest
parseExpr ('"':rest) = first StringLit $ parseStringLit rest
parseExpr ('\'':rest) = first CharLit $ parseCharLit rest
parseExpr (c:rest) | isDigit c = first NumberLit $ parseNumberLit c rest
parseExpr other = first Other $ parseOther other
parseExprs :: String -> ([Expr], String)
parseExprs [] = ([], "")
parseExprs s@(c:_)
| c `elem` (")]}," :: String) = ([], s)
| otherwise = let (parsed, rest') = parseExpr s
(toParse, rest) = parseExprs rest'
in (parsed : toParse, rest)
parseCSep :: Char -> String -> ([[Expr]], String)
parseCSep _ [] = ([], "")
parseCSep end s@(c:cs)
| c == end = ([], cs)
| c `elem` (")]}" :: String) = ([], s)
| c == ',' = parseCSep end cs
| otherwise = let (parsed, rest') = parseExprs s
(toParse, rest) = parseCSep end rest'
in (parsed : toParse, rest)
parseStringLit :: String -> (String, String)
parseStringLit [] = ("", "")
parseStringLit ('"':rest) = ("", rest)
parseStringLit ('\\':c:cs) = ('\\':c:cs', rest)
where (cs', rest) = parseStringLit cs
parseStringLit (c:cs) = (c:cs', rest)
where (cs', rest) = parseStringLit cs
parseCharLit :: String -> (String, String)
parseCharLit [] = ("", "")
parseCharLit ('\'':rest) = ("", rest)
parseCharLit ('\\':c:cs) = ('\\':c:cs', rest)
where (cs', rest) = parseCharLit cs
parseCharLit (c:cs) = (c:cs', rest)
where (cs', rest) = parseCharLit cs
parseNumberLit :: Char -> String -> (String, String)
parseNumberLit firstDigit rest1 =
case rest2 of
[] -> (firstDigit:remainingDigits, "")
'.':rest3 ->
let (digitsAfterDot, rest4) = span isDigit rest3
in ((firstDigit : remainingDigits) ++ ('.' : digitsAfterDot), rest4)
_ -> (firstDigit:remainingDigits, rest2)
where
remainingDigits :: String
rest2 :: String
(remainingDigits, rest2) = span isDigit rest1
parseOther :: String -> (String, String)
parseOther = go False
where
go
:: Bool
-> String
-> (String, String)
go _ [] = ("", "")
go insideIdent cs@(c:cs')
| c `elem` ("{[()]}\"'," :: String) = ("", cs)
| isDigit c && not insideIdent = ("", cs)
| insideIdent = first (c :) (go (isIdentRest c) cs')
| otherwise = first (c :) (go (isIdentBegin c) cs')
isIdentBegin :: Char -> Bool
isIdentBegin '_' = True
isIdentBegin c = isAlpha c
isIdentRest :: Char -> Bool
isIdentRest '_' = True
isIdentRest '\'' = True
isIdentRest c = isAlpha c || isDigit c