{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE CPP #-}
-- | General parsers, functions and datatypes for all Shakespeare languages.
module Text.Shakespeare.Base
    ( Deref (..)
    , Ident (..)
    , Scope
    , parseDeref
    , parseHash
    , parseVar
    , parseVarString
    , parseAt
    , parseUrl
    , parseUrlString
    , parseCaret
    , parseUnder
    , parseInt
    , parseIntString
    , derefToExp
    , flattenDeref
    , readUtf8File
    , readUtf8FileString
    , readFileQ
    , readFileRecompileQ
    ) where

import Language.Haskell.TH.Syntax hiding (makeRelativeToProject)
import Language.Haskell.TH (appE)
import Data.Char (isUpper, isSymbol, isPunctuation, isAscii)
import Data.FileEmbed (makeRelativeToProject)
import Text.ParserCombinators.Parsec
import Text.Parsec.Prim (Parsec)
import Data.List (intercalate)
import Data.Ratio (Ratio, numerator, denominator, (%))
import Data.Data (Data)
import Data.Typeable (Typeable)
import qualified Data.Text.Lazy as TL
import qualified System.IO as SIO
import qualified Data.Text.Lazy.IO as TIO
import Control.Monad (when)

newtype Ident = Ident String
    deriving (Int -> Ident -> ShowS
[Ident] -> ShowS
Ident -> String
(Int -> Ident -> ShowS)
-> (Ident -> String) -> ([Ident] -> ShowS) -> Show Ident
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ident] -> ShowS
$cshowList :: [Ident] -> ShowS
show :: Ident -> String
$cshow :: Ident -> String
showsPrec :: Int -> Ident -> ShowS
$cshowsPrec :: Int -> Ident -> ShowS
Show, Ident -> Ident -> Bool
(Ident -> Ident -> Bool) -> (Ident -> Ident -> Bool) -> Eq Ident
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ident -> Ident -> Bool
$c/= :: Ident -> Ident -> Bool
== :: Ident -> Ident -> Bool
$c== :: Ident -> Ident -> Bool
Eq, ReadPrec [Ident]
ReadPrec Ident
Int -> ReadS Ident
ReadS [Ident]
(Int -> ReadS Ident)
-> ReadS [Ident]
-> ReadPrec Ident
-> ReadPrec [Ident]
-> Read Ident
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Ident]
$creadListPrec :: ReadPrec [Ident]
readPrec :: ReadPrec Ident
$creadPrec :: ReadPrec Ident
readList :: ReadS [Ident]
$creadList :: ReadS [Ident]
readsPrec :: Int -> ReadS Ident
$creadsPrec :: Int -> ReadS Ident
Read, Typeable Ident
DataType
Constr
Typeable Ident
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Ident -> c Ident)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Ident)
-> (Ident -> Constr)
-> (Ident -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Ident))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident))
-> ((forall b. Data b => b -> b) -> Ident -> Ident)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r)
-> (forall u. (forall d. Data d => d -> u) -> Ident -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Ident -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Ident -> m Ident)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Ident -> m Ident)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Ident -> m Ident)
-> Data Ident
Ident -> DataType
Ident -> Constr
(forall b. Data b => b -> b) -> Ident -> Ident
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ident -> c Ident
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ident
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Ident -> u
forall u. (forall d. Data d => d -> u) -> Ident -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ident
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ident -> c Ident
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Ident)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident)
$cIdent :: Constr
$tIdent :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Ident -> m Ident
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
gmapMp :: (forall d. Data d => d -> m d) -> Ident -> m Ident
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
gmapM :: (forall d. Data d => d -> m d) -> Ident -> m Ident
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
gmapQi :: Int -> (forall d. Data d => d -> u) -> Ident -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Ident -> u
gmapQ :: (forall d. Data d => d -> u) -> Ident -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Ident -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
gmapT :: (forall b. Data b => b -> b) -> Ident -> Ident
$cgmapT :: (forall b. Data b => b -> b) -> Ident -> Ident
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Ident)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Ident)
dataTypeOf :: Ident -> DataType
$cdataTypeOf :: Ident -> DataType
toConstr :: Ident -> Constr
$ctoConstr :: Ident -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ident
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ident
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ident -> c Ident
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ident -> c Ident
$cp1Data :: Typeable Ident
Data, Typeable, Eq Ident
Eq Ident
-> (Ident -> Ident -> Ordering)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Ident)
-> (Ident -> Ident -> Ident)
-> Ord Ident
Ident -> Ident -> Bool
Ident -> Ident -> Ordering
Ident -> Ident -> Ident
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Ident -> Ident -> Ident
$cmin :: Ident -> Ident -> Ident
max :: Ident -> Ident -> Ident
$cmax :: Ident -> Ident -> Ident
>= :: Ident -> Ident -> Bool
$c>= :: Ident -> Ident -> Bool
> :: Ident -> Ident -> Bool
$c> :: Ident -> Ident -> Bool
<= :: Ident -> Ident -> Bool
$c<= :: Ident -> Ident -> Bool
< :: Ident -> Ident -> Bool
$c< :: Ident -> Ident -> Bool
compare :: Ident -> Ident -> Ordering
$ccompare :: Ident -> Ident -> Ordering
$cp1Ord :: Eq Ident
Ord, Ident -> Q Exp
Ident -> Q (TExp Ident)
(Ident -> Q Exp) -> (Ident -> Q (TExp Ident)) -> Lift Ident
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: Ident -> Q (TExp Ident)
$cliftTyped :: Ident -> Q (TExp Ident)
lift :: Ident -> Q Exp
$clift :: Ident -> Q Exp
Lift)

type Scope = [(Ident, Exp)]

