{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE CPP #-}
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, isLower, isNumber)
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)
import Data.Maybe (mapMaybe)
import Data.List.NonEmpty (nonEmpty, NonEmpty ((:|)))
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
$cshowsPrec :: Int -> Ident -> ShowS
showsPrec :: Int -> Ident -> ShowS
$cshow :: Ident -> String
show :: Ident -> String
$cshowList :: [Ident] -> ShowS
showList :: [Ident] -> ShowS
Show, Ident -> Ident -> Bool
(Ident -> Ident -> Bool) -> (Ident -> Ident -> Bool) -> Eq Ident
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Ident -> Ident -> Bool
== :: Ident -> Ident -> Bool
$c/= :: Ident -> Ident -> Bool
/= :: 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
$creadsPrec :: Int -> ReadS Ident
readsPrec :: Int -> ReadS Ident
$creadList :: ReadS [Ident]
readList :: ReadS [Ident]
$creadPrec :: ReadPrec Ident
readPrec :: ReadPrec Ident
$creadListPrec :: ReadPrec [Ident]
readListPrec :: ReadPrec [Ident]
Read, Typeable Ident
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 -> Constr
Ident -> DataType
(forall b. Data b => b -> b) -> Ident -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ident -> c Ident
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ident -> c Ident
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ident
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ident
$ctoConstr :: Ident -> Constr
toConstr :: Ident -> Constr
$cdataTypeOf :: Ident -> DataType
dataTypeOf :: Ident -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Ident)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Ident)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident)
$cgmapT :: (forall b. Data b => b -> b) -> Ident -> Ident
gmapT :: (forall b. Data b => b -> b) -> Ident -> Ident
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Ident -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Ident -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Ident -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Ident -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ident -> m 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
$ccompare :: Ident -> Ident -> Ordering
compare :: Ident -> Ident -> Ordering
$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
>= :: Ident -> Ident -> Bool
$cmax :: Ident -> Ident -> Ident
max :: Ident -> Ident -> Ident
$cmin :: Ident -> Ident -> Ident
min :: Ident -> Ident -> Ident
Ord, (forall (m :: * -> *). Quote m => Ident -> m Exp)
-> (forall (m :: * -> *). Quote m => Ident -> Code m Ident)
-> Lift Ident
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Ident -> m Exp
forall (m :: * -> *). Quote m => Ident -> Code m Ident
$clift :: forall (m :: * -> *). Quote m => Ident -> m Exp
lift :: forall (m :: * -> *). Quote m => Ident -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => Ident -> Code m Ident
liftTyped :: forall (m :: * -> *). Quote m => Ident -> Code m Ident
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]
| DerefType String
| DerefGetField Deref String
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
$cshowsPrec :: Int -> Deref -> ShowS
showsPrec :: Int -> Deref -> ShowS
$cshow :: Deref -> String
show :: Deref -> String
$cshowList :: [Deref] -> ShowS
showList :: [Deref] -> ShowS
Show, Deref -> Deref -> Bool
(Deref -> Deref -> Bool) -> (Deref -> Deref -> Bool) -> Eq Deref
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Deref -> Deref -> Bool
== :: Deref -> Deref -> Bool
$c/= :: Deref -> Deref -> Bool
/= :: 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
$creadsPrec :: Int -> ReadS Deref
readsPrec :: Int -> ReadS Deref
$creadList :: ReadS [Deref]
readList :: ReadS [Deref]
$creadPrec :: ReadPrec Deref
readPrec :: ReadPrec Deref
$creadListPrec :: ReadPrec [Deref]
readListPrec :: ReadPrec [Deref]
Read, Typeable Deref
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 -> Constr
Deref -> DataType
(forall b. Data b => b -> b) -> Deref -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Deref -> c Deref
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Deref -> c Deref
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Deref
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Deref
$ctoConstr :: Deref -> Constr
toConstr :: Deref -> Constr
$cdataTypeOf :: Deref -> DataType
dataTypeOf :: Deref -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Deref)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Deref)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Deref)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Deref)
$cgmapT :: (forall b. Data b => b -> b) -> Deref -> Deref
gmapT :: (forall b. Data b => b -> b) -> Deref -> Deref
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Deref -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Deref -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Deref -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Deref -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Deref -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Deref -> m Deref
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Deref -> m 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
$ccompare :: Deref -> Deref -> Ordering
compare :: Deref -> Deref -> Ordering
$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
>= :: Deref -> Deref -> Bool
$cmax :: Deref -> Deref -> Deref
max :: Deref -> Deref -> Deref
$cmin :: Deref -> Deref -> Deref
min :: Deref -> Deref -> Deref
Ord, (forall (m :: * -> *). Quote m => Deref -> m Exp)
-> (forall (m :: * -> *). Quote m => Deref -> Code m Deref)
-> Lift Deref
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Deref -> m Exp
forall (m :: * -> *). Quote m => Deref -> Code m Deref
$clift :: forall (m :: * -> *). Quote m => Deref -> m Exp
lift :: forall (m :: * -> *). Quote m => Deref -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => Deref -> Code m Deref
liftTyped :: forall (m :: * -> *). Quote m => Deref -> Code m Deref
Lift)
derefParens, derefCurlyBrackets :: UserParser a Deref
derefParens :: forall a. UserParser a Deref
derefParens = ParsecT String a Identity Char
-> ParsecT String a Identity Char
-> ParsecT String a Identity Deref
-> ParsecT String a Identity 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
')') ParsecT String a Identity Deref
forall a. UserParser a Deref
parseDeref
derefCurlyBrackets :: forall a. UserParser a Deref
derefCurlyBrackets = ParsecT String a Identity Char
-> ParsecT String a Identity Char
-> ParsecT String a Identity Deref
-> ParsecT String a Identity 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
'}') ParsecT String a Identity Deref
forall a. UserParser a Deref
parseDeref
derefList, derefTuple :: UserParser a Deref
derefList :: forall a. UserParser a Deref
derefList = ParsecT String a Identity Char
-> ParsecT String a Identity Char
-> ParsecT String a Identity Deref
-> ParsecT String a Identity 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]
-> ParsecT String a Identity Deref
forall a b.
(a -> b)
-> ParsecT String a Identity a -> ParsecT String a Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Deref] -> Deref
DerefList (ParsecT String a Identity [Deref]
-> ParsecT String a Identity Deref)
-> ParsecT String a Identity [Deref]
-> ParsecT String a Identity Deref
forall a b. (a -> b) -> a -> b
$ ParsecT String a Identity 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 ParsecT String a Identity 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 :: forall a. UserParser a Deref
derefTuple = GenParser Char a Deref -> GenParser Char a Deref
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char a Deref -> GenParser Char a Deref)
-> GenParser Char a Deref -> GenParser Char 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 <- GenParser Char 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 GenParser Char 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 a. [a] -> 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 -> GenParser Char a Deref
forall a. a -> ParsecT String a Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Deref -> GenParser Char a Deref)
-> Deref -> GenParser Char a Deref
forall a b. (a -> b) -> a -> b
$ [Deref] -> Deref
DerefTuple [Deref]
x
parseDeref :: UserParser a Deref
parseDeref :: forall a. 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 u (m :: * -> *) a. 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 a b.
ParsecT String u Identity a
-> ParsecT String u Identity b -> ParsecT String u Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ParsecT String u Identity ()
forall a. a -> ParsecT String u Identity a
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 a b.
ParsecT String u Identity a
-> ParsecT String u Identity b -> ParsecT String u Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ParsecT String u Identity ()
forall a. a -> ParsecT String u Identity a
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 u (m :: * -> *) a. 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 a. a -> ParsecT String st Identity a
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
isOperatorChar :: Char -> Bool
isOperatorChar Char
c
| Char -> Bool
isAscii Char
c = Char
c Char -> String -> Bool
forall a. Eq a => a -> [a] -> 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 a. a -> ParsecT String u Identity a
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 a b.
ParsecT String st Identity a
-> (a -> ParsecT String st Identity b)
-> ParsecT String st Identity b
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 a b.
ParsecT String st Identity a
-> ParsecT String st Identity b -> ParsecT String st Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Deref -> GenParser Char st Deref
forall a. a -> ParsecT String st Identity a
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 u (m :: * -> *) a. 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
-> ParsecT String st Identity Char
-> ParsecT String st Identity String
forall a b.
ParsecT String st Identity a
-> ParsecT String st Identity b -> ParsecT String st Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT String st Identity Char -> ParsecT String st Identity Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (String -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
" \t")) 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"
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 a. String -> ParsecT String st Identity a
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 u (m :: * -> *) a. 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 a b.
ParsecT String st Identity a
-> ParsecT String st Identity b -> ParsecT String st Identity b
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 a. a -> ParsecT String st Identity a
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 a. (a -> a -> a) -> [a] -> a
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 a. (a -> a -> a) -> [a] -> a
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 = do
Deref
x <- ParsecT String u Identity Deref
forall a. UserParser a Deref
derefType 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
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
<|> (String -> Deref)
-> ParsecT String u Identity String
-> ParsecT String u Identity Deref
forall a b.
(a -> b)
-> ParsecT String u Identity a -> ParsecT String u Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Deref
DerefString ParsecT String u Identity String
forall {u}. ParsecT String u Identity String
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
[String]
fields <- 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 {u}. ParsecT String u Identity String
recordDot
Deref -> ParsecT String u Identity Deref
forall a. a -> ParsecT String u Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Deref -> ParsecT String u Identity Deref)
-> Deref -> ParsecT String u Identity Deref
forall a b. (a -> b) -> a -> b
$ (Deref -> String -> Deref) -> Deref -> [String] -> Deref
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Deref -> String -> Deref
DerefGetField Deref
x [String]
fields
tyNameOrVar :: ParsecT String u Identity String
tyNameOrVar = (Char -> ShowS)
-> ParsecT String u Identity Char
-> ParsecT String u Identity String
-> ParsecT String u Identity String
forall a b c.
(a -> b -> c)
-> ParsecT String u Identity a
-> ParsecT String u Identity b
-> ParsecT String u Identity c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:) (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 String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (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
'\''))
derefType :: GenParser Char st Deref
derefType = 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 -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'@' ParsecT String st Identity Char
-> ParsecT String st Identity () -> ParsecT String st Identity ()
forall a b.
ParsecT String st Identity a
-> ParsecT String st Identity b -> ParsecT String st Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String st Identity Char -> ParsecT String st Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (String -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
" \t")
String
x <-
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
forall {u}. ParsecT String u Identity String
tyNameOrVar
GenParser Char st String
-> GenParser Char st String -> GenParser Char st String
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> GenParser Char st String -> GenParser Char st String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (String -> GenParser Char st String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"()")
GenParser Char st String
-> GenParser Char st String -> GenParser Char st String
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> 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
forall {u}. ParsecT String u Identity String
strLit
GenParser Char st String
-> GenParser Char st String -> GenParser Char st String
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String st Identity Char
-> ParsecT String st Identity Char
-> GenParser Char st String
-> GenParser Char st String
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 st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m 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] -> String
unwords ([String] -> String)
-> ParsecT String st Identity [String] -> GenParser Char st String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenParser Char st String -> ParsecT String st Identity [String]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ((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
forall {u}. ParsecT String u Identity String
tyNameOrVar GenParser Char st String
-> GenParser Char st String -> GenParser Char st String
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> 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
forall {u}. ParsecT String u Identity String
strLitQuoted) GenParser Char st String
-> GenParser Char st String -> GenParser Char st String
forall a b.
ParsecT String st Identity a
-> ParsecT String st Identity b -> ParsecT String st Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* 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 (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 a. a -> ParsecT String st Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Deref -> GenParser Char st Deref)
-> Deref -> GenParser Char st Deref
forall a b. (a -> b) -> a -> b
$ String -> Deref
DerefType String
x
recordDot :: ParsecT String u Identity String
recordDot = do
Char
_ <- Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'.'
Char
x <- ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
lower 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
'_'
String
xs <- 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 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
'\'')
String -> ParsecT String u Identity String
forall a. a -> ParsecT String u Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Char
x Char -> ShowS
forall a. a -> [a] -> [a]
: String
xs)
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 a. a -> ParsecT String u Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Deref -> Deref -> Deref) -> t Deref -> Deref
forall a. (a -> a -> a) -> t a -> a
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 a b.
ParsecT String st Identity a
-> ParsecT String st Identity b -> ParsecT String st Identity b
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 a. (a -> a -> a) -> t a -> a
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 a. a -> ParsecT String st Identity a
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 a b.
ParsecT String u Identity a
-> ParsecT String u Identity b -> ParsecT String u Identity b
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 a b.
ParsecT String u Identity a
-> ParsecT String u Identity b -> ParsecT String u Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> ParsecT String u Identity String
forall a. a -> ParsecT String u Identity a
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 a. a -> ParsecT String u Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return String
""
String
x <- 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]
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 a b.
ParsecT String u Identity a
-> ParsecT String u Identity b -> ParsecT String u Identity b
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 a b.
(a -> b)
-> ParsecT String u Identity a -> ParsecT String u Identity b
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 u (m :: * -> *) a. 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 a. a -> ParsecT String u Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
Deref -> ParsecT String u Identity Deref
forall a. a -> ParsecT String u Identity a
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)
strLitQuoted :: ParsecT String u Identity String
strLitQuoted = (Char -> ShowS)
-> ParsecT String u Identity Char
-> ParsecT String u Identity String
-> ParsecT String u Identity String
forall a b c.
(a -> b -> c)
-> ParsecT String u Identity a
-> ParsecT String u Identity b
-> ParsecT String u Identity c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:) (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
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) ParsecT String u Identity String
-> ParsecT String u Identity String
-> ParsecT String u Identity String
forall a. Semigroup a => a -> a -> a
<> (Char -> String)
-> ParsecT String u Identity Char
-> ParsecT String u Identity String
forall a b.
(a -> b)
-> ParsecT String u Identity a -> ParsecT String u Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> String
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"')
strLit :: ParsecT String u Identity String
strLit = 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 a b.
ParsecT String u Identity a
-> ParsecT String u Identity b -> ParsecT String u Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> 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 ParsecT String u Identity String
-> ParsecT String u Identity Char
-> ParsecT String u Identity String
forall a b.
ParsecT String u Identity a
-> ParsecT String u Identity b -> ParsecT String u Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"'
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 a b.
ParsecT String u Identity a
-> ParsecT String u Identity b -> ParsecT String u Identity b
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 a b.
ParsecT String u Identity a
-> ParsecT String u Identity b -> ParsecT String u Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT String u Identity Char
forall a. a -> ParsecT String u Identity a
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 {u}. ParsecT String u Identity String
modul
String
func <- 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]
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 a. a -> ParsecT String u Identity a
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 a. [a] -> 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 a. a -> ParsecT String st Identity a
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' :: forall a. Read a => 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"
strType :: String -> Type
strType :: String -> Type
strType String
t0 = case String
t0 of
String
"" -> Name -> Type
ConT ''()
Char
hd : String
tl
| (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isNumber String
t0 -> TyLit -> Type
LitT (Integer -> TyLit
NumTyLit (String -> Integer
forall a. Read a => String -> a
read String
t0))
| Char -> Bool
isLower Char
hd -> Name -> Type
VarT (String -> Name
mkName (Char
hd Char -> ShowS
forall a. a -> [a] -> [a]
: String
tl))
| Bool
otherwise -> Name -> Type
ConT (String -> Name
mkName (Char
hd Char -> ShowS
forall a. a -> [a] -> [a]
: String
tl))
strTypeWords :: String -> Type
strTypeWords :: String -> Type
strTypeWords String
t = case String -> [String]
words String
t of
[] -> Name -> Type
ConT ''()
[String
ty] -> String -> Type
strType String
ty
ts :: [String]
ts@(String
ty : [String]
tys)
| Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
ty)
Bool -> Bool -> Bool
&& String -> Char
forall a. HasCallStack => [a] -> a
head String
ty Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\"'
Bool -> Bool -> Bool
&& Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([String] -> String
forall a. HasCallStack => [a] -> a
last [String]
ts))
Bool -> Bool -> Bool
&& String -> Char
forall a. HasCallStack => [a] -> a
last ([String] -> String
forall a. HasCallStack => [a] -> a
last [String]
ts) Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\"' ->
TyLit -> Type
LitT (String -> TyLit
StrTyLit String
t)
| Bool
otherwise -> (Type -> Type -> Type) -> Type -> [Type] -> Type
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Type -> Type -> Type
AppT (String -> Type
strType String
ty) ((String -> Type) -> [String] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map String -> Type
strType [String]
tys)
derefToExp :: Scope -> Deref -> Exp
derefToExp :: Scope -> Deref -> Exp
derefToExp Scope
s (DerefBranch Deref
x Deref
y) = case Deref
y of
DerefBranch (DerefType String
t) Deref
y' -> Scope -> Deref -> Exp
derefToExp Scope
s Deref
x Exp -> Type -> Exp
`AppTypeE` String -> Type
strTypeWords String
t Exp -> Exp -> Exp
`AppE` Scope -> Deref -> Exp
derefToExp Scope
s Deref
y'
DerefType String
t -> Scope -> Deref -> Exp
derefToExp Scope
s Deref
x Exp -> Type -> Exp
`AppTypeE` String -> Type
strTypeWords String
t
Deref
_ -> 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
_ (DerefType String
_) = String -> Exp
forall a. HasCallStack => String -> a
error String
"exposed type application"
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
derefToExp Scope
s (DerefGetField Deref
x String
f) =
#if MIN_VERSION_template_haskell(2,18,0)
Exp -> String -> Exp
GetFieldE (Scope -> Deref -> Exp
derefToExp Scope
s Deref
x) String
f
#else
error "Your compiler doesn't support OverloadedRecordDot"
#endif
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 :: forall a. 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 :: forall {u}. ParsecT String u Identity 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 u (m :: * -> *) a. 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 a. a -> ParsecT String a Identity a
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 :: forall a. 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 a b.
ParsecT String a Identity a
-> ParsecT String a Identity b -> ParsecT String a Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String Deref -> UserParser a (Either String Deref)
forall a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
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
()
_ <- 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 a b.
ParsecT String a Identity a
-> ParsecT String a Identity b -> ParsecT String a Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ParsecT String a Identity ()
forall a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
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 :: forall a. 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 :: forall a.
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 a b.
ParsecT String a Identity a
-> ParsecT String a Identity b -> ParsecT String a Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String (Deref, Bool)
-> UserParser a (Either String (Deref, Bool))
forall a. a -> ParsecT String a Identity a
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 a b.
ParsecT String a Identity a
-> ParsecT String a Identity b -> ParsecT String a Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> ParsecT String a Identity Bool
forall a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
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 :: forall a. 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 a b.
ParsecT String a Identity a
-> ParsecT String a Identity b -> ParsecT String a Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String String -> UserParser a (Either String String)
forall a. a -> ParsecT String a Identity a
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 {u}. ParsecT String u Identity String
curlyBrackets
Either String String -> UserParser a (Either String String)
forall a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
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 :: forall a. 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 :: forall a. 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 a b.
ParsecT String a Identity a
-> ParsecT String a Identity b -> ParsecT String a Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String String -> UserParser a (Either String String)
forall a. a -> ParsecT String a Identity a
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 a b.
ParsecT String a Identity a
-> ParsecT String a Identity b -> ParsecT String a Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> ParsecT String a Identity String
forall a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return []
(do String
bracketed <- ParsecT String a Identity String
forall {u}. ParsecT String u Identity String
curlyBrackets
Either String String -> UserParser a (Either String String)
forall a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
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 :: forall a. 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 :: forall a. 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 :: forall a. 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 a b.
ParsecT String a Identity a
-> ParsecT String a Identity b -> ParsecT String a Identity b
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 a b.
ParsecT String a Identity a
-> ParsecT String a Identity b -> ParsecT String a Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String Deref -> UserParser a (Either String Deref)
forall a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
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 :: forall a. 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 a b.
ParsecT String a Identity a
-> ParsecT String a Identity b -> ParsecT String a Identity b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either String Deref -> UserParser a (Either String Deref)
forall a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
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 a. a -> ParsecT String a Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String Deref
forall a b. a -> Either a b
Left String
"_")
readUtf8FileString :: FilePath -> IO String
readUtf8FileString :: String -> IO String
readUtf8FileString String
fp = (Text -> String) -> IO Text -> IO String
forall a b. (a -> b) -> IO a -> IO b
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 a. a -> IO a
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
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 a. IO a -> Q a
forall (m :: * -> *) a. Quasi m => IO a -> m a
qRunIO (String -> IO String
readUtf8FileString String
fp)
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 a. IO a -> Q a
forall (m :: * -> *) a. Quasi m => IO a -> m a
qRunIO (String -> IO String
readUtf8FileString String
fp)