morley-1.7.0: Developer tools for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Michelson.ErrorPos

Documentation

newtype Pos Source #

Constructors

Pos Word 

Instances

Instances details
Eq Pos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

(==) :: Pos -> Pos -> Bool #

(/=) :: Pos -> Pos -> Bool #

Data Pos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pos -> c Pos #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pos #

toConstr :: Pos -> Constr #

dataTypeOf :: Pos -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pos) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos) #

gmapT :: (forall b. Data b => b -> b) -> Pos -> Pos #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r #

gmapQ :: (forall d. Data d => d -> u) -> Pos -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pos -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pos -> m Pos #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos #

Ord Pos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

compare :: Pos -> Pos -> Ordering #

(<) :: Pos -> Pos -> Bool #

(<=) :: Pos -> Pos -> Bool #

(>) :: Pos -> Pos -> Bool #

(>=) :: Pos -> Pos -> Bool #

max :: Pos -> Pos -> Pos #

min :: Pos -> Pos -> Pos #

Show Pos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Generic Pos Source # 
Instance details

Defined in Michelson.ErrorPos

Associated Types

type Rep Pos :: Type -> Type #

Methods

from :: Pos -> Rep Pos x #

to :: Rep Pos x -> Pos #

Arbitrary Pos Source # 
Instance details

Defined in Util.Test.Arbitrary

Methods

arbitrary :: Gen Pos #

shrink :: Pos -> [Pos] #

ToJSON Pos Source # 
Instance details

Defined in Michelson.ErrorPos

FromJSON Pos Source # 
Instance details

Defined in Michelson.ErrorPos

NFData Pos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

rnf :: Pos -> () #

Default Pos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: Pos #

ToADTArbitrary Pos Source # 
Instance details

Defined in Util.Test.Arbitrary

type Rep Pos Source # 
Instance details

Defined in Michelson.ErrorPos

type Rep Pos = D1 ('MetaData "Pos" "Michelson.ErrorPos" "morley-1.7.0-inplace" 'True) (C1 ('MetaCons "Pos" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

data SrcPos Source #

Constructors

SrcPos Pos Pos 

Instances

Instances details
Eq SrcPos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

(==) :: SrcPos -> SrcPos -> Bool #

(/=) :: SrcPos -> SrcPos -> Bool #

Data SrcPos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcPos -> c SrcPos #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcPos #

toConstr :: SrcPos -> Constr #

dataTypeOf :: SrcPos -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcPos) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcPos) #

gmapT :: (forall b. Data b => b -> b) -> SrcPos -> SrcPos #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcPos -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcPos -> r #

gmapQ :: (forall d. Data d => d -> u) -> SrcPos -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcPos -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcPos -> m SrcPos #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcPos -> m SrcPos #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcPos -> m SrcPos #

Ord SrcPos Source # 
Instance details

Defined in Michelson.ErrorPos

Show SrcPos Source # 
Instance details

Defined in Michelson.ErrorPos

Generic SrcPos Source # 
Instance details

Defined in Michelson.ErrorPos

Associated Types

type Rep SrcPos :: Type -> Type #

Methods

from :: SrcPos -> Rep SrcPos x #

to :: Rep SrcPos x -> SrcPos #

Arbitrary SrcPos Source # 
Instance details

Defined in Util.Test.Arbitrary

ToJSON SrcPos Source # 
Instance details

Defined in Michelson.ErrorPos

FromJSON SrcPos Source # 
Instance details

Defined in Michelson.ErrorPos

NFData SrcPos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

rnf :: SrcPos -> () #

Default SrcPos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: SrcPos #

ToADTArbitrary SrcPos Source # 
Instance details

Defined in Util.Test.Arbitrary

type Rep SrcPos Source # 
Instance details

Defined in Michelson.ErrorPos

data InstrCallStack Source #

Instances

Instances details
Eq InstrCallStack Source # 
Instance details

Defined in Michelson.ErrorPos

Data InstrCallStack Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstrCallStack -> c InstrCallStack #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InstrCallStack #

toConstr :: InstrCallStack -> Constr #

dataTypeOf :: InstrCallStack -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InstrCallStack) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InstrCallStack) #

gmapT :: (forall b. Data b => b -> b) -> InstrCallStack -> InstrCallStack #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstrCallStack -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstrCallStack -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstrCallStack -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstrCallStack -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstrCallStack -> m InstrCallStack #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstrCallStack -> m InstrCallStack #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstrCallStack -> m InstrCallStack #

Ord InstrCallStack Source # 
Instance details

Defined in Michelson.ErrorPos

Show InstrCallStack Source # 
Instance details

Defined in Michelson.ErrorPos

Generic InstrCallStack Source # 
Instance details

Defined in Michelson.ErrorPos

Associated Types

type Rep InstrCallStack :: Type -> Type #

Arbitrary InstrCallStack Source # 
Instance details

Defined in Util.Test.Arbitrary

ToJSON InstrCallStack Source # 
Instance details

Defined in Michelson.ErrorPos

FromJSON InstrCallStack Source # 
Instance details

Defined in Michelson.ErrorPos

NFData InstrCallStack Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

rnf :: InstrCallStack -> () #

Default InstrCallStack Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: InstrCallStack #

ToADTArbitrary InstrCallStack Source # 
Instance details

Defined in Util.Test.Arbitrary

type Rep InstrCallStack Source # 
Instance details

Defined in Michelson.ErrorPos

type Rep InstrCallStack = D1 ('MetaData "InstrCallStack" "Michelson.ErrorPos" "morley-1.7.0-inplace" 'False) (C1 ('MetaCons "InstrCallStack" 'PrefixI 'True) (S1 ('MetaSel ('Just "icsCallStack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LetCallStack) :*: S1 ('MetaSel ('Just "icsSrcPos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SrcPos)))

newtype LetName Source #

Constructors

LetName Text 

Instances

Instances details
Eq LetName Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

(==) :: LetName -> LetName -> Bool #

(/=) :: LetName -> LetName -> Bool #

Data LetName Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LetName -> c LetName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LetName #

toConstr :: LetName -> Constr #

dataTypeOf :: LetName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LetName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LetName) #

gmapT :: (forall b. Data b => b -> b) -> LetName -> LetName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LetName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LetName -> r #

gmapQ :: (forall d. Data d => d -> u) -> LetName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LetName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LetName -> m LetName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LetName -> m LetName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LetName -> m LetName #

Ord LetName Source # 
Instance details

Defined in Michelson.ErrorPos

Show LetName Source # 
Instance details

Defined in Michelson.ErrorPos

Generic LetName Source # 
Instance details

Defined in Michelson.ErrorPos

Associated Types

type Rep LetName :: Type -> Type #

Methods

from :: LetName -> Rep LetName x #

to :: Rep LetName x -> LetName #

Arbitrary LetName Source # 
Instance details

Defined in Util.Test.Arbitrary

ToJSON LetName Source # 
Instance details

Defined in Michelson.ErrorPos

FromJSON LetName Source # 
Instance details

Defined in Michelson.ErrorPos

NFData LetName Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

rnf :: LetName -> () #

Buildable LetName Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

build :: LetName -> Builder #

ToADTArbitrary LetName Source # 
Instance details

Defined in Util.Test.Arbitrary

type Rep LetName Source # 
Instance details

Defined in Michelson.ErrorPos

type Rep LetName = D1 ('MetaData "LetName" "Michelson.ErrorPos" "morley-1.7.0-inplace" 'True) (C1 ('MetaCons "LetName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))