data Deref = DerefModulesIdent [String] Ident
           | DerefIdent Ident
           | DerefIntegral Integer
           | DerefRational Rational
           | DerefString String
           | DerefBranch Deref Deref
           | DerefList [Deref]
           | DerefTuple [Deref]
    deriving (Int -> Deref -> ShowS
[Deref] -> ShowS
Deref -> String
(Int -> Deref -> ShowS)
-> (Deref -> String) -> ([Deref] -> ShowS) -> Show Deref
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Deref] -> ShowS
$cshowList :: [Deref] -> ShowS
show :: Deref -> String
$cshow :: Deref -> String
showsPrec :: Int -> Deref -> ShowS
$cshowsPrec :: Int -> Deref -> ShowS
Show, Deref -> Deref -> Bool
(Deref -> Deref -> Bool) -> (Deref -> Deref -> Bool) -> Eq Deref
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Deref -> Deref -> Bool
$c/= :: Deref -> Deref -> Bool
== :: Deref -> Deref -> Bool
$c== :: Deref -> Deref -> Bool
Eq, ReadPrec [Deref]
ReadPrec Deref
Int -> ReadS Deref
ReadS [Deref]
(Int -> ReadS Deref)
-> ReadS [Deref]
-> ReadPrec Deref
-> ReadPrec [Deref]
-> Read Deref
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Deref]
$creadListPrec :: ReadPrec [Deref]
readPrec :: ReadPrec Deref
$creadPrec :: ReadPrec Deref
readList :: ReadS [Deref]
$creadList :: ReadS [Deref]
readsPrec :: Int -> ReadS Deref
$creadsPrec :: Int -> ReadS Deref
Read, Typeable Deref
DataType
Constr
Typeable Deref
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Deref -> c Deref)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Deref)
-> (Deref -> Constr)
-> (Deref -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Deref))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Deref))
-> ((forall b. Data b => b -> b) -> Deref -> Deref)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r)
-> (forall u. (forall d. Data d => d -> u) -> Deref -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Deref -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Deref -> m Deref)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Deref -> m Deref)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Deref -> m Deref)
-> Data Deref
Deref -> DataType
Deref -> Constr
(forall b. Data b => b -> b) -> Deref -> Deref
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Deref -> c Deref
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Deref
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Deref -> u
forall u. (forall d. Data d => d -> u) -> Deref -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Deref -> m Deref
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Deref -> m Deref
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Deref
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Deref -> c Deref
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Deref)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Deref)
$cDerefTuple :: Constr
$cDerefList :: Constr
$cDerefBranch :: Constr
$cDerefString :: Constr
$cDerefRational :: Constr
$cDerefIntegral :: Constr
$cDerefIdent :: Constr
$cDerefModulesIdent :: Constr
$tDeref :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Deref -> m Deref
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Deref -> m Deref
gmapMp :: (forall d. Data d => d -> m d) -> Deref -> m Deref
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Deref -> m Deref
gmapM :: (forall d. Data d => d -> m d) -> Deref -> m Deref
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Deref -> m Deref
gmapQi :: Int -> (forall d. Data d => d -> u) -> Deref -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Deref -> u
gmapQ :: (forall d. Data d => d -> u) -> Deref -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Deref -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r
gmapT :: (forall b. Data b => b -> b) -> Deref -> Deref
$cgmapT :: (forall b. Data b => b -> b) -> Deref -> Deref
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Deref)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Deref)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Deref)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Deref)
dataTypeOf :: Deref -> DataType
$cdataTypeOf :: Deref -> DataType
toConstr :: Deref -> Constr
$ctoConstr :: Deref -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Deref
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Deref
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Deref -> c Deref
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Deref -> c Deref
$cp1Data :: Typeable Deref
Data, Typeable, Eq Deref
Eq Deref
-> (Deref -> Deref -> Ordering)
-> (Deref -> Deref -> Bool)
-> (Deref -> Deref -> Bool)
-> (Deref -> Deref -> Bool)
-> (Deref -> Deref -> Bool)
-> (Deref -> Deref -> Deref)
-> (Deref -> Deref -> Deref)
-> Ord Deref
Deref -> Deref -> Bool
Deref -> Deref -> Ordering
Deref -> Deref -> Deref
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Deref -> Deref -> Deref
$cmin :: Deref -> Deref -> Deref
max :: Deref -> Deref -> Deref
$cmax :: Deref -> Deref -> Deref
>= :: Deref -> Deref -> Bool
$c>= :: Deref -> Deref -> Bool
> :: Deref -> Deref -> Bool
$c> :: Deref -> Deref -> Bool
<= :: Deref -> Deref -> Bool
$c<= :: Deref -> Deref -> Bool
< :: Deref -> Deref -> Bool
$c< :: Deref -> Deref -> Bool
compare :: Deref -> Deref -> Ordering
$ccompare :: Deref -> Deref -> Ordering
$cp1Ord :: Eq Deref
Ord, Deref -> Q Exp
Deref -> Q (TExp Deref)
(Deref -> Q Exp) -> (Deref -> Q (TExp Deref)) -> Lift Deref
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: Deref -> Q (TExp Deref)
$cliftTyped :: Deref -> Q (TExp Deref)
lift :: Deref -> Q Exp
$clift :: Deref -> Q Exp
Lift)

derefParens, derefCurlyBrackets :: UserParser a Deref
derefParens :: UserParser a Deref
derefParens        = ParsecT String a Identity Char
-> ParsecT String a Identity Char
-> UserParser a Deref
-> UserParser a Deref
forall s (m :: * -> *) t u open close a.
Stream s m t =>
ParsecT s u m open
-> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a
between (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'(') (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')') UserParser a Deref
forall a. UserParser a Deref
parseDeref
derefCurlyBrackets :: UserParser a Deref
derefCurlyBrackets = ParsecT String a Identity Char
-> ParsecT String a Identity Char
-> UserParser a Deref
-> UserParser a Deref
forall s (m :: * -> *) t u open close a.
Stream s m t =>
ParsecT s u m open
-> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a
between (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{') (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'}') UserParser a Deref
forall a. UserParser a Deref
parseDeref

derefList, derefTuple :: UserParser a Deref
derefList :: UserParser a Deref
derefList = ParsecT String a Identity Char
-> ParsecT String a Identity Char
-> UserParser a Deref
-> UserParser a Deref
forall s (m :: * -> *) t u open close a.
Stream s m t =>
ParsecT s u m open
-> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a
between (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'[') (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
']') (([Deref] -> Deref)
-> ParsecT String a Identity [Deref] -> UserParser a Deref
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Deref] -> Deref
DerefList (ParsecT String a Identity [Deref] -> UserParser a Deref)
-> ParsecT String a Identity [Deref] -> UserParser a Deref
forall a b. (a -> b) -> a -> b
$ UserParser a Deref
-> ParsecT String a Identity Char
-> ParsecT String a Identity [Deref]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy UserParser a Deref
forall a. UserParser a Deref
parseDeref (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
','))
derefTuple :: UserParser a Deref
derefTuple = UserParser a Deref -> UserParser a Deref
forall tok st a. GenParser tok st a -> GenParser tok st a
try (UserParser a Deref -> UserParser a Deref)
-> UserParser a Deref -> UserParser a Deref
forall a b. (a -> b) -> a -> b
$ do
  Char
