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