{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
module Swarm.Language.Syntax.Loc (
SrcLoc (..),
Located (..),
LocVar,
srcLocStartsBefore,
srcLocEndsBefore,
) where
import Data.Aeson (FromJSON (..), ToJSON (..), genericParseJSON, genericToJSON)
import Data.Data (Data)
import Data.Hashable (Hashable)
import GHC.Generics (Generic)
import Swarm.Language.Var (Var)
import Swarm.Util.JSON (optionsUntagged)
data SrcLoc
= NoLoc
|
SrcLoc Int Int
deriving (SrcLoc -> SrcLoc -> Bool
(SrcLoc -> SrcLoc -> Bool)
-> (SrcLoc -> SrcLoc -> Bool) -> Eq SrcLoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SrcLoc -> SrcLoc -> Bool
== :: SrcLoc -> SrcLoc -> Bool
$c/= :: SrcLoc -> SrcLoc -> Bool
/= :: SrcLoc -> SrcLoc -> Bool
Eq, Eq SrcLoc
Eq SrcLoc =>
(SrcLoc -> SrcLoc -> Ordering)
-> (SrcLoc -> SrcLoc -> Bool)
-> (SrcLoc -> SrcLoc -> Bool)
-> (SrcLoc -> SrcLoc -> Bool)
-> (SrcLoc -> SrcLoc -> Bool)
-> (SrcLoc -> SrcLoc -> SrcLoc)
-> (SrcLoc -> SrcLoc -> SrcLoc)
-> Ord SrcLoc
SrcLoc -> SrcLoc -> Bool
SrcLoc -> SrcLoc -> Ordering
SrcLoc -> SrcLoc -> SrcLoc
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 :: SrcLoc -> SrcLoc -> Ordering
compare :: SrcLoc -> SrcLoc -> Ordering
$c< :: SrcLoc -> SrcLoc -> Bool
< :: SrcLoc -> SrcLoc -> Bool
$c<= :: SrcLoc -> SrcLoc -> Bool
<= :: SrcLoc -> SrcLoc -> Bool
$c> :: SrcLoc -> SrcLoc -> Bool
> :: SrcLoc -> SrcLoc -> Bool
$c>= :: SrcLoc -> SrcLoc -> Bool
>= :: SrcLoc -> SrcLoc -> Bool
$cmax :: SrcLoc -> SrcLoc -> SrcLoc
max :: SrcLoc -> SrcLoc -> SrcLoc
$cmin :: SrcLoc -> SrcLoc -> SrcLoc
min :: SrcLoc -> SrcLoc -> SrcLoc
Ord, Int -> SrcLoc -> ShowS
[SrcLoc] -> ShowS
SrcLoc -> String
(Int -> SrcLoc -> ShowS)
-> (SrcLoc -> String) -> ([SrcLoc] -> ShowS) -> Show SrcLoc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SrcLoc -> ShowS
showsPrec :: Int -> SrcLoc -> ShowS
$cshow :: SrcLoc -> String
show :: SrcLoc -> String
$cshowList :: [SrcLoc] -> ShowS
showList :: [SrcLoc] -> ShowS
Show, Typeable SrcLoc
Typeable SrcLoc =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcLoc -> c SrcLoc)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcLoc)
-> (SrcLoc -> Constr)
-> (SrcLoc -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SrcLoc))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcLoc))
-> ((forall b. Data b => b -> b) -> SrcLoc -> SrcLoc)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SrcLoc -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SrcLoc -> r)
-> (forall u. (forall d. Data d => d -> u) -> SrcLoc -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> SrcLoc -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc)
-> Data SrcLoc
SrcLoc -> Constr
SrcLoc -> DataType
(forall b. Data b => b -> b) -> SrcLoc -> SrcLoc
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) -> SrcLoc -> u
forall u. (forall d. Data d => d -> u) -> SrcLoc -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcLoc
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcLoc -> c SrcLoc
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SrcLoc)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcLoc)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcLoc -> c SrcLoc
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcLoc -> c SrcLoc
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcLoc
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcLoc
$ctoConstr :: SrcLoc -> Constr
toConstr :: SrcLoc -> Constr
$cdataTypeOf :: SrcLoc -> DataType
dataTypeOf :: SrcLoc -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SrcLoc)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SrcLoc)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcLoc)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcLoc)
$cgmapT :: (forall b. Data b => b -> b) -> SrcLoc -> SrcLoc
gmapT :: (forall b. Data b => b -> b) -> SrcLoc -> SrcLoc
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcLoc -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SrcLoc -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> SrcLoc -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SrcLoc -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SrcLoc -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SrcLoc -> m SrcLoc
Data, (forall x. SrcLoc -> Rep SrcLoc x)
-> (forall x. Rep SrcLoc x -> SrcLoc) -> Generic SrcLoc
forall x. Rep SrcLoc x -> SrcLoc
forall x. SrcLoc -> Rep SrcLoc x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SrcLoc -> Rep SrcLoc x
from :: forall x. SrcLoc -> Rep SrcLoc x
$cto :: forall x. Rep SrcLoc x -> SrcLoc
to :: forall x. Rep SrcLoc x -> SrcLoc
Generic, Eq SrcLoc
Eq SrcLoc =>
(Int -> SrcLoc -> Int) -> (SrcLoc -> Int) -> Hashable SrcLoc
Int -> SrcLoc -> Int
SrcLoc -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> SrcLoc -> Int
hashWithSalt :: Int -> SrcLoc -> Int
$chash :: SrcLoc -> Int
hash :: SrcLoc -> Int
Hashable)
instance ToJSON SrcLoc where
toJSON :: SrcLoc -> Value
toJSON = Options -> SrcLoc -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
optionsUntagged
omitField :: SrcLoc -> Bool
omitField = (SrcLoc -> SrcLoc -> Bool
forall a. Eq a => a -> a -> Bool
== SrcLoc
NoLoc)
instance FromJSON SrcLoc where
parseJSON :: Value -> Parser SrcLoc
parseJSON = Options -> Value -> Parser SrcLoc
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
optionsUntagged
omittedField :: Maybe SrcLoc
omittedField = SrcLoc -> Maybe SrcLoc
forall a. a -> Maybe a
Just SrcLoc
NoLoc
instance Semigroup SrcLoc where
SrcLoc
NoLoc <> :: SrcLoc -> SrcLoc -> SrcLoc
<> SrcLoc
l = SrcLoc
l
SrcLoc
l <> SrcLoc
NoLoc = SrcLoc
l
SrcLoc Int
s1 Int
e1 <> SrcLoc Int
s2 Int
e2 = Int -> Int -> SrcLoc
SrcLoc (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
s1 Int
s2) (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
e1 Int
e2)
instance Monoid SrcLoc where
mempty :: SrcLoc
mempty = SrcLoc
NoLoc
srcLocStartsBefore :: SrcLoc -> SrcLoc -> Bool
srcLocStartsBefore :: SrcLoc -> SrcLoc -> Bool
srcLocStartsBefore (SrcLoc Int
a Int
_) (SrcLoc Int
b Int
_) = Int
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
b
srcLocStartsBefore SrcLoc
_ SrcLoc
_ = Bool
False
srcLocEndsBefore :: SrcLoc -> SrcLoc -> Bool
srcLocEndsBefore :: SrcLoc -> SrcLoc -> Bool
srcLocEndsBefore (SrcLoc Int
_ Int
a) (SrcLoc Int
_ Int
b) = Int
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
b
srcLocEndsBefore SrcLoc
_ SrcLoc
_ = Bool
False
data Located v = LV {forall v. Located v -> SrcLoc
lvSrcLoc :: SrcLoc, forall v. Located v -> v
lvVar :: v}
deriving (Located v -> Located v -> Bool
(Located v -> Located v -> Bool)
-> (Located v -> Located v -> Bool) -> Eq (Located v)
forall v. Eq v => Located v -> Located v -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall v. Eq v => Located v -> Located v -> Bool
== :: Located v -> Located v -> Bool
$c/= :: forall v. Eq v => Located v -> Located v -> Bool
/= :: Located v -> Located v -> Bool
Eq, Eq (Located v)
Eq (Located v) =>
(Located v -> Located v -> Ordering)
-> (Located v -> Located v -> Bool)
-> (Located v -> Located v -> Bool)
-> (Located v -> Located v -> Bool)
-> (Located v -> Located v -> Bool)
-> (Located v -> Located v -> Located v)
-> (Located v -> Located v -> Located v)
-> Ord (Located v)
Located v -> Located v -> Bool
Located v -> Located v -> Ordering
Located v -> Located v -> Located v
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
forall v. Ord v => Eq (Located v)
forall v. Ord v => Located v -> Located v -> Bool
forall v. Ord v => Located v -> Located v -> Ordering
forall v. Ord v => Located v -> Located v -> Located v
$ccompare :: forall v. Ord v => Located v -> Located v -> Ordering
compare :: Located v -> Located v -> Ordering
$c< :: forall v. Ord v => Located v -> Located v -> Bool
< :: Located v -> Located v -> Bool
$c<= :: forall v. Ord v => Located v -> Located v -> Bool
<= :: Located v -> Located v -> Bool
$c> :: forall v. Ord v => Located v -> Located v -> Bool
> :: Located v -> Located v -> Bool
$c>= :: forall v. Ord v => Located v -> Located v -> Bool
>= :: Located v -> Located v -> Bool
$cmax :: forall v. Ord v => Located v -> Located v -> Located v
max :: Located v -> Located v -> Located v
$cmin :: forall v. Ord v => Located v -> Located v -> Located v
min :: Located v -> Located v -> Located v
Ord, (forall a b. (a -> b) -> Located a -> Located b)
-> (forall a b. a -> Located b -> Located a) -> Functor Located
forall a b. a -> Located b -> Located a
forall a b. (a -> b) -> Located a -> Located b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Located a -> Located b
fmap :: forall a b. (a -> b) -> Located a -> Located b
$c<$ :: forall a b. a -> Located b -> Located a
<$ :: forall a b. a -> Located b -> Located a
Functor, Int -> Located v -> ShowS
[Located v] -> ShowS
Located v -> String
(Int -> Located v -> ShowS)
-> (Located v -> String)
-> ([Located v] -> ShowS)
-> Show (Located v)
forall v. Show v => Int -> Located v -> ShowS
forall v. Show v => [Located v] -> ShowS
forall v. Show v => Located v -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall v. Show v => Int -> Located v -> ShowS
showsPrec :: Int -> Located v -> ShowS
$cshow :: forall v. Show v => Located v -> String
show :: Located v -> String
$cshowList :: forall v. Show v => [Located v] -> ShowS
showList :: [Located v] -> ShowS
Show, Typeable (Located v)
Typeable (Located v) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Located v -> c (Located v))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Located v))
-> (Located v -> Constr)
-> (Located v -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Located v)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Located v)))
-> ((forall b. Data b => b -> b) -> Located v -> Located v)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Located v -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Located v -> r)
-> (forall u. (forall d. Data d => d -> u) -> Located v -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Located v -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v))
-> Data (Located v)
Located v -> Constr
Located v -> DataType
(forall b. Data b => b -> b) -> Located v -> Located v
forall v. Data v => Typeable (Located v)
forall v. Data v => Located v -> Constr
forall v. Data v => Located v -> DataType
forall v.
Data v =>
(forall b. Data b => b -> b) -> Located v -> Located v
forall v u.
Data v =>
Int -> (forall d. Data d => d -> u) -> Located v -> u
forall v u.
Data v =>
(forall d. Data d => d -> u) -> Located v -> [u]
forall v r r'.
Data v =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Located v -> r
forall v r r'.
Data v =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Located v -> r
forall v (m :: * -> *).
(Data v, Monad m) =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v)
forall v (m :: * -> *).
(Data v, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v)
forall v (c :: * -> *).
Data v =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Located v)
forall v (c :: * -> *).
Data v =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Located v -> c (Located v)
forall v (t :: * -> *) (c :: * -> *).
(Data v, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Located v))
forall v (t :: * -> * -> *) (c :: * -> *).
(Data v, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Located v))
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) -> Located v -> u
forall u. (forall d. Data d => d -> u) -> Located v -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Located v -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Located v -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Located v)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Located v -> c (Located v)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Located v))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Located v))
$cgfoldl :: forall v (c :: * -> *).
Data v =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Located v -> c (Located v)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Located v -> c (Located v)
$cgunfold :: forall v (c :: * -> *).
Data v =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Located v)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Located v)
$ctoConstr :: forall v. Data v => Located v -> Constr
toConstr :: Located v -> Constr
$cdataTypeOf :: forall v. Data v => Located v -> DataType
dataTypeOf :: Located v -> DataType
$cdataCast1 :: forall v (t :: * -> *) (c :: * -> *).
(Data v, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Located v))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Located v))
$cdataCast2 :: forall v (t :: * -> * -> *) (c :: * -> *).
(Data v, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Located v))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Located v))
$cgmapT :: forall v.
Data v =>
(forall b. Data b => b -> b) -> Located v -> Located v
gmapT :: (forall b. Data b => b -> b) -> Located v -> Located v
$cgmapQl :: forall v r r'.
Data v =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Located v -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Located v -> r
$cgmapQr :: forall v r r'.
Data v =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Located v -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Located v -> r
$cgmapQ :: forall v u.
Data v =>
(forall d. Data d => d -> u) -> Located v -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Located v -> [u]
$cgmapQi :: forall v u.
Data v =>
Int -> (forall d. Data d => d -> u) -> Located v -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Located v -> u
$cgmapM :: forall v (m :: * -> *).
(Data v, Monad m) =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v)
$cgmapMp :: forall v (m :: * -> *).
(Data v, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v)
$cgmapMo :: forall v (m :: * -> *).
(Data v, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Located v -> m (Located v)
Data, (forall x. Located v -> Rep (Located v) x)
-> (forall x. Rep (Located v) x -> Located v)
-> Generic (Located v)
forall x. Rep (Located v) x -> Located v
forall x. Located v -> Rep (Located v) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall v x. Rep (Located v) x -> Located v
forall v x. Located v -> Rep (Located v) x
$cfrom :: forall v x. Located v -> Rep (Located v) x
from :: forall x. Located v -> Rep (Located v) x
$cto :: forall v x. Rep (Located v) x -> Located v
to :: forall x. Rep (Located v) x -> Located v
Generic, Eq (Located v)
Eq (Located v) =>
(Int -> Located v -> Int)
-> (Located v -> Int) -> Hashable (Located v)
Int -> Located v -> Int
Located v -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall v. Hashable v => Eq (Located v)
forall v. Hashable v => Int -> Located v -> Int
forall v. Hashable v => Located v -> Int
$chashWithSalt :: forall v. Hashable v => Int -> Located v -> Int
hashWithSalt :: Int -> Located v -> Int
$chash :: forall v. Hashable v => Located v -> Int
hash :: Located v -> Int
Hashable, Maybe (Located v)
Value -> Parser [Located v]
Value -> Parser (Located v)
(Value -> Parser (Located v))
-> (Value -> Parser [Located v])
-> Maybe (Located v)
-> FromJSON (Located v)
forall v. FromJSON v => Maybe (Located v)
forall v. FromJSON v => Value -> Parser [Located v]
forall v. FromJSON v => Value -> Parser (Located v)
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: forall v. FromJSON v => Value -> Parser (Located v)
parseJSON :: Value -> Parser (Located v)
$cparseJSONList :: forall v. FromJSON v => Value -> Parser [Located v]
parseJSONList :: Value -> Parser [Located v]
$comittedField :: forall v. FromJSON v => Maybe (Located v)
omittedField :: Maybe (Located v)
FromJSON, [Located v] -> Value
[Located v] -> Encoding
Located v -> Bool
Located v -> Value
Located v -> Encoding
(Located v -> Value)
-> (Located v -> Encoding)
-> ([Located v] -> Value)
-> ([Located v] -> Encoding)
-> (Located v -> Bool)
-> ToJSON (Located v)
forall v. ToJSON v => [Located v] -> Value
forall v. ToJSON v => [Located v] -> Encoding
forall v. ToJSON v => Located v -> Bool
forall v. ToJSON v => Located v -> Value
forall v. ToJSON v => Located v -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: forall v. ToJSON v => Located v -> Value
toJSON :: Located v -> Value
$ctoEncoding :: forall v. ToJSON v => Located v -> Encoding
toEncoding :: Located v -> Encoding
$ctoJSONList :: forall v. ToJSON v => [Located v] -> Value
toJSONList :: [Located v] -> Value
$ctoEncodingList :: forall v. ToJSON v => [Located v] -> Encoding
toEncodingList :: [Located v] -> Encoding
$comitField :: forall v. ToJSON v => Located v -> Bool
omitField :: Located v -> Bool
ToJSON)
type LocVar = Located Var