_ <- Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'('
  [Deref]
x <- UserParser a Deref
-> ParsecT String a Identity Char
-> ParsecT String a Identity [Deref]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy1 UserParser a Deref
forall a. UserParser a Deref
parseDeref (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
',')
  Bool
-> ParsecT String a Identity () -> ParsecT String a Identity ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([Deref] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Deref]
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
2) (ParsecT String a Identity () -> ParsecT String a Identity ())
-> ParsecT String a Identity () -> ParsecT String a Identity ()
forall a b. (a -> b) -> a -> b
$ ParsecT String a Identity ()
forall tok st a. GenParser tok st a
pzero
  Char
_ <- Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')'
  Deref -> UserParser a Deref
forall (m :: * -> *) a. Monad m => a -> m a
return (Deref -> UserParser a Deref) -> Deref -> UserParser a Deref
forall a b. (a -> b) -> a -> b
$ [Deref] -> Deref
DerefTuple [Deref]
x

parseDeref :: UserParser a Deref
parseDeref :: UserParser a Deref
parseDeref = do
    ParsecT String a Identity Char -> ParsecT String a Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (String -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
" \t")
    UserParser a Deref
forall a. UserParser a Deref
derefList UserParser a Deref -> UserParser a Deref -> UserParser a Deref
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> UserParser a Deref
forall a. UserParser a Deref
derefTuple UserParser a Deref -> UserParser a Deref -> UserParser a Deref
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> UserParser a Deref
forall a. UserParser a Deref
derefOther
  where
    derefOther :: ParsecT String u Identity Deref
derefOther = do
        Deref
x <- ParsecT String u Identity Deref
forall a. UserParser a Deref
derefSingle
        Deref -> ParsecT String u Identity Deref
forall st. Deref -> GenParser Char st Deref
derefInfix Deref
x ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Deref -> ParsecT String u Identity Deref
forall st. Deref -> GenParser Char st Deref
derefPrefix Deref
x
    delim :: ParsecT String u Identity ()
delim = (ParsecT String u Identity Char -> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
' ') ParsecT String u Identity String
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ParsecT String u Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return())
            ParsecT String u Identity ()
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity () -> ParsecT String u Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
"(\"" ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ParsecT String u Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
    derefOp :: GenParser Char st Deref
derefOp = GenParser Char st Deref -> GenParser Char st Deref
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st Deref -> GenParser Char st Deref)
-> GenParser Char st Deref -> GenParser Char st Deref
forall a b. (a -> b) -> a -> b
$ do
            Char
_ <- Char -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'('
            String
x <- ParsecT String st Identity Char
-> ParsecT String st Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT String st Identity Char
 -> ParsecT String st Identity String)
-> ParsecT String st Identity Char
-> ParsecT String st Identity String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
" \t\n\r()"
            Char
_ <- Char -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')'
            Deref -> GenParser Char st Deref
forall (m :: * -> *) a. Monad m => a -> m a
return (Deref -> GenParser Char st Deref)
-> Deref -> GenParser Char st Deref
forall a b. (a -> b) -> a -> b
$ Ident -> Deref
DerefIdent (Ident -> Deref) -> Ident -> Deref
forall a b. (a -> b) -> a -> b
$ String -> Ident
Ident String
x

    -- See: http://www.haskell.org/onlinereport/haskell2010/haskellch2.html#x7-160002.2
    isOperatorChar :: Char -> Bool
isOperatorChar Char
c
        | Char -> Bool
isAscii Char
c = Char
c Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
"!#$%&*+./<=>?@\\^|-~:"
        | Bool
otherwise = Char -> Bool
isSymbol Char
c Bool -> Bool -> Bool
|| Char -> Bool
isPunctuation Char
c

    derefPrefix :: Deref -> ParsecT String u Identity Deref
derefPrefix Deref
x = do
        Deref
res <- ([Deref] -> [Deref]) -> ParsecT String u Identity Deref
forall (t :: * -> *) u.
Foldable t =>
([Deref] -> t Deref) -> ParsecT String u Identity Deref
deref' (([Deref] -> [Deref]) -> ParsecT String u Identity Deref)
-> ([Deref] -> [Deref]) -> ParsecT String u Identity Deref
forall a b. (a -> b) -> a -> b
$ (:) Deref
x
        ParsecT String u Identity Char -> ParsecT String u Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (ParsecT String u Identity Char -> ParsecT String u Identity ())
-> ParsecT String u Identity Char -> ParsecT String u Identity ()
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
" \t"
        Deref -> ParsecT String u Identity Deref
forall (m :: * -> *) a. Monad m => a -> m a
return Deref
res
    derefInfix :: Deref -> GenParser Char st Deref
derefInfix Deref
x = GenParser Char st Deref -> GenParser Char st Deref
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st Deref -> GenParser Char st Deref)
-> GenParser Char st Deref -> GenParser Char st Deref
forall a b. (a -> b) -> a -> b
$ do
        ()
_ <- ParsecT String st Identity ()
forall u. ParsecT String u Identity ()
delim
        [Deref]
xs <- GenParser Char st Deref -> ParsecT String st Identity [Deref]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (GenParser Char st Deref -> ParsecT String st Identity [Deref])
-> GenParser Char st Deref -> ParsecT String st Identity [Deref]
forall a b. (a -> b) -> a -> b
$ GenParser Char st Deref -> GenParser Char st Deref
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st Deref -> GenParser Char st Deref)
-> GenParser Char st Deref -> GenParser Char st Deref
forall a b. (a -> b) -> a -> b
$ GenParser Char st Deref
forall a. UserParser a Deref
derefSingle GenParser Char st Deref
-> (Deref -> GenParser Char st Deref) -> GenParser Char st Deref
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Deref
x' -> ParsecT String st Identity ()
forall u. ParsecT String u Identity ()
delim ParsecT String st Identity ()
-> GenParser Char st Deref -> GenParser Char st Deref
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Deref -> GenParser Char st Deref
forall (m :: * -> *) a. Monad m => a -> m a
return Deref
x'
        String
op <- ParsecT String st Identity Char
-> ParsecT String st Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ((Char -> Bool) -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
satisfy Char -> Bool
isOperatorChar) ParsecT String st Identity String
-> String -> ParsecT String st Identity String
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"operator"
        -- special handling for $, which we don't deal with
        Bool
-> ParsecT String st Identity () -> ParsecT String st Identity ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String
op String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"$") (ParsecT String st Identity () -> ParsecT String st Identity ())
-> ParsecT String st Identity () -> ParsecT String st Identity ()
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String st Identity ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"don't handle $"
        let op' :: Deref
op' = Ident -> Deref
DerefIdent (Ident -> Deref) -> Ident -> Deref
forall a b. (a -> b) -> a -> b
$ String -> Ident
Ident String
op
        [Deref]
ys <- GenParser Char st Deref -> ParsecT String st Identity [Deref]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (GenParser Char st Deref -> ParsecT String st Identity [Deref])
-> GenParser Char st Deref -> ParsecT String st Identity [Deref]
forall a b. (a -> b) -> a -> b
$ GenParser Char st Deref -> GenParser Char st Deref
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st Deref -> GenParser Char st Deref)
-> GenParser Char st Deref -> GenParser Char st Deref
forall a b. (a -> b) -> a -> b
$ ParsecT String st Identity ()
forall u. ParsecT String u Identity ()
delim ParsecT String st Identity ()
-> GenParser Char st Deref -> GenParser Char st Deref
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> GenParser Char st Deref
forall a. UserParser a Deref
derefSingle
        ParsecT String st Identity Char -> ParsecT String st Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (ParsecT String st Identity Char -> ParsecT String st Identity ())
-> ParsecT String st Identity Char -> ParsecT String st Identity ()
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
" \t"
        Deref -> GenParser Char st Deref
forall (m :: * -> *) a. Monad m => a -> m a
return (Deref -> GenParser Char st Deref)
-> Deref -> GenParser Char st Deref
forall a b. (a -> b) -> a -> b
$ Deref -> Deref -> Deref
DerefBranch (Deref -> Deref -> Deref
DerefBranch Deref
op' (Deref -> Deref) -> Deref -> Deref
forall a b. (a -> b) -> a -> b
$ (Deref -> Deref -> Deref) -> [Deref] -> Deref
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 Deref -> Deref -> Deref
DerefBranch ([Deref] -> Deref) -> [Deref] -> Deref
forall a b. (a -> b) -> a -> b
$ Deref
x Deref -> [Deref] -> [Deref]
forall a. a -> [a] -> [a]
: [Deref]
xs) ((Deref -> Deref -> Deref) -> [Deref] -> Deref
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 Deref -> Deref -> Deref
DerefBranch [Deref]
ys)
    derefSingle :: ParsecT String u Identity Deref
derefSingle = ParsecT String u Identity Deref
forall a. UserParser a Deref
derefTuple ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity Deref
forall a. UserParser a Deref
derefList ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity Deref
forall a. UserParser a Deref
derefOp ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity Deref
forall a. UserParser a Deref
derefParens ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity Deref
forall a. UserParser a Deref
numeric ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity Deref
forall a. UserParser a Deref
strLit ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity Deref
forall a. UserParser a Deref
ident
    deref' :: ([Deref] -> t Deref) -> ParsecT String u Identity Deref
deref' [Deref] -> t Deref
lhs =
        ParsecT String u Identity Deref
forall a. UserParser a Deref
dollar ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity Deref
derefSingle'
               ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Deref -> ParsecT String u Identity Deref
forall (m :: * -> *) a. Monad m => a -> m a
return ((Deref -> Deref -> Deref) -> t Deref -> Deref
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 Deref -> Deref -> Deref
DerefBranch (t Deref -> Deref) -> t Deref -> Deref
forall a b. (a -> b) -> a -> b
$ [Deref] -> t Deref
lhs [])
      where
        dollar :: ParsecT String st Identity Deref
dollar = do
            Char
_ <- GenParser Char st Char -> GenParser Char st Char
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st Char -> GenParser Char st Char)
-> GenParser Char st Char -> GenParser Char st Char
forall a b. (a -> b) -> a -> b
$ ParsecT String st Identity ()
forall u. ParsecT String u Identity ()
delim ParsecT String st Identity ()
-> GenParser Char st Char -> GenParser Char st Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> GenParser Char st Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'$'
            Deref
rhs <- ParsecT String st Identity Deref
forall a. UserParser a Deref
parseDeref
            let lhs' :: Deref
lhs' = (Deref -> Deref -> Deref) -> t Deref -> Deref
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 Deref -> Deref -> Deref
DerefBranch (t Deref -> Deref) -> t Deref -> Deref
forall a b. (a -> b) -> a -> b
$ [Deref] -> t Deref
lhs []
            Deref -> ParsecT String st Identity Deref
forall (m :: * -> *) a. Monad m => a -> m a
return (Deref -> ParsecT String st Identity Deref)
-> Deref -> ParsecT String st Identity Deref
forall a b. (a -> b) -> a -> b
$ Deref -> Deref -> Deref
DerefBranch Deref
lhs' Deref
rhs
        derefSingle' :: ParsecT String u Identity Deref
derefSingle' = do
            Deref
x <- ParsecT String u Identity Deref -> ParsecT String u Identity Deref
forall tok st a. GenParser tok st a -> GenParser tok st a
try (ParsecT String u Identity Deref
 -> ParsecT String u Identity Deref)
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
forall a b. (a -> b) -> a -> b
$ ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
delim ParsecT String u Identity ()
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity Deref
forall a. UserParser a Deref
derefSingle
            ([Deref] -> t Deref) -> ParsecT String u Identity Deref
deref' (([Deref] -> t Deref) -> ParsecT String u Identity Deref)
-> ([Deref] -> t Deref) -> ParsecT String u Identity Deref
forall a b. (a -> b) -> a -> b
$ [Deref] -> t Deref
lhs ([Deref] -> t Deref) -> ([Deref] -> [Deref]) -> [Deref] -> t Deref
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) Deref
x
    numeric :: ParsecT String u Identity Deref
numeric = do
        String
n <- (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'-' ParsecT String u Identity Char
-> ParsecT String u Identity String
-> ParsecT String u Identity String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> ParsecT String u Identity String
forall (m :: * -> *) a. Monad m => a -> m a
return String
"-") ParsecT String u Identity String
-> ParsecT String u Identity String
-> ParsecT String u Identity String
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> String -> ParsecT String u Identity String
forall (m :: * -> *) a. Monad m => a -> m a
return String
""
        String
x <- ParsecT String u Identity Char -> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit
        Maybe String
y <- (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'.' ParsecT String u Identity Char
-> ParsecT String u Identity (Maybe String)
-> ParsecT String u Identity (Maybe String)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (String -> Maybe String)
-> ParsecT String u Identity String
-> ParsecT String u Identity (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Maybe String
forall a. a -> Maybe a
Just (ParsecT String u Identity Char -> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit)) ParsecT String u Identity (Maybe String)
-> ParsecT String u Identity (Maybe String)
-> ParsecT String u Identity (Maybe String)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Maybe String -> ParsecT String u Identity (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
        Deref -> ParsecT String u Identity Deref
forall (m :: * -> *) a. Monad m => a -> m a
return (Deref -> ParsecT String u Identity Deref)
-> Deref -> ParsecT String u Identity Deref
forall a b. (a -> b) -> a -> b
$ case Maybe String
y of
            Maybe String
Nothing -> Integer -> Deref
DerefIntegral (Integer -> Deref) -> Integer -> Deref
forall a b. (a -> b) -> a -> b
$ String -> String -> Integer
forall a. Read a => String -> String -> a
read' String
"Integral" (String -> Integer) -> String -> Integer
forall a b. (a -> b) -> a -> b
$ String
n String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
x
            Just String
z -> Rational -> Deref
DerefRational (Rational -> Deref) -> Rational -> Deref
forall a b. (a -> b) -> a -> b
$ Double -> Rational
forall a. Real a => a -> Rational
toRational
                       (String -> String -> Double
forall a. Read a => String -> String -> a
read' String
"Rational" (String -> Double) -> String -> Double
forall a b. (a -> b) -> a -> b
$ String
n String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
x String -> ShowS
forall a. [a] -> [a] -> [a]
++ Char
'.' Char -> ShowS
forall a. a -> [a] -> [a]
: String
z :: Double)
    strLit :: ParsecT String u Identity Deref
strLit = do
        Char
_ <- Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"'
        String
chars <- ParsecT String u Identity Char -> ParsecT String u Identity String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT String u Identity Char
forall u. ParsecT String u Identity Char
quotedChar
        Char
_ <- Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"'
        Deref -> ParsecT String u Identity Deref
forall (m :: * -> *) a. Monad m => a -> m a
return (Deref -> ParsecT String u Identity Deref)
-> Deref -> ParsecT String u Identity Deref
forall a b. (a -> b) -> a -> b
$ String -> Deref
DerefString String
chars
    quotedChar :: ParsecT String u Identity Char
quotedChar = (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT String u Identity Char
-> ParsecT String u Identity Char -> ParsecT String u Identity Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity Char
forall u. ParsecT String u Identity Char
escapedChar) ParsecT String u Identity Char
-> ParsecT String u Identity Char -> ParsecT String u Identity Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\""
    escapedChar :: ParsecT String u Identity Char
escapedChar =
        let cecs :: [(Char, Char)]
cecs = [(Char
'n', Char
'\n'),  (Char
'r', Char
'\r'), (Char
'b', Char
'\b'), (Char
't', Char
'\t')
                   ,(Char
'\\', Char
'\\'), (Char
'"', Char
'"'),  (Char
'\'', Char
'\'')]
        in [ParsecT String u Identity Char] -> ParsecT String u Identity Char
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
c ParsecT String u Identity Char
-> ParsecT String u Identity Char -> ParsecT String u Identity Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT String u Identity Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
ec | (Char
c, Char
ec) <- [(Char, Char)]
cecs]
    ident :: ParsecT String u Identity Deref
ident = do
        [String]
mods <- ParsecT String u Identity String
-> ParsecT String u Identity [String]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT String u Identity String
forall st. GenParser Char st String
modul
        String
func <- ParsecT String u Identity Char -> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
alphaNum ParsecT String u Identity Char
-> ParsecT String u Identity Char -> ParsecT String u Identity Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'_' ParsecT String u Identity Char
-> ParsecT String u Identity Char -> ParsecT String u Identity Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\'')
        let func' :: Ident
func' = String -> Ident
Ident String
func
        Deref -> ParsecT String u Identity Deref
forall (m :: * -> *) a. Monad m => a -> m a
return (Deref -> ParsecT String u Identity Deref)
-> Deref -> ParsecT String u Identity Deref
forall a b. (a -> b) -> a -> b
$
            if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
mods
                then Ident -> Deref
DerefIdent Ident
func'
                else [String] -> Ident -> Deref
DerefModulesIdent [String]
mods Ident
func'
    modul :: GenParser Char st String
modul = GenParser Char st String -> GenParser Char st String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st String -> GenParser Char st String)
-> GenParser Char st String -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ do
        Char
c <- ParsecT String st Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
upper
        String
cs <- ParsecT String st Identity Char -> GenParser Char st String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT String st Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
alphaNum ParsecT String st Identity Char
-> ParsecT String st Identity Char
-> ParsecT String st Identity Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'_')
        Char
_ <- Char -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'.'
        String -> GenParser Char st String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> GenParser Char st String)
-> String -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: String
cs

read' :: Read a => String -> String -> a
read' :: String -> String -> a
read' String
t String
s =
    case ReadS a
forall a. Read a => ReadS a
reads String
s of
        (a
x, String
_):[(a, String)]
_ -> a
x
        [] -> String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
t String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" read failed: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
s

expType :: Ident -> Name -> Exp
expType :: Ident -> Name -> Exp
expType (Ident (Char
c:String
_)) = if Char -> Bool
isUpper Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':' then Name -> Exp
ConE else Name -> Exp
VarE
expType (Ident String
"") = String -> Name -> Exp
forall a. HasCallStack => String -> a
error String
"Bad Ident"

derefToExp :: Scope -> Deref -> Exp
derefToExp :: Scope -> Deref -> Exp
derefToExp Scope
s (DerefBranch Deref
x Deref
y) = Scope -> Deref -> Exp
derefToExp Scope
s Deref
x Exp -> Exp -> Exp
`AppE` Scope -> Deref -> Exp
derefToExp Scope
s Deref
y
derefToExp Scope
_ (DerefModulesIdent [String]
mods i :: Ident
i@(Ident String
s)) =
    Ident -> Name -> Exp
expType Ident
i (Name -> Exp) -> Name -> Exp
forall a b. (a -> b) -> a -> b
$ OccName -> NameFlavour -> Name
Name (String -> OccName
mkOccName String
s) (ModName -> NameFlavour
NameQ (ModName -> NameFlavour) -> ModName -> NameFlavour
forall a b. (a -> b) -> a -> b
$ String -> ModName
mkModName (String -> ModName) -> String -> ModName
forall a b. (a -> b) -> a -> b
$ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"." [String]
mods)
derefToExp Scope
scope (DerefIdent i :: Ident
i@(Ident String
s)) =
    case Ident -> Scope -> Maybe Exp
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Ident
i Scope
scope of
        Just Exp
e -> Exp
e
        Maybe Exp
Nothing -> Ident -> Name -> Exp
expType Ident
i (Name -> Exp) -> Name -> Exp
forall a b. (a -> b) -> a -> b
$ String -> Name
mkName String
s
derefToExp Scope
_ (DerefIntegral Integer
i) = Lit -> Exp
LitE (Lit -> Exp) -> Lit -> Exp
forall a b. (a -> b) -> a -> b
$ Integer -> Lit
IntegerL Integer
i
derefToExp Scope
_ (DerefRational Rational
r) = Lit -> Exp
LitE (Lit -> Exp) -> Lit -> Exp
forall a b. (a -> b) -> a -> b
$ Rational -> Lit
RationalL Rational
r
derefToExp Scope
_ (DerefString String
s) = Lit -> Exp
LitE (Lit -> Exp) -> Lit -> Exp
forall a b. (a -> b) -> a -> b
$ String -> Lit
StringL String
s
derefToExp Scope
s (DerefList [Deref]
ds) = [Exp] -> Exp
ListE ([Exp] -> Exp) -> [Exp] -> Exp
forall a b. (a -> b) -> a -> b
$ (Deref -> Exp) -> [Deref] -> [Exp]
forall a b. (a -> b) -> [a] -> [b]
map (Scope -> Deref -> Exp
derefToExp Scope
s) [Deref]
ds
derefToExp Scope
s (DerefTuple [Deref]
ds) = [Maybe Exp] -> Exp
TupE ([Maybe Exp] -> Exp) -> [Maybe Exp] -> Exp
forall a b. (a -> b) -> a -> b
$
#if MIN_VERSION_template_haskell(2,16,0)
                               (Exp -> Maybe Exp) -> [Exp] -> [Maybe Exp]
forall a b. (a -> b) -> [a] -> [b]
map Exp -> Maybe Exp
forall a. a -> Maybe a
Just ([Exp] -> [Maybe Exp]) -> [Exp] -> [Maybe Exp]
forall a b. (a -> b) -> a -> b
$
#endif
                               (Deref -> Exp) -> [Deref] -> [Exp]
forall a b. (a -> b) -> [a] -> [b]
map (Scope -> Deref -> Exp
derefToExp Scope
s) [Deref]
ds

-- FIXME shouldn't we use something besides a list here?
flattenDeref :: Deref -> Maybe [String]
flattenDeref :: Deref -> Maybe [String]
flattenDeref (DerefIdent (Ident String
x)) = [String] -> Maybe [String]
forall a. a -> Maybe a
Just [String
x]
flattenDeref (DerefBranch (DerefIdent (Ident String
x)) Deref
y) = do
    [String]
y' <- Deref -> Maybe [String]
flattenDeref Deref
y
    [String] -> Maybe [String]
forall a. a -> Maybe a
Just ([String] -> Maybe [String]) -> [String] -> Maybe [String]
forall a b. (a -> b) -> a -> b
$ [String]
y' [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
x]
flattenDeref Deref
_ = Maybe [String]
forall a. Maybe a
Nothing

parseHash :: UserParser a (Either String Deref)
parseHash :: UserParser a (Either String Deref)
parseHash = Char -> UserParser a (Either String Deref)
forall a. Char -> UserParser a (Either String Deref)
parseVar Char
'#'

curlyBrackets :: UserParser a String
curlyBrackets :: UserParser a String
curlyBrackets = do
  Char
_<- Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{'
  String
var <- ParsecT String a Identity Char -> UserParser a String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT String a Identity Char -> UserParser a String)
-> ParsecT String a Identity Char -> UserParser a String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"}"
  Char
_<- Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'}'
  String -> UserParser a String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> UserParser a String) -> String -> UserParser a String
forall a b. (a -> b) -> a -> b
$ (Char
'{'Char -> ShowS
forall a. a -> [a] -> [a]
:String
var) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"}"


type UserParser a = Parsec String a

parseVar :: Char -> UserParser a (Either String Deref)
parseVar :: Char -> UserParser a (Either String Deref)
parseVar Char
c = do
    Char
_ <- Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
c
    (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT String a Identity Char
-> UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String Deref -> UserParser a (Either String Deref)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String Deref
forall a b. a -> Either a b
Left [Char
c])) UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do
        Deref
deref <- UserParser a Deref
forall a. UserParser a Deref
derefCurlyBrackets
        Either String Deref -> UserParser a (Either String Deref)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Deref -> UserParser a (Either String Deref))
-> Either String Deref -> UserParser a (Either String Deref)
forall a b. (a -> b) -> a -> b
$ Deref -> Either String Deref
forall a b. b -> Either a b
Right Deref
deref) UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do
            -- Check for hash just before newline
            ()
_ <- ParsecT String a Identity () -> ParsecT String a Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (String -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
"\r\n" ParsecT String a Identity Char
-> ParsecT String a Identity () -> ParsecT String a Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ParsecT String a Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) ParsecT String a Identity ()
-> ParsecT String a Identity () -> ParsecT String a Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String a Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
            Either String Deref -> UserParser a (Either String Deref)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Deref -> UserParser a (Either String Deref))
-> Either String Deref -> UserParser a (Either String Deref)
forall a b. (a -> b) -> a -> b
$ String -> Either String Deref
forall a b. a -> Either a b
Left String
""
            ) UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Either String Deref -> UserParser a (Either String Deref)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String Deref
forall a b. a -> Either a b
Left [Char
c])

parseAt :: UserParser a (Either String (Deref, Bool))
parseAt :: UserParser a (Either String (Deref, Bool))
parseAt = Char -> Char -> UserParser a (Either String (Deref, Bool))
forall a.
Char -> Char -> UserParser a (Either String (Deref, Bool))
parseUrl Char
'@' Char
'?'

parseUrl :: Char -> Char -> UserParser a (Either String (Deref, Bool))
parseUrl :: Char -> Char -> UserParser a (Either String (Deref, Bool))
parseUrl Char
c Char
d = do
    Char
_ <- Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
c
    (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT String a Identity Char
-> UserParser a (Either String (Deref, Bool))
-> UserParser a (Either String (Deref, Bool))
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String (Deref, Bool)
-> UserParser a (Either String (Deref, Bool))
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String (Deref, Bool)
forall a b. a -> Either a b
Left [Char
c])) UserParser a (Either String (Deref, Bool))
-> UserParser a (Either String (Deref, Bool))
-> UserParser a (Either String (Deref, Bool))
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do
        Bool
x <- (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
d ParsecT String a Identity Char
-> ParsecT String a Identity Bool -> ParsecT String a Identity Bool
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> ParsecT String a Identity Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True) ParsecT String a Identity Bool
-> ParsecT String a Identity Bool -> ParsecT String a Identity Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT String a Identity Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
        (do
            Deref
deref <- UserParser a Deref
forall a. UserParser a Deref
derefCurlyBrackets
            Either String (Deref, Bool)
-> UserParser a (Either String (Deref, Bool))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String (Deref, Bool)
 -> UserParser a (Either String (Deref, Bool)))
-> Either String (Deref, Bool)
-> UserParser a (Either String (Deref, Bool))
forall a b. (a -> b) -> a -> b
$ (Deref, Bool) -> Either String (Deref, Bool)
forall a b. b -> Either a b
Right (Deref
deref, Bool
x))
                UserParser a (Either String (Deref, Bool))
-> UserParser a (Either String (Deref, Bool))
-> UserParser a (Either String (Deref, Bool))
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Either String (Deref, Bool)
-> UserParser a (Either String (Deref, Bool))
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String (Deref, Bool)
forall a b. a -> Either a b
Left (String -> Either String (Deref, Bool))
-> String -> Either String (Deref, Bool)
forall a b. (a -> b) -> a -> b
$ if Bool
x then [Char
c, Char
d] else [Char
c]))

parseInterpolatedString :: Char -> UserParser a (Either String String)
parseInterpolatedString :: Char -> UserParser a (Either String String)
parseInterpolatedString Char
c = do
    Char
_ <- Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
c
    (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT String a Identity Char
-> UserParser a (Either String String)
-> UserParser a (Either String String)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String String -> UserParser a (Either String String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String String
forall a b. a -> Either a b
Left [Char
'\\', Char
c])) UserParser a (Either String String)
-> UserParser a (Either String String)
-> UserParser a (Either String String)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do
        String
bracketed <- UserParser a String
forall st. GenParser Char st String
curlyBrackets
        Either String String -> UserParser a (Either String String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String String -> UserParser a (Either String String))
-> Either String String -> UserParser a (Either String String)
forall a b. (a -> b) -> a -> b
$ String -> Either String String
forall a b. b -> Either a b
Right (Char
cChar -> ShowS
forall a. a -> [a] -> [a]
:String
bracketed)) UserParser a (Either String String)
-> UserParser a (Either String String)
-> UserParser a (Either String String)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Either String String -> UserParser a (Either String String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String String
forall a b. a -> Either a b
Left [Char
c])

parseVarString :: Char -> UserParser a (Either String String)
parseVarString :: Char -> UserParser a (Either String String)
parseVarString = Char -> UserParser a (Either String String)
forall a. Char -> UserParser a (Either String String)
parseInterpolatedString

parseUrlString :: Char -> Char -> UserParser a (Either String String)
parseUrlString :: Char -> Char -> UserParser a (Either String String)
parseUrlString Char
c Char
d = do
    Char
_ <- Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
c
    (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT String a Identity Char
-> UserParser a (Either String String)
-> UserParser a (Either String String)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String String -> UserParser a (Either String String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String String
forall a b. a -> Either a b
Left [Char
c, Char
'\\'])) UserParser a (Either String String)
-> UserParser a (Either String String)
-> UserParser a (Either String String)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do
        String
ds <- (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
d ParsecT String a Identity Char
-> ParsecT String a Identity String
-> ParsecT String a Identity String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> ParsecT String a Identity String
forall (m :: * -> *) a. Monad m => a -> m a
return [Char
d]) ParsecT String a Identity String
-> ParsecT String a Identity String
-> ParsecT String a Identity String
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> String -> ParsecT String a Identity String
forall (m :: * -> *) a. Monad m => a -> m a
return []
        (do String
bracketed <- ParsecT String a Identity String
forall st. GenParser Char st String
curlyBrackets
            Either String String -> UserParser a (Either String String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String String -> UserParser a (Either String String))
-> Either String String -> UserParser a (Either String String)
forall a b. (a -> b) -> a -> b
$ String -> Either String String
forall a b. b -> Either a b
Right (Char
cChar -> ShowS
forall a. a -> [a] -> [a]
:String
ds String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
bracketed))
                UserParser a (Either String String)
-> UserParser a (Either String String)
-> UserParser a (Either String String)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Either String String -> UserParser a (Either String String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String String
forall a b. a -> Either a b
Left (Char
cChar -> ShowS
forall a. a -> [a] -> [a]
:String
ds)))

parseIntString :: Char -> UserParser a (Either String String)
parseIntString :: Char -> UserParser a (Either String String)
parseIntString = Char -> UserParser a (Either String String)
forall a. Char -> UserParser a (Either String String)
parseInterpolatedString

parseCaret :: UserParser a (Either String Deref)
parseCaret :: UserParser a (Either String Deref)
parseCaret = Char -> UserParser a (Either String Deref)
forall a. Char -> UserParser a (Either String Deref)
parseInt Char
'^'

parseInt :: Char -> UserParser a (Either String Deref)
parseInt :: Char -> UserParser a (Either String Deref)
parseInt Char
c = do
    Char
_ <- Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
c
    (UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall tok st a. GenParser tok st a -> GenParser tok st a
try (UserParser a (Either String Deref)
 -> UserParser a (Either String Deref))
-> UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT String a Identity Char
-> ParsecT String a Identity Char -> ParsecT String a Identity Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{' ParsecT String a Identity Char
-> UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String Deref -> UserParser a (Either String Deref)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String Deref
forall a b. a -> Either a b
Left [Char
c, Char
'{'])) UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do
        Deref
deref <- UserParser a Deref
forall a. UserParser a Deref
derefCurlyBrackets
        Either String Deref -> UserParser a (Either String Deref)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Deref -> UserParser a (Either String Deref))
-> Either String Deref -> UserParser a (Either String Deref)
forall a b. (a -> b) -> a -> b
$ Deref -> Either String Deref
forall a b. b -> Either a b
Right Deref
deref) UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Either String Deref -> UserParser a (Either String Deref)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String Deref
forall a b. a -> Either a b
Left [Char
c])

parseUnder :: UserParser a (Either String Deref)
parseUnder :: UserParser a (Either String Deref)
parseUnder = do
    Char
_ <- Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'_'
    (Char -> ParsecT String a Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT String a Identity Char
-> UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String Deref -> UserParser a (Either String Deref)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String Deref
forall a b. a -> Either a b
Left String
"_")) UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do
        Deref
deref <- UserParser a Deref
forall a. UserParser a Deref
derefCurlyBrackets
        Either String Deref -> UserParser a (Either String Deref)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Deref -> UserParser a (Either String Deref))
-> Either String Deref -> UserParser a (Either String Deref)
forall a b. (a -> b) -> a -> b
$ Deref -> Either String Deref
forall a b. b -> Either a b
Right Deref
deref) UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
-> UserParser a (Either String Deref)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Either String Deref -> UserParser a (Either String Deref)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String Deref
forall a b. a -> Either a b
Left String
"_")

-- | Read file's content as `String`, converting newlines
--
-- @since 2.0.19
readUtf8FileString :: FilePath -> IO String
readUtf8FileString :: String -> IO String
readUtf8FileString String
fp = (Text -> String) -> IO Text -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> String
TL.unpack (IO Text -> IO String) -> IO Text -> IO String
forall a b. (a -> b) -> a -> b
$ String -> IO Text
readUtf8File String
fp

readUtf8File :: FilePath -> IO TL.Text
readUtf8File :: String -> IO Text
readUtf8File String
fp = do
    Handle
h <- String -> IOMode -> IO Handle
SIO.openFile String
fp IOMode
SIO.ReadMode
    Handle -> TextEncoding -> IO ()
SIO.hSetEncoding Handle
h TextEncoding
SIO.utf8_bom
    Text
ret <- Handle -> IO Text
TIO.hGetContents Handle
h
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> IO Text) -> Text -> IO Text
forall a b. (a -> b) -> a -> b
$
#ifdef WINDOWS
      TL.filter ('\r'/=) ret
#else
      Text
ret
#endif

-- | Embed file's content, converting newlines
--
-- @since 2.0.19
readFileQ :: FilePath -> Q String
readFileQ :: String -> Q String
readFileQ String
rawFp = do
  String
fp <- String -> Q String
makeRelativeToProject String
rawFp
  IO String -> Q String
forall (m :: * -> *) a. Quasi m => IO a -> m a
qRunIO (String -> IO String
readUtf8FileString String
fp)

-- | Embed file's content, converting newlines
-- and track file via ghc dependencies, recompiling on changes
--
-- @since 2.0.19
readFileRecompileQ :: FilePath -> Q String
readFileRecompileQ :: String -> Q String
readFileRecompileQ String
rawFp = do
  String
fp <- String -> Q String
makeRelativeToProject String
rawFp
  String -> Q ()
addDependentFile String
fp
  IO String -> Q String
forall (m :: * -> *) a. Quasi m => IO a -> m a
qRunIO (String -> IO String
readUtf8FileString String
fp)