-- | This module provides a short introduction to get users started using
-- Trifecta. The key takeaway message is that it’s not harder, or even much
-- different, from using other parser libraries, so for users familiar with one
-- of the many Parsecs should feel right at home.
--
-- __The source of this file is written in a literate style__, and can be read
-- top-to-bottom.
module Text.Trifecta.Tutorial where

import Control.Applicative
import Text.Trifecta

-- | First, we import Trifecta itself. It only the core parser definitions and
-- instances. Since Trifecta on its own is just the parser and a handful of
-- instances; the bulk of the utility functions is actually from a separate
-- package, /parsers/, that provides the usual parsing functions like
-- 'manyTill', 'between', and so on. The idea behind the /parsers/ package is
-- that most parser libraries define the same generic functions, so they were
-- put into their own package to be shared. Trifecta reexports these
-- definitions, but it’s useful to keep in mind that the documentation of
-- certain functions might not be directly in the /trifecta/ package.
importDocumentation :: docDummy
importDocumentation :: forall docDummy. docDummy
importDocumentation = [Char] -> docDummy
forall a. HasCallStack => [Char] -> a
error [Char]
"Auxiliary definition to write Haddock documentation for :-)"

-- | In order to keep things minimal, we define a very simple language for
-- arithmetic expressions.
data Expr
    = Add Expr Expr -- ^ expr + expr
    | Lit Integer   -- ^ 1, 2, -345, …
    deriving (Int -> Expr -> ShowS
[Expr] -> ShowS
Expr -> [Char]
(Int -> Expr -> ShowS)
-> (Expr -> [Char]) -> ([Expr] -> ShowS) -> Show Expr
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expr -> ShowS
showsPrec :: Int -> Expr -> ShowS
$cshow :: Expr -> [Char]
show :: Expr -> [Char]
$cshowList :: [Expr] -> ShowS
showList :: [Expr] -> ShowS
Show)

-- | The parser is straightforward: there are literal integers, and
-- parenthesized additions. We require parentheses in order to keep the example
-- super simple as to not worry about operator precedence.
--
-- It is useful to use /tokenizing/ functions to write parsers. Roughly
-- speaking, these automatically skip trailing whitespace on their own, so that
-- the parser isn’t cluttered with 'skipWhitespace' calls. 'symbolic' for
-- example parses a 'Char' and then skips trailing whitespace; there is also the
-- more primitive 'char' function that just parses its argument and nothing
-- else.
parseExpr :: Parser Expr
parseExpr :: Parser Expr
parseExpr = Parser Expr
parseAdd Parser Expr -> Parser Expr -> Parser Expr
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser Expr
parseLit
  where
    parseAdd :: Parser Expr
parseAdd = Parser Expr -> Parser Expr
forall (m :: * -> *) a. TokenParsing m => m a -> m a
parens (Parser Expr -> Parser Expr) -> Parser Expr -> Parser Expr
forall a b. (a -> b) -> a -> b
$ do
        Expr
x <- Parser Expr
parseExpr
        Char
_ <- Char -> Parser Char
forall (m :: * -> *). TokenParsing m => Char -> m Char
symbolic Char
'+'
        Expr
y <- Parser Expr
parseExpr
        Expr -> Parser Expr
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Expr -> Expr -> Expr
Add Expr
x Expr
y)
    parseLit :: Parser Expr
parseLit = Integer -> Expr
Lit (Integer -> Expr) -> Parser Integer -> Parser Expr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Integer
forall (m :: * -> *). TokenParsing m => m Integer
integer

-- | We can now use our parser to convert a 'String' to an 'Expr',
--
-- @
-- parseString parseExpr mempty "(1 + (2 + 3))"
-- @
--
-- > Success (Add (Lit 1) (Add (Lit 2) (Lit 3)))
--
-- When we provide ill-formed input, we get a nice error message with an arrow
-- to the location where the error occurred:
--
-- @
-- parseString parseExpr mempty "(1 + 2 + 3))"
-- @
--
-- > (interactive):1:8: error: expected: ")"
-- > 1 | (1 + 2 + 3))<EOF>
-- >   |        ^
examples :: docDummy
examples :: forall docDummy. docDummy
examples = [Char] -> docDummy
forall a. HasCallStack => [Char] -> a
error [Char]
"Haddock dummy for documentation"