{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Data.Format
( fmt
, fmtConcat
, Format(..)
) where
import Control.Applicative
import Control.Exception (SomeException)
import Data.Char
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as Text.Lazy
import Language.Haskell.Meta.Parse
import Language.Haskell.TH
import Language.Haskell.TH.Quote
import Language.Haskell.TH.Syntax
import Text.Earley
fmtConcat :: [Text] -> Text
fmtConcat = mconcat
class Format a where
formatText :: a -> Text
instance Format Int where
formatText = tshow
instance Format SomeException where
formatText = tshow
instance Format String where
formatText = Text.pack
instance Format Double where
formatText = tshow
instance Format Float where
formatText = tshow
instance Format Integer where
formatText = tshow
instance Format Text where
formatText = id
instance Format Text.Lazy.Text where
formatText = Text.Lazy.toStrict
instance Format Bool where
formatText = tshow
tshow :: Show a => a -> Text
tshow = Text.pack . show
data Fmt = Literal String
| Identifier String
| Expression String
deriving (Show, Eq)
fmt :: QuasiQuoter
fmt = QuasiQuoter { quoteExp = parseFormatStringQ
, quotePat = undefined
, quoteType = undefined
, quoteDec = undefined
}
instance Lift Fmt where
lift (Literal s) = stringE s
lift (Identifier s) =
lookupValueName s >>= \case
Just v -> (return . formatTextEmbed . VarE) v
Nothing -> fail $ "Not in scope: '" ++ s ++ "'"
lift (Expression s) = either fail (return . formatTextEmbed) (parseExp s)
formatTextEmbed :: Exp -> Exp
formatTextEmbed expr = AppE (VarE 'formatText) expr
newtype FmtString = FmtString [Fmt]
instance Lift FmtString where
lift (FmtString fmts) = do
fmtExprs <- Prelude.mapM lift fmts
return $ AppE (VarE 'fmtConcat) (ListE fmtExprs)
parseFormatStringQ :: String -> Q Exp
parseFormatStringQ s =
let parseResult = FmtString (parseFormatString s)
in [| parseResult |]
parseFormatString :: String -> [Fmt]
parseFormatString s =
case fullParses (parser fmtParser) s of
([], Report { unconsumed = "" }) ->
[]
([uniqueResult], Report { unconsumed = "" }) ->
uniqueResult
_ ->
fail "Parse failure"
fmtParser :: Grammar r (Prod r String Char [Fmt])
fmtParser = mdo
start <- rule $ interpolationOrLiteral
interpolationOrLiteral <- rule $
interpolationThenRest
<|> literalThenRest
interpolationThenRest <- rule $
interpolationSimpleThenRest
<|> interpolationDelimitedThenRest
interpolationSimpleThenRest <- rule $
(Identifier <$> interpolationSimple) `apCons` delimLiteralThenRest
<|> (Identifier <$> interpolationSimple) `apCons` interpolationThenRest
<|> (Identifier <$> interpolationSimple) `apCons` pure []
interpolationDelimitedThenRest <- rule $
(Expression <$> interpolationDelimited) `apCons` interpolationOrLiteral
<|> (Expression <$> interpolationDelimited) `apCons` pure []
delimLiteral <- rule $ Literal <$>
(satisfy (\c -> not (identifierChar c) && c /= '$')) `apCons` strChars
delimLiteralThenRest <- rule $
delimLiteral `apCons` interpolationThenRest
<|> delimLiteral `apCons` (pure [])
literalThenRest <- rule $
(Literal <$> literal) `apCons` pure []
<|> (Literal <$> literal) `apCons` interpolationThenRest
identifier <- rule $
satisfy initialIdentifierChar `apCons` many (satisfy identifierChar)
interpolationSimple <- rule $ token '$' *> identifier
interpolationDelimited <- rule $ token '$' *> token '{' *> expression <* token '}'
strChar <- rule $
satisfy (`Prelude.notElem` ['$', '\\'])
<|> token '\\' *> satisfy (const True)
strChars <- rule $ many strChar
literal <- rule $ strChar `apCons` strChars
expression <- rule $ some (satisfy (/= '}'))
return start
where apCons = liftA2 (:)
identifierChar :: Char -> Bool
identifierChar c = isLower c || isUpper c || c `Prelude.elem` ['\'', '_']
initialIdentifierChar :: Char -> Bool
initialIdentifierChar c = isLower c || c == '_'