inferno-types-0.1.0.0: Core types for Inferno
Safe HaskellSafe-Inferred
LanguageHaskell2010

Inferno.Types.Syntax

Synopsis

Documentation

newtype Ident Source #

Constructors

Ident 

Fields

Instances

Instances details
Arbitrary Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

arbitrary :: Gen Ident #

shrink :: Ident -> [Ident] #

FromJSON Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSONKey Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSONKey Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

Data Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: Ident -> Constr #

dataTypeOf :: Ident -> DataType #

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

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

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

gmapQl :: (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 #

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

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

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

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

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

IsString Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fromString :: String -> Ident #

Generic Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep Ident :: Type -> Type #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

Show Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

NFData Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

rnf :: Ident -> () #

Eq Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

Ord Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

compare :: Ident -> Ident -> Ordering #

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

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

(>) :: Ident -> Ident -> Bool #

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

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Hashable Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

hashWithSalt :: Int -> Ident -> Int #

hash :: Ident -> Int #

ElementPosition Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

VCHashUpdate Ident Source # 
Instance details

Defined in Inferno.Types.VersionControl

ToADTArbitrary Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

ElementPosition (Maybe Ident) Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep Ident Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep Ident = D1 ('MetaData "Ident" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'True) (C1 ('MetaCons "Ident" 'PrefixI 'True) (S1 ('MetaSel ('Just "unIdent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype ExtIdent Source #

An extended identifier; either an internal (e.g., var$4) or a regular variable

Constructors

ExtIdent (Either Int Text) 

Instances

Instances details
Arbitrary ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSON ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSONKey ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSONKey ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

Data ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: ExtIdent -> Constr #

dataTypeOf :: ExtIdent -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep ExtIdent :: Type -> Type #

Methods

from :: ExtIdent -> Rep ExtIdent x #

to :: Rep ExtIdent x -> ExtIdent #

Show ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

Eq ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

Ord ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

VCHashUpdate ExtIdent Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: ExtIdent -> Doc ann #

prettyList :: [ExtIdent] -> Doc ann #

Monad m => MonadReader (Map ExtIdent (Value c (ImplEnvM m c))) (ImplEnvM m c) Source # 
Instance details

Defined in Inferno.Types.Value

Methods

ask :: ImplEnvM m c (Map ExtIdent (Value c (ImplEnvM m c))) #

local :: (Map ExtIdent (Value c (ImplEnvM m c)) -> Map ExtIdent (Value c (ImplEnvM m c))) -> ImplEnvM m c a -> ImplEnvM m c a #

reader :: (Map ExtIdent (Value c (ImplEnvM m c)) -> a) -> ImplEnvM m c a #

type Rep ExtIdent Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep ExtIdent = D1 ('MetaData "ExtIdent" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'True) (C1 ('MetaCons "ExtIdent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either Int Text))))

data ImplExpl Source #

Constructors

Impl ExtIdent 
Expl ExtIdent 

Instances

Instances details
FromJSON ImplExpl Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON ImplExpl Source # 
Instance details

Defined in Inferno.Types.Syntax

Data ImplExpl Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: ImplExpl -> Constr #

dataTypeOf :: ImplExpl -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ImplExpl Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep ImplExpl :: Type -> Type #

Methods

from :: ImplExpl -> Rep ImplExpl x #

to :: Rep ImplExpl x -> ImplExpl #

Show ImplExpl Source # 
Instance details

Defined in Inferno.Types.Syntax

Eq ImplExpl Source # 
Instance details

Defined in Inferno.Types.Syntax

Ord ImplExpl Source # 
Instance details

Defined in Inferno.Types.Syntax

ElementPosition ImplExpl Source # 
Instance details

Defined in Inferno.Types.Syntax

VCHashUpdate ImplExpl Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty ImplExpl Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: ImplExpl -> Doc ann #

prettyList :: [ImplExpl] -> Doc ann #

type Rep ImplExpl Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep ImplExpl = D1 ('MetaData "ImplExpl" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (C1 ('MetaCons "Impl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExtIdent)) :+: C1 ('MetaCons "Expl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExtIdent)))

data Import pos Source #

Constructors

IVar pos Ident 
IOpVar pos Ident 
IEnum pos pos Ident 
ICommentAbove (Comment pos) (Import pos) 
ICommentAfter (Import pos) (Comment pos) 
ICommentBelow (Import pos) (Comment pos) 

Instances

Instances details
Foldable Import Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fold :: Monoid m => Import m -> m #

foldMap :: Monoid m => (a -> m) -> Import a -> m #

foldMap' :: Monoid m => (a -> m) -> Import a -> m #

foldr :: (a -> b -> b) -> b -> Import a -> b #

foldr' :: (a -> b -> b) -> b -> Import a -> b #

foldl :: (b -> a -> b) -> b -> Import a -> b #

foldl' :: (b -> a -> b) -> b -> Import a -> b #

foldr1 :: (a -> a -> a) -> Import a -> a #

foldl1 :: (a -> a -> a) -> Import a -> a #

toList :: Import a -> [a] #

null :: Import a -> Bool #

length :: Import a -> Int #

elem :: Eq a => a -> Import a -> Bool #

maximum :: Ord a => Import a -> a #

minimum :: Ord a => Import a -> a #

sum :: Num a => Import a -> a #

product :: Num a => Import a -> a #

Functor Import Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fmap :: (a -> b) -> Import a -> Import b #

(<$) :: a -> Import b -> Import a #

BlockUtils Import Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSON pos => FromJSON (Import pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

parseJSON :: Value -> Parser (Import pos) #

parseJSONList :: Value -> Parser [Import pos] #

ToJSON pos => ToJSON (Import pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

toJSON :: Import pos -> Value #

toEncoding :: Import pos -> Encoding #

toJSONList :: [Import pos] -> Value #

toEncodingList :: [Import pos] -> Encoding #

Data pos => Data (Import pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: Import pos -> Constr #

dataTypeOf :: Import pos -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Import pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep (Import pos) :: Type -> Type #

Methods

from :: Import pos -> Rep (Import pos) x #

to :: Rep (Import pos) x -> Import pos #

Show pos => Show (Import pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> Import pos -> ShowS #

show :: Import pos -> String #

showList :: [Import pos] -> ShowS #

Eq pos => Eq (Import pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

(==) :: Import pos -> Import pos -> Bool #

(/=) :: Import pos -> Import pos -> Bool #

Ord pos => Ord (Import pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

compare :: Import pos -> Import pos -> Ordering #

(<) :: Import pos -> Import pos -> Bool #

(<=) :: Import pos -> Import pos -> Bool #

(>) :: Import pos -> Import pos -> Bool #

(>=) :: Import pos -> Import pos -> Bool #

max :: Import pos -> Import pos -> Import pos #

min :: Import pos -> Import pos -> Import pos #

VCHashUpdate a => VCHashUpdate (Import a) Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty (Import a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: Import a -> Doc ann #

prettyList :: [Import a] -> Doc ann #

Corecursive (Import pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

embed :: Base (Import pos) (Import pos) -> Import pos #

ana :: (a -> Base (Import pos) a) -> a -> Import pos #

apo :: (a -> Base (Import pos) (Either (Import pos) a)) -> a -> Import pos #

postpro :: Recursive (Import pos) => (forall b. Base (Import pos) b -> Base (Import pos) b) -> (a -> Base (Import pos) a) -> a -> Import pos #

gpostpro :: (Recursive (Import pos), Monad m) => (forall b. m (Base (Import pos) b) -> Base (Import pos) (m b)) -> (forall c. Base (Import pos) c -> Base (Import pos) c) -> (a -> Base (Import pos) (m a)) -> a -> Import pos #

Recursive (Import pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

project :: Import pos -> Base (Import pos) (Import pos) #

cata :: (Base (Import pos) a -> a) -> Import pos -> a #

para :: (Base (Import pos) (Import pos, a) -> a) -> Import pos -> a #

gpara :: (Corecursive (Import pos), Comonad w) => (forall b. Base (Import pos) (w b) -> w (Base (Import pos) b)) -> (Base (Import pos) (EnvT (Import pos) w a) -> a) -> Import pos -> a #

prepro :: Corecursive (Import pos) => (forall b. Base (Import pos) b -> Base (Import pos) b) -> (Base (Import pos) a -> a) -> Import pos -> a #

gprepro :: (Corecursive (Import pos), Comonad w) => (forall b. Base (Import pos) (w b) -> w (Base (Import pos) b)) -> (forall c. Base (Import pos) c -> Base (Import pos) c) -> (Base (Import pos) (w a) -> a) -> Import pos -> a #

type Rep (Import pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep (Import pos) = D1 ('MetaData "Import" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) ((C1 ('MetaCons "IVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: (C1 ('MetaCons "IOpVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: C1 ('MetaCons "IEnum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))))) :+: (C1 ('MetaCons "ICommentAbove" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Comment pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Import pos))) :+: (C1 ('MetaCons "ICommentAfter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Import pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Comment pos))) :+: C1 ('MetaCons "ICommentBelow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Import pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Comment pos))))))
type Base (Import pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

type Base (Import pos)

newtype ModuleName Source #

Constructors

ModuleName 

Fields

Instances

Instances details
Arbitrary ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSON ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

Data ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: ModuleName -> Constr #

dataTypeOf :: ModuleName -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

Generic ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep ModuleName :: Type -> Type #

Show ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

Eq ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

Ord ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

ElementPosition ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

VCHashUpdate ModuleName Source # 
Instance details

Defined in Inferno.Types.VersionControl

ToADTArbitrary ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep ModuleName Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep ModuleName = D1 ('MetaData "ModuleName" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'True) (C1 ('MetaCons "ModuleName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unModuleName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data InfixFixity Source #

Constructors

NoFix 
LeftFix 
RightFix 

Instances

Instances details
FromJSON InfixFixity Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON InfixFixity Source # 
Instance details

Defined in Inferno.Types.Syntax

Data InfixFixity Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: InfixFixity -> Constr #

dataTypeOf :: InfixFixity -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic InfixFixity Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep InfixFixity :: Type -> Type #

Show InfixFixity Source # 
Instance details

Defined in Inferno.Types.Syntax

Eq InfixFixity Source # 
Instance details

Defined in Inferno.Types.Syntax

Ord InfixFixity Source # 
Instance details

Defined in Inferno.Types.Syntax

VCHashUpdate InfixFixity Source # 
Instance details

Defined in Inferno.Types.VersionControl

type Rep InfixFixity Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep InfixFixity = D1 ('MetaData "InfixFixity" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (C1 ('MetaCons "NoFix" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LeftFix" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RightFix" 'PrefixI 'False) (U1 :: Type -> Type)))

data Fixity Source #

Instances

Instances details
FromJSON Fixity Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON Fixity Source # 
Instance details

Defined in Inferno.Types.Syntax

Data Fixity Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: Fixity -> Constr #

dataTypeOf :: Fixity -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Fixity Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Show Fixity Source # 
Instance details

Defined in Inferno.Types.Syntax

Eq Fixity Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

Ord Fixity Source # 
Instance details

Defined in Inferno.Types.Syntax

VCHashUpdate Fixity Source # 
Instance details

Defined in Inferno.Types.VersionControl

type Rep Fixity Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep Fixity = D1 ('MetaData "Fixity" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (C1 ('MetaCons "InfixOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfixFixity)) :+: C1 ('MetaCons "PrefixOp" 'PrefixI 'False) (U1 :: Type -> Type))

data Comment pos Source #

Constructors

LineComment pos Text pos 
BlockComment pos Text pos 

Instances

Instances details
Foldable Comment Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fold :: Monoid m => Comment m -> m #

foldMap :: Monoid m => (a -> m) -> Comment a -> m #

foldMap' :: Monoid m => (a -> m) -> Comment a -> m #

foldr :: (a -> b -> b) -> b -> Comment a -> b #

foldr' :: (a -> b -> b) -> b -> Comment a -> b #

foldl :: (b -> a -> b) -> b -> Comment a -> b #

foldl' :: (b -> a -> b) -> b -> Comment a -> b #

foldr1 :: (a -> a -> a) -> Comment a -> a #

foldl1 :: (a -> a -> a) -> Comment a -> a #

toList :: Comment a -> [a] #

null :: Comment a -> Bool #

length :: Comment a -> Int #

elem :: Eq a => a -> Comment a -> Bool #

maximum :: Ord a => Comment a -> a #

minimum :: Ord a => Comment a -> a #

sum :: Num a => Comment a -> a #

product :: Num a => Comment a -> a #

Functor Comment Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fmap :: (a -> b) -> Comment a -> Comment b #

(<$) :: a -> Comment b -> Comment a #

BlockUtils Comment Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSON pos => FromJSON (Comment pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON pos => ToJSON (Comment pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Data pos => Data (Comment pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: Comment pos -> Constr #

dataTypeOf :: Comment pos -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Comment pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep (Comment pos) :: Type -> Type #

Methods

from :: Comment pos -> Rep (Comment pos) x #

to :: Rep (Comment pos) x -> Comment pos #

Show pos => Show (Comment pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> Comment pos -> ShowS #

show :: Comment pos -> String #

showList :: [Comment pos] -> ShowS #

Eq pos => Eq (Comment pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

(==) :: Comment pos -> Comment pos -> Bool #

(/=) :: Comment pos -> Comment pos -> Bool #

Ord pos => Ord (Comment pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

compare :: Comment pos -> Comment pos -> Ordering #

(<) :: Comment pos -> Comment pos -> Bool #

(<=) :: Comment pos -> Comment pos -> Bool #

(>) :: Comment pos -> Comment pos -> Bool #

(>=) :: Comment pos -> Comment pos -> Bool #

max :: Comment pos -> Comment pos -> Comment pos #

min :: Comment pos -> Comment pos -> Comment pos #

VCHashUpdate a => VCHashUpdate (Comment a) Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty (Comment a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: Comment a -> Doc ann #

prettyList :: [Comment a] -> Doc ann #

type Rep (Comment pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

data IStr (f :: Bool) e where Source #

Constructors

ISEmpty :: IStr 'True e 
ISStr :: Text -> IStr 'True e -> IStr 'False e 
ISExpr :: Typeable f => e -> IStr f e -> IStr 'True e 

Instances

Instances details
Foldable (IStr f) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fold :: Monoid m => IStr f m -> m #

foldMap :: Monoid m => (a -> m) -> IStr f a -> m #

foldMap' :: Monoid m => (a -> m) -> IStr f a -> m #

foldr :: (a -> b -> b) -> b -> IStr f a -> b #

foldr' :: (a -> b -> b) -> b -> IStr f a -> b #

foldl :: (b -> a -> b) -> b -> IStr f a -> b #

foldl' :: (b -> a -> b) -> b -> IStr f a -> b #

foldr1 :: (a -> a -> a) -> IStr f a -> a #

foldl1 :: (a -> a -> a) -> IStr f a -> a #

toList :: IStr f a -> [a] #

null :: IStr f a -> Bool #

length :: IStr f a -> Int #

elem :: Eq a => a -> IStr f a -> Bool #

maximum :: Ord a => IStr f a -> a #

minimum :: Ord a => IStr f a -> a #

sum :: Num a => IStr f a -> a #

product :: Num a => IStr f a -> a #

Traversable (IStr f) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

traverse :: Applicative f0 => (a -> f0 b) -> IStr f a -> f0 (IStr f b) #

sequenceA :: Applicative f0 => IStr f (f0 a) -> f0 (IStr f a) #

mapM :: Monad m => (a -> m b) -> IStr f a -> m (IStr f b) #

sequence :: Monad m => IStr f (m a) -> m (IStr f a) #

Functor (IStr f) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fmap :: (a -> b) -> IStr f a -> IStr f b #

(<$) :: a -> IStr f b -> IStr f a #

(Typeable f, Data e) => Data (IStr f e) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IStr f e -> c (IStr f e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IStr f e) #

toConstr :: IStr f e -> Constr #

dataTypeOf :: IStr f e -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> IStr f e -> IStr f e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IStr f e -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IStr f e -> r #

gmapQ :: (forall d. Data d => d -> u) -> IStr f e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IStr f e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IStr f e -> m (IStr f e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IStr f e -> m (IStr f e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IStr f e -> m (IStr f e) #

Show e => Show (IStr f e) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> IStr f e -> ShowS #

show :: IStr f e -> String #

showList :: [IStr f e] -> ShowS #

VCHashUpdate e => VCHashUpdate (IStr f e) Source # 
Instance details

Defined in Inferno.Types.VersionControl

data SomeIStr e Source #

Constructors

forall f.Typeable f => SomeIStr (IStr f e) 

Instances

Instances details
Foldable SomeIStr Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fold :: Monoid m => SomeIStr m -> m #

foldMap :: Monoid m => (a -> m) -> SomeIStr a -> m #

foldMap' :: Monoid m => (a -> m) -> SomeIStr a -> m #

foldr :: (a -> b -> b) -> b -> SomeIStr a -> b #

foldr' :: (a -> b -> b) -> b -> SomeIStr a -> b #

foldl :: (b -> a -> b) -> b -> SomeIStr a -> b #

foldl' :: (b -> a -> b) -> b -> SomeIStr a -> b #

foldr1 :: (a -> a -> a) -> SomeIStr a -> a #

foldl1 :: (a -> a -> a) -> SomeIStr a -> a #

toList :: SomeIStr a -> [a] #

null :: SomeIStr a -> Bool #

length :: SomeIStr a -> Int #

elem :: Eq a => a -> SomeIStr a -> Bool #

maximum :: Ord a => SomeIStr a -> a #

minimum :: Ord a => SomeIStr a -> a #

sum :: Num a => SomeIStr a -> a #

product :: Num a => SomeIStr a -> a #

Traversable SomeIStr Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

traverse :: Applicative f => (a -> f b) -> SomeIStr a -> f (SomeIStr b) #

sequenceA :: Applicative f => SomeIStr (f a) -> f (SomeIStr a) #

mapM :: Monad m => (a -> m b) -> SomeIStr a -> m (SomeIStr b) #

sequence :: Monad m => SomeIStr (m a) -> m (SomeIStr a) #

Functor SomeIStr Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fmap :: (a -> b) -> SomeIStr a -> SomeIStr b #

(<$) :: a -> SomeIStr b -> SomeIStr a #

FromJSON e => FromJSON (SomeIStr e) Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON e => ToJSON (SomeIStr e) Source # 
Instance details

Defined in Inferno.Types.Syntax

Data e => Data (SomeIStr e) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: SomeIStr e -> Constr #

dataTypeOf :: SomeIStr e -> DataType #

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

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

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

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

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

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

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

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

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

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

Show e => Show (SomeIStr e) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> SomeIStr e -> ShowS #

show :: SomeIStr e -> String #

showList :: [SomeIStr e] -> ShowS #

Eq e => Eq (SomeIStr e) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

(==) :: SomeIStr e -> SomeIStr e -> Bool #

(/=) :: SomeIStr e -> SomeIStr e -> Bool #

Ord e => Ord (SomeIStr e) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

compare :: SomeIStr e -> SomeIStr e -> Ordering #

(<) :: SomeIStr e -> SomeIStr e -> Bool #

(<=) :: SomeIStr e -> SomeIStr e -> Bool #

(>) :: SomeIStr e -> SomeIStr e -> Bool #

(>=) :: SomeIStr e -> SomeIStr e -> Bool #

max :: SomeIStr e -> SomeIStr e -> SomeIStr e #

min :: SomeIStr e -> SomeIStr e -> SomeIStr e #

VCHashUpdate e => VCHashUpdate (SomeIStr e) Source # 
Instance details

Defined in Inferno.Types.VersionControl

data Lit Source #

Instances

Instances details
FromJSON Lit Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON Lit Source # 
Instance details

Defined in Inferno.Types.Syntax

Data Lit Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: Lit -> Constr #

dataTypeOf :: Lit -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Lit Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep Lit :: Type -> Type #

Methods

from :: Lit -> Rep Lit x #

to :: Rep Lit x -> Lit #

Show Lit Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> Lit -> ShowS #

show :: Lit -> String #

showList :: [Lit] -> ShowS #

Eq Lit Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

Ord Lit Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

compare :: Lit -> Lit -> Ordering #

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

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

(>) :: Lit -> Lit -> Bool #

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

max :: Lit -> Lit -> Lit #

min :: Lit -> Lit -> Lit #

ElementPosition Lit Source # 
Instance details

Defined in Inferno.Types.Syntax

VCHashUpdate Lit Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty Lit Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: Lit -> Doc ann #

prettyList :: [Lit] -> Doc ann #

type Rep Lit Source # 
Instance details

Defined in Inferno.Types.Syntax

data Pat hash pos Source #

Constructors

PVar pos (Maybe Ident) 
PEnum pos hash (Scoped ModuleName) Ident 
PLit pos Lit 
POne pos (Pat hash pos) 
PEmpty pos 
PTuple pos (TList (Pat hash pos, Maybe pos)) pos 
PCommentAbove (Comment pos) (Pat hash pos) 
PCommentAfter (Pat hash pos) (Comment pos) 
PCommentBelow (Pat hash pos) (Comment pos) 

Instances

Instances details
Bifunctor Pat Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

bimap :: (a -> b) -> (c -> d) -> Pat a c -> Pat b d #

first :: (a -> b) -> Pat a c -> Pat b c #

second :: (b -> c) -> Pat a b -> Pat a c #

Foldable (Pat hash) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fold :: Monoid m => Pat hash m -> m #

foldMap :: Monoid m => (a -> m) -> Pat hash a -> m #

foldMap' :: Monoid m => (a -> m) -> Pat hash a -> m #

foldr :: (a -> b -> b) -> b -> Pat hash a -> b #

foldr' :: (a -> b -> b) -> b -> Pat hash a -> b #

foldl :: (b -> a -> b) -> b -> Pat hash a -> b #

foldl' :: (b -> a -> b) -> b -> Pat hash a -> b #

foldr1 :: (a -> a -> a) -> Pat hash a -> a #

foldl1 :: (a -> a -> a) -> Pat hash a -> a #

toList :: Pat hash a -> [a] #

null :: Pat hash a -> Bool #

length :: Pat hash a -> Int #

elem :: Eq a => a -> Pat hash a -> Bool #

maximum :: Ord a => Pat hash a -> a #

minimum :: Ord a => Pat hash a -> a #

sum :: Num a => Pat hash a -> a #

product :: Num a => Pat hash a -> a #

Functor (Pat hash) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fmap :: (a -> b) -> Pat hash a -> Pat hash b #

(<$) :: a -> Pat hash b -> Pat hash a #

BlockUtils (Pat hash) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

blockPosition :: Pat hash SourcePos -> (SourcePos, SourcePos) Source #

removeComments :: Pat hash pos -> Pat hash pos Source #

hasLeadingComment :: Pat hash pos -> Bool Source #

hasTrailingComment :: Pat hash pos -> Bool Source #

renameModule :: Scoped ModuleName -> Pat hash pos -> Pat hash pos Source #

(FromJSON hash, FromJSON pos) => FromJSON (Pat hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

parseJSON :: Value -> Parser (Pat hash pos) #

parseJSONList :: Value -> Parser [Pat hash pos] #

(ToJSON pos, ToJSON hash) => ToJSON (Pat hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

toJSON :: Pat hash pos -> Value #

toEncoding :: Pat hash pos -> Encoding #

toJSONList :: [Pat hash pos] -> Value #

toEncodingList :: [Pat hash pos] -> Encoding #

(Data hash, Data pos) => Data (Pat hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat hash pos -> c (Pat hash pos) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat hash pos) #

toConstr :: Pat hash pos -> Constr #

dataTypeOf :: Pat hash pos -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Pat hash pos -> Pat hash pos #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat hash pos -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat hash pos -> r #

gmapQ :: (forall d. Data d => d -> u) -> Pat hash pos -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat hash pos -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat hash pos -> m (Pat hash pos) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat hash pos -> m (Pat hash pos) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat hash pos -> m (Pat hash pos) #

Generic (Pat hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep (Pat hash pos) :: Type -> Type #

Methods

from :: Pat hash pos -> Rep (Pat hash pos) x #

to :: Rep (Pat hash pos) x -> Pat hash pos #

(Show pos, Show hash) => Show (Pat hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> Pat hash pos -> ShowS #

show :: Pat hash pos -> String #

showList :: [Pat hash pos] -> ShowS #

(Eq pos, Eq hash) => Eq (Pat hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

(==) :: Pat hash pos -> Pat hash pos -> Bool #

(/=) :: Pat hash pos -> Pat hash pos -> Bool #

(Ord pos, Ord hash) => Ord (Pat hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

compare :: Pat hash pos -> Pat hash pos -> Ordering #

(<) :: Pat hash pos -> Pat hash pos -> Bool #

(<=) :: Pat hash pos -> Pat hash pos -> Bool #

(>) :: Pat hash pos -> Pat hash pos -> Bool #

(>=) :: Pat hash pos -> Pat hash pos -> Bool #

max :: Pat hash pos -> Pat hash pos -> Pat hash pos #

min :: Pat hash pos -> Pat hash pos -> Pat hash pos #

(VCHashUpdate hash, VCHashUpdate a) => VCHashUpdate (Pat hash a) Source # 
Instance details

Defined in Inferno.Types.VersionControl

Methods

(&<) :: Context SHA256 -> Pat hash a -> Context SHA256 Source #

Pretty (Pat hash a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: Pat hash a -> Doc ann #

prettyList :: [Pat hash a] -> Doc ann #

Corecursive (Pat hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

embed :: Base (Pat hash pos) (Pat hash pos) -> Pat hash pos #

ana :: (a -> Base (Pat hash pos) a) -> a -> Pat hash pos #

apo :: (a -> Base (Pat hash pos) (Either (Pat hash pos) a)) -> a -> Pat hash pos #

postpro :: Recursive (Pat hash pos) => (forall b. Base (Pat hash pos) b -> Base (Pat hash pos) b) -> (a -> Base (Pat hash pos) a) -> a -> Pat hash pos #

gpostpro :: (Recursive (Pat hash pos), Monad m) => (forall b. m (Base (Pat hash pos) b) -> Base (Pat hash pos) (m b)) -> (forall c. Base (Pat hash pos) c -> Base (Pat hash pos) c) -> (a -> Base (Pat hash pos) (m a)) -> a -> Pat hash pos #

Recursive (Pat hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

project :: Pat hash pos -> Base (Pat hash pos) (Pat hash pos) #

cata :: (Base (Pat hash pos) a -> a) -> Pat hash pos -> a #

para :: (Base (Pat hash pos) (Pat hash pos, a) -> a) -> Pat hash pos -> a #

gpara :: (Corecursive (Pat hash pos), Comonad w) => (forall b. Base (Pat hash pos) (w b) -> w (Base (Pat hash pos) b)) -> (Base (Pat hash pos) (EnvT (Pat hash pos) w a) -> a) -> Pat hash pos -> a #

prepro :: Corecursive (Pat hash pos) => (forall b. Base (Pat hash pos) b -> Base (Pat hash pos) b) -> (Base (Pat hash pos) a -> a) -> Pat hash pos -> a #

gprepro :: (Corecursive (Pat hash pos), Comonad w) => (forall b. Base (Pat hash pos) (w b) -> w (Base (Pat hash pos) b)) -> (forall c. Base (Pat hash pos) c -> Base (Pat hash pos) c) -> (Base (Pat hash pos) (w a) -> a) -> Pat hash pos -> a #

Dependencies (Pat hash pos) hash Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

getDependencies :: Pat hash pos -> Set hash Source #

type Rep (Pat hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep (Pat hash pos) = D1 ('MetaData "Pat" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (((C1 ('MetaCons "PVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ident))) :+: C1 ('MetaCons "PEnum" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 hash)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Scoped ModuleName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)))) :+: (C1 ('MetaCons "PLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lit)) :+: C1 ('MetaCons "POne" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat hash pos))))) :+: ((C1 ('MetaCons "PEmpty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos)) :+: C1 ('MetaCons "PTuple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TList (Pat hash pos, Maybe pos))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos)))) :+: (C1 ('MetaCons "PCommentAbove" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Comment pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat hash pos))) :+: (C1 ('MetaCons "PCommentAfter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat hash pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Comment pos))) :+: C1 ('MetaCons "PCommentBelow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat hash pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Comment pos)))))))
type Base (Pat hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

type Base (Pat hash pos) = PatF hash pos

data PatF (hash :: Type) (pos :: Type) r Source #

Constructors

PVarF pos (Maybe Ident) 
PEnumF pos hash (Scoped ModuleName) Ident 
PLitF pos Lit 
POneF pos r 
PEmptyF pos 
PTupleF pos (TList (r, Maybe pos)) pos 
PCommentAboveF (Comment pos) r 
PCommentAfterF r (Comment pos) 
PCommentBelowF r (Comment pos) 

Instances

Instances details
Foldable (PatF hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fold :: Monoid m => PatF hash pos m -> m #

foldMap :: Monoid m => (a -> m) -> PatF hash pos a -> m #

foldMap' :: Monoid m => (a -> m) -> PatF hash pos a -> m #

foldr :: (a -> b -> b) -> b -> PatF hash pos a -> b #

foldr' :: (a -> b -> b) -> b -> PatF hash pos a -> b #

foldl :: (b -> a -> b) -> b -> PatF hash pos a -> b #

foldl' :: (b -> a -> b) -> b -> PatF hash pos a -> b #

foldr1 :: (a -> a -> a) -> PatF hash pos a -> a #

foldl1 :: (a -> a -> a) -> PatF hash pos a -> a #

toList :: PatF hash pos a -> [a] #

null :: PatF hash pos a -> Bool #

length :: PatF hash pos a -> Int #

elem :: Eq a => a -> PatF hash pos a -> Bool #

maximum :: Ord a => PatF hash pos a -> a #

minimum :: Ord a => PatF hash pos a -> a #

sum :: Num a => PatF hash pos a -> a #

product :: Num a => PatF hash pos a -> a #

Traversable (PatF hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

traverse :: Applicative f => (a -> f b) -> PatF hash pos a -> f (PatF hash pos b) #

sequenceA :: Applicative f => PatF hash pos (f a) -> f (PatF hash pos a) #

mapM :: Monad m => (a -> m b) -> PatF hash pos a -> m (PatF hash pos b) #

sequence :: Monad m => PatF hash pos (m a) -> m (PatF hash pos a) #

Functor (PatF hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fmap :: (a -> b) -> PatF hash pos a -> PatF hash pos b #

(<$) :: a -> PatF hash pos b -> PatF hash pos a #

newtype TV Source #

Constructors

TV 

Fields

Instances

Instances details
Arbitrary TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

arbitrary :: Gen TV #

shrink :: TV -> [TV] #

FromJSON TV Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSONKey TV Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON TV Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSONKey TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Data TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: TV -> Constr #

dataTypeOf :: TV -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep TV :: Type -> Type #

Methods

from :: TV -> Rep TV x #

to :: Rep TV x -> TV #

Show TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> TV -> ShowS #

show :: TV -> String #

showList :: [TV] -> ShowS #

Serialize TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

put :: Putter TV #

get :: Get TV #

NFData TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

rnf :: TV -> () #

Eq TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

Ord TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

compare :: TV -> TV -> Ordering #

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

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

(>) :: TV -> TV -> Bool #

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

max :: TV -> TV -> TV #

min :: TV -> TV -> TV #

Hashable TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

hashWithSalt :: Int -> TV -> Int #

hash :: TV -> Int #

VCHashUpdate TV Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty TV Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: TV -> Doc ann #

prettyList :: [TV] -> Doc ann #

ToADTArbitrary TV Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep TV Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep TV = D1 ('MetaData "TV" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'True) (C1 ('MetaCons "TV" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTV") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data BaseType Source #

Instances

Instances details
Arbitrary BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSON BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Data BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: BaseType -> Constr #

dataTypeOf :: BaseType -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep BaseType :: Type -> Type #

Methods

from :: BaseType -> Rep BaseType x #

to :: Rep BaseType x -> BaseType #

Show BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Serialize BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

NFData BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

rnf :: BaseType -> () #

Eq BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Ord BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Hashable BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

hashWithSalt :: Int -> BaseType -> Int #

hash :: BaseType -> Int #

VCHashUpdate BaseType Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: BaseType -> Doc ann #

prettyList :: [BaseType] -> Doc ann #

ToADTArbitrary BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep BaseType Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep BaseType = D1 ('MetaData "BaseType" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (((C1 ('MetaCons "TInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TDouble" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TWord16" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TWord32" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TWord64" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "TText" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TTime" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TTimeDiff" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TResolution" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TEnum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Ident)))))))

data InfernoType Source #

Instances

Instances details
Arbitrary InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

FromJSON InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Data InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: InfernoType -> Constr #

dataTypeOf :: InfernoType -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep InfernoType :: Type -> Type #

Show InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Serialize InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

NFData InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

rnf :: InfernoType -> () #

Eq InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Ord InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Hashable InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Substitutable InfernoType Source # 
Instance details

Defined in Inferno.Types.Type

VCHashUpdate InfernoType Source # 
Instance details

Defined in Inferno.Types.VersionControl

Pretty InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: InfernoType -> Doc ann #

prettyList :: [InfernoType] -> Doc ann #

ToADTArbitrary InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep InfernoType Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep InfernoType = D1 ('MetaData "InfernoType" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (((C1 ('MetaCons "TVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TV)) :+: C1 ('MetaCons "TBase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BaseType))) :+: (C1 ('MetaCons "TArr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType)) :+: C1 ('MetaCons "TArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType)))) :+: ((C1 ('MetaCons "TSeries" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType)) :+: C1 ('MetaCons "TOptional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType))) :+: (C1 ('MetaCons "TTuple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TList InfernoType))) :+: C1 ('MetaCons "TRep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType)))))

data Expr hash pos Source #

Constructors

Var pos hash (Scoped ModuleName) ImplExpl 
OpVar pos hash (Scoped ModuleName) Ident 
TypeRep pos InfernoType 
Enum pos hash (Scoped ModuleName) Ident 
App (Expr hash pos) (Expr hash pos) 
Lam pos (NonEmpty (pos, Maybe ExtIdent)) pos (Expr hash pos) 
Let pos pos ImplExpl pos (Expr hash pos) pos (Expr hash pos) 
Lit pos Lit 
InterpolatedString pos (SomeIStr (pos, Expr hash pos, pos)) pos 
If pos (Expr hash pos) pos (Expr hash pos) pos (Expr hash pos) 
Op (Expr hash pos) pos hash (Int, InfixFixity) (Scoped ModuleName) Ident (Expr hash pos) 
PreOp pos hash Int (Scoped ModuleName) Ident (Expr hash pos) 
Tuple pos (TList (Expr hash pos, Maybe pos)) pos 
One pos (Expr hash pos) 
Empty pos 
Assert pos (Expr hash pos) pos (Expr hash pos) 
Case pos (Expr hash pos) pos (NonEmpty (pos, Pat hash pos, pos, Expr hash pos)) pos 
Array pos [(Expr hash pos, Maybe pos)] pos 
ArrayComp pos (Expr hash pos) pos (NonEmpty (pos, Ident, pos, Expr hash pos, Maybe pos)) (Maybe (pos, Expr hash pos)) pos 
CommentAbove (Comment pos) (Expr hash pos) 
CommentAfter (Expr hash pos) (Comment pos) 
CommentBelow (Expr hash pos) (Comment pos) 
Bracketed pos (Expr hash pos) pos 
RenameModule pos ModuleName pos ModuleName pos (Expr hash pos) 
OpenModule pos hash ModuleName [(Import pos, Maybe pos)] pos (Expr hash pos) 

Bundled Patterns

pattern Var_ :: forall hash pos. hash -> Scoped ModuleName -> ImplExpl -> Expr hash pos 
pattern OpVar_ :: forall hash pos. hash -> Scoped ModuleName -> Ident -> Expr hash pos 
pattern TypeRep_ :: forall hash pos. InfernoType -> Expr hash pos 
pattern Enum_ :: forall hash pos. hash -> Scoped ModuleName -> Ident -> Expr hash pos 
pattern App_ :: forall hash pos. Expr hash pos -> Expr hash pos -> Expr hash pos 
pattern Lam_ :: forall hash pos. NonEmpty (pos, Maybe ExtIdent) -> Expr hash pos -> Expr hash pos 
pattern Let_ :: forall hash pos. ImplExpl -> Expr hash pos -> Expr hash pos -> Expr hash pos 
pattern Lit_ :: forall hash pos. Lit -> Expr hash pos 
pattern InterpolatedString_ :: forall hash pos. SomeIStr (pos, Expr hash pos, pos) -> Expr hash pos 
pattern If_ :: forall hash pos. Expr hash pos -> Expr hash pos -> Expr hash pos -> Expr hash pos 
pattern Op_ :: forall hash pos. Expr hash pos -> hash -> Scoped ModuleName -> Ident -> Expr hash pos -> Expr hash pos 
pattern PreOp_ :: forall hash pos. hash -> Scoped ModuleName -> Ident -> Expr hash pos -> Expr hash pos 
pattern Tuple_ :: forall hash pos. TList (Expr hash pos, Maybe pos) -> Expr hash pos 
pattern One_ :: forall hash pos. Expr hash pos -> Expr hash pos 
pattern Empty_ :: forall hash pos. Expr hash pos 
pattern Assert_ :: forall hash pos. Expr hash pos -> Expr hash pos -> Expr hash pos 
pattern Case_ :: forall hash pos. Expr hash pos -> NonEmpty (pos, Pat hash pos, pos, Expr hash pos) -> Expr hash pos 
pattern Array_ :: forall hash pos. [(Expr hash pos, Maybe pos)] -> Expr hash pos 
pattern ArrayComp_ :: forall hash pos. Expr hash pos -> NonEmpty (pos, Ident, pos, Expr hash pos, Maybe pos) -> Maybe (pos, Expr hash pos) -> Expr hash pos 
pattern Bracketed_ :: forall hash pos. Expr hash pos -> Expr hash pos 
pattern RenameModule_ :: forall hash pos. ModuleName -> ModuleName -> Expr hash pos -> Expr hash pos 
pattern OpenModule_ :: forall hash pos. ModuleName -> [(Import pos, Maybe pos)] -> Expr hash pos -> Expr hash pos 

Instances

Instances details
Bifunctor Expr Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

bimap :: (a -> b) -> (c -> d) -> Expr a c -> Expr b d #

first :: (a -> b) -> Expr a c -> Expr b c #

second :: (b -> c) -> Expr a b -> Expr a c #

Foldable (Expr hash) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fold :: Monoid m => Expr hash m -> m #

foldMap :: Monoid m => (a -> m) -> Expr hash a -> m #

foldMap' :: Monoid m => (a -> m) -> Expr hash a -> m #

foldr :: (a -> b -> b) -> b -> Expr hash a -> b #

foldr' :: (a -> b -> b) -> b -> Expr hash a -> b #

foldl :: (b -> a -> b) -> b -> Expr hash a -> b #

foldl' :: (b -> a -> b) -> b -> Expr hash a -> b #

foldr1 :: (a -> a -> a) -> Expr hash a -> a #

foldl1 :: (a -> a -> a) -> Expr hash a -> a #

toList :: Expr hash a -> [a] #

null :: Expr hash a -> Bool #

length :: Expr hash a -> Int #

elem :: Eq a => a -> Expr hash a -> Bool #

maximum :: Ord a => Expr hash a -> a #

minimum :: Ord a => Expr hash a -> a #

sum :: Num a => Expr hash a -> a #

product :: Num a => Expr hash a -> a #

Functor (Expr hash) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fmap :: (a -> b) -> Expr hash a -> Expr hash b #

(<$) :: a -> Expr hash b -> Expr hash a #

BlockUtils (Expr hash) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

blockPosition :: Expr hash SourcePos -> (SourcePos, SourcePos) Source #

removeComments :: Expr hash pos -> Expr hash pos Source #

hasLeadingComment :: Expr hash pos -> Bool Source #

hasTrailingComment :: Expr hash pos -> Bool Source #

renameModule :: Scoped ModuleName -> Expr hash pos -> Expr hash pos Source #

(FromJSON hash, FromJSON pos) => FromJSON (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

parseJSON :: Value -> Parser (Expr hash pos) #

parseJSONList :: Value -> Parser [Expr hash pos] #

(ToJSON hash, ToJSON pos) => ToJSON (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

toJSON :: Expr hash pos -> Value #

toEncoding :: Expr hash pos -> Encoding #

toJSONList :: [Expr hash pos] -> Value #

toEncodingList :: [Expr hash pos] -> Encoding #

(Data hash, Data pos) => Data (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expr hash pos -> c (Expr hash pos) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Expr hash pos) #

toConstr :: Expr hash pos -> Constr #

dataTypeOf :: Expr hash pos -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Expr hash pos -> Expr hash pos #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expr hash pos -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expr hash pos -> r #

gmapQ :: (forall d. Data d => d -> u) -> Expr hash pos -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Expr hash pos -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expr hash pos -> m (Expr hash pos) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr hash pos -> m (Expr hash pos) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr hash pos -> m (Expr hash pos) #

Generic (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep (Expr hash pos) :: Type -> Type #

Methods

from :: Expr hash pos -> Rep (Expr hash pos) x #

to :: Rep (Expr hash pos) x -> Expr hash pos #

(Show pos, Show hash) => Show (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> Expr hash pos -> ShowS #

show :: Expr hash pos -> String #

showList :: [Expr hash pos] -> ShowS #

(Eq pos, Eq hash) => Eq (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

(==) :: Expr hash pos -> Expr hash pos -> Bool #

(/=) :: Expr hash pos -> Expr hash pos -> Bool #

(Ord pos, Ord hash) => Ord (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

compare :: Expr hash pos -> Expr hash pos -> Ordering #

(<) :: Expr hash pos -> Expr hash pos -> Bool #

(<=) :: Expr hash pos -> Expr hash pos -> Bool #

(>) :: Expr hash pos -> Expr hash pos -> Bool #

(>=) :: Expr hash pos -> Expr hash pos -> Bool #

max :: Expr hash pos -> Expr hash pos -> Expr hash pos #

min :: Expr hash pos -> Expr hash pos -> Expr hash pos #

(VCHashUpdate hash, VCHashUpdate a) => VCHashUpdate (Expr hash a) Source # 
Instance details

Defined in Inferno.Types.VersionControl

Methods

(&<) :: Context SHA256 -> Expr hash a -> Context SHA256 Source #

Pretty (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

pretty :: Expr hash pos -> Doc ann #

prettyList :: [Expr hash pos] -> Doc ann #

Corecursive (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

embed :: Base (Expr hash pos) (Expr hash pos) -> Expr hash pos #

ana :: (a -> Base (Expr hash pos) a) -> a -> Expr hash pos #

apo :: (a -> Base (Expr hash pos) (Either (Expr hash pos) a)) -> a -> Expr hash pos #

postpro :: Recursive (Expr hash pos) => (forall b. Base (Expr hash pos) b -> Base (Expr hash pos) b) -> (a -> Base (Expr hash pos) a) -> a -> Expr hash pos #

gpostpro :: (Recursive (Expr hash pos), Monad m) => (forall b. m (Base (Expr hash pos) b) -> Base (Expr hash pos) (m b)) -> (forall c. Base (Expr hash pos) c -> Base (Expr hash pos) c) -> (a -> Base (Expr hash pos) (m a)) -> a -> Expr hash pos #

Recursive (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

project :: Expr hash pos -> Base (Expr hash pos) (Expr hash pos) #

cata :: (Base (Expr hash pos) a -> a) -> Expr hash pos -> a #

para :: (Base (Expr hash pos) (Expr hash pos, a) -> a) -> Expr hash pos -> a #

gpara :: (Corecursive (Expr hash pos), Comonad w) => (forall b. Base (Expr hash pos) (w b) -> w (Base (Expr hash pos) b)) -> (Base (Expr hash pos) (EnvT (Expr hash pos) w a) -> a) -> Expr hash pos -> a #

prepro :: Corecursive (Expr hash pos) => (forall b. Base (Expr hash pos) b -> Base (Expr hash pos) b) -> (Base (Expr hash pos) a -> a) -> Expr hash pos -> a #

gprepro :: (Corecursive (Expr hash pos), Comonad w) => (forall b. Base (Expr hash pos) (w b) -> w (Base (Expr hash pos) b)) -> (forall c. Base (Expr hash pos) c -> Base (Expr hash pos) c) -> (Base (Expr hash pos) (w a) -> a) -> Expr hash pos -> a #

Dependencies (Expr hash pos) hash Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

getDependencies :: Expr hash pos -> Set hash Source #

type Rep (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep (Expr hash pos) = D1 ('MetaData "Expr" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) ((((C1 ('MetaCons "Var" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 hash)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Scoped ModuleName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ImplExpl))) :+: (C1 ('MetaCons "OpVar" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 hash)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Scoped ModuleName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) :+: C1 ('MetaCons "TypeRep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InfernoType)))) :+: (C1 ('MetaCons "Enum" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 hash)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Scoped ModuleName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) :+: (C1 ('MetaCons "App" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))) :+: C1 ('MetaCons "Lam" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (pos, Maybe ExtIdent)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))))))) :+: ((C1 ('MetaCons "Let" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ImplExpl))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))))) :+: (C1 ('MetaCons "Lit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lit)) :+: C1 ('MetaCons "InterpolatedString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SomeIStr (pos, Expr hash pos, pos))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos))))) :+: (C1 ('MetaCons "If" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))))) :+: (C1 ('MetaCons "Op" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 hash))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, InfixFixity)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Scoped ModuleName))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))))) :+: C1 ('MetaCons "PreOp" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 hash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Scoped ModuleName)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))))))))) :+: (((C1 ('MetaCons "Tuple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TList (Expr hash pos, Maybe pos))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos))) :+: (C1 ('MetaCons "One" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))) :+: C1 ('MetaCons "Empty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos)))) :+: (C1 ('MetaCons "Assert" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos)))) :+: (C1 ('MetaCons "Case" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (pos, Pat hash pos, pos, Expr hash pos))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos)))) :+: C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Expr hash pos, Maybe pos)]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos)))))) :+: ((C1 ('MetaCons "ArrayComp" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (pos, Ident, pos, Expr hash pos, Maybe pos))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (pos, Expr hash pos))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos)))) :+: (C1 ('MetaCons "CommentAbove" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Comment pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))) :+: C1 ('MetaCons "CommentAfter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Comment pos))))) :+: ((C1 ('MetaCons "CommentBelow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Comment pos))) :+: C1 ('MetaCons "Bracketed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos)))) :+: (C1 ('MetaCons "RenameModule" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))))) :+: C1 ('MetaCons "OpenModule" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 hash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Import pos, Maybe pos)]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expr hash pos))))))))))
type Base (Expr hash pos) Source # 
Instance details

Defined in Inferno.Types.Syntax

type Base (Expr hash pos)

class BlockUtils f where Source #

Instances

Instances details
BlockUtils Comment Source # 
Instance details

Defined in Inferno.Types.Syntax

BlockUtils Import Source # 
Instance details

Defined in Inferno.Types.Syntax

BlockUtils (Expr hash) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

blockPosition :: Expr hash SourcePos -> (SourcePos, SourcePos) Source #

removeComments :: Expr hash pos -> Expr hash pos Source #

hasLeadingComment :: Expr hash pos -> Bool Source #

hasTrailingComment :: Expr hash pos -> Bool Source #

renameModule :: Scoped ModuleName -> Expr hash pos -> Expr hash pos Source #

BlockUtils (Pat hash) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

blockPosition :: Pat hash SourcePos -> (SourcePos, SourcePos) Source #

removeComments :: Pat hash pos -> Pat hash pos Source #

hasLeadingComment :: Pat hash pos -> Bool Source #

hasTrailingComment :: Pat hash pos -> Bool Source #

renameModule :: Scoped ModuleName -> Pat hash pos -> Pat hash pos Source #

data TList a Source #

Constructors

TNil 
TCons a a [a] 

Instances

Instances details
Foldable TList Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fold :: Monoid m => TList m -> m #

foldMap :: Monoid m => (a -> m) -> TList a -> m #

foldMap' :: Monoid m => (a -> m) -> TList a -> m #

foldr :: (a -> b -> b) -> b -> TList a -> b #

foldr' :: (a -> b -> b) -> b -> TList a -> b #

foldl :: (b -> a -> b) -> b -> TList a -> b #

foldl' :: (b -> a -> b) -> b -> TList a -> b #

foldr1 :: (a -> a -> a) -> TList a -> a #

foldl1 :: (a -> a -> a) -> TList a -> a #

toList :: TList a -> [a] #

null :: TList a -> Bool #

length :: TList a -> Int #

elem :: Eq a => a -> TList a -> Bool #

maximum :: Ord a => TList a -> a #

minimum :: Ord a => TList a -> a #

sum :: Num a => TList a -> a #

product :: Num a => TList a -> a #

Traversable TList Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

traverse :: Applicative f => (a -> f b) -> TList a -> f (TList b) #

sequenceA :: Applicative f => TList (f a) -> f (TList a) #

mapM :: Monad m => (a -> m b) -> TList a -> m (TList b) #

sequence :: Monad m => TList (m a) -> m (TList a) #

Functor TList Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fmap :: (a -> b) -> TList a -> TList b #

(<$) :: a -> TList b -> TList a #

Arbitrary a => Arbitrary (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

arbitrary :: Gen (TList a) #

shrink :: TList a -> [TList a] #

FromJSON a => FromJSON (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON a => ToJSON (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Data a => Data (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: TList a -> Constr #

dataTypeOf :: TList a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep (TList a) :: Type -> Type #

Methods

from :: TList a -> Rep (TList a) x #

to :: Rep (TList a) x -> TList a #

Show a => Show (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> TList a -> ShowS #

show :: TList a -> String #

showList :: [TList a] -> ShowS #

Serialize a => Serialize (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

put :: Putter (TList a) #

get :: Get (TList a) #

NFData a => NFData (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

rnf :: TList a -> () #

Eq a => Eq (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

(==) :: TList a -> TList a -> Bool #

(/=) :: TList a -> TList a -> Bool #

Ord a => Ord (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

compare :: TList a -> TList a -> Ordering #

(<) :: TList a -> TList a -> Bool #

(<=) :: TList a -> TList a -> Bool #

(>) :: TList a -> TList a -> Bool #

(>=) :: TList a -> TList a -> Bool #

max :: TList a -> TList a -> TList a #

min :: TList a -> TList a -> TList a #

Hashable a => Hashable (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

hashWithSalt :: Int -> TList a -> Int #

hash :: TList a -> Int #

VCHashUpdate a => VCHashUpdate (TList a) Source # 
Instance details

Defined in Inferno.Types.VersionControl

Arbitrary a => ToADTArbitrary (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep (TList a) Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep (TList a) = D1 ('MetaData "TList" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (C1 ('MetaCons "TNil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TCons" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))))

data SigVar Source #

Constructors

SigVar Text 
SigOpVar Text 

Instances

Instances details
Data SigVar Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: SigVar -> Constr #

dataTypeOf :: SigVar -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SigVar Source # 
Instance details

Defined in Inferno.Types.Syntax

Eq SigVar Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

data SourcePos #

The data type SourcePos represents source positions. It contains the name of the source file, a line number, and a column number. Source line and column positions change intensively during parsing, so we need to make them strict to avoid memory leaks.

Constructors

SourcePos 

Fields

Instances

Instances details
FromJSON SourcePos Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON SourcePos Source # 
Instance details

Defined in Inferno.Types.Syntax

Data SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

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

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

toConstr :: SourcePos -> Constr #

dataTypeOf :: SourcePos -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePos :: Type -> Type #

Read SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Show SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

NFData SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

rnf :: SourcePos -> () #

Eq SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Ord SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

VCHashUpdate SourcePos Source # 
Instance details

Defined in Inferno.Types.VersionControl

type Rep SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

type Rep SourcePos = D1 ('MetaData "SourcePos" "Text.Megaparsec.Pos" "megaparsec-9.2.2-C7z8jWaM1K5L3stUFAJNLW" 'False) (C1 ('MetaCons "SourcePos" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "sourceLine") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos) :*: S1 ('MetaSel ('Just "sourceColumn") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos))))

data Scoped a Source #

Constructors

LocalScope 
Scope a 

Instances

Instances details
Foldable Scoped Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fold :: Monoid m => Scoped m -> m #

foldMap :: Monoid m => (a -> m) -> Scoped a -> m #

foldMap' :: Monoid m => (a -> m) -> Scoped a -> m #

foldr :: (a -> b -> b) -> b -> Scoped a -> b #

foldr' :: (a -> b -> b) -> b -> Scoped a -> b #

foldl :: (b -> a -> b) -> b -> Scoped a -> b #

foldl' :: (b -> a -> b) -> b -> Scoped a -> b #

foldr1 :: (a -> a -> a) -> Scoped a -> a #

foldl1 :: (a -> a -> a) -> Scoped a -> a #

toList :: Scoped a -> [a] #

null :: Scoped a -> Bool #

length :: Scoped a -> Int #

elem :: Eq a => a -> Scoped a -> Bool #

maximum :: Ord a => Scoped a -> a #

minimum :: Ord a => Scoped a -> a #

sum :: Num a => Scoped a -> a #

product :: Num a => Scoped a -> a #

Traversable Scoped Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

traverse :: Applicative f => (a -> f b) -> Scoped a -> f (Scoped b) #

sequenceA :: Applicative f => Scoped (f a) -> f (Scoped a) #

mapM :: Monad m => (a -> m b) -> Scoped a -> m (Scoped b) #

sequence :: Monad m => Scoped (m a) -> m (Scoped a) #

Functor Scoped Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

fmap :: (a -> b) -> Scoped a -> Scoped b #

(<$) :: a -> Scoped b -> Scoped a #

FromJSON a => FromJSON (Scoped a) Source # 
Instance details

Defined in Inferno.Types.Syntax

ToJSON a => ToJSON (Scoped a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Data a => Data (Scoped a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

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

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

toConstr :: Scoped a -> Constr #

dataTypeOf :: Scoped a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Scoped a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Associated Types

type Rep (Scoped a) :: Type -> Type #

Methods

from :: Scoped a -> Rep (Scoped a) x #

to :: Rep (Scoped a) x -> Scoped a #

Show a => Show (Scoped a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

showsPrec :: Int -> Scoped a -> ShowS #

show :: Scoped a -> String #

showList :: [Scoped a] -> ShowS #

Eq a => Eq (Scoped a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

(==) :: Scoped a -> Scoped a -> Bool #

(/=) :: Scoped a -> Scoped a -> Bool #

Ord a => Ord (Scoped a) Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

compare :: Scoped a -> Scoped a -> Ordering #

(<) :: Scoped a -> Scoped a -> Bool #

(<=) :: Scoped a -> Scoped a -> Bool #

(>) :: Scoped a -> Scoped a -> Bool #

(>=) :: Scoped a -> Scoped a -> Bool #

max :: Scoped a -> Scoped a -> Scoped a #

min :: Scoped a -> Scoped a -> Scoped a #

VCHashUpdate a => VCHashUpdate (Scoped a) Source # 
Instance details

Defined in Inferno.Types.VersionControl

type Rep (Scoped a) Source # 
Instance details

Defined in Inferno.Types.Syntax

type Rep (Scoped a) = D1 ('MetaData "Scoped" "Inferno.Types.Syntax" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (C1 ('MetaCons "LocalScope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Scope" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

class Dependencies f hash where Source #

Methods

getDependencies :: Ord hash => f -> Set hash Source #

Instances

Instances details
Dependencies (Expr hash pos) hash Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

getDependencies :: Expr hash pos -> Set hash Source #

Dependencies (Pat hash pos) hash Source # 
Instance details

Defined in Inferno.Types.Syntax

Methods

getDependencies :: Pat hash pos -> Set hash Source #

extractArgsAndPrettyPrint :: Expr hash pos -> ([Maybe Ident], Text) Source #

Extract the arguments of a script and pretty print the script body. This hides the internal variable arguments.

patternToExpr :: Pat () () -> Expr () () Source #

fromScoped :: a -> Scoped a -> a Source #

punctuate' :: Doc ann -> [Doc ann] -> [Doc ann] Source #

hideInternalIdents :: Expr hash pos -> Expr hash pos Source #

Filter out any var$n?var$n variables and their letlambda bindings This is used when pretty printing for the front-end, as we don't want the users to see these auto-generated internal variables.

substInternalIdents :: Map Int (Either Int InfernoType) -> Expr hash pos -> Expr hash pos Source #

Substitute every variable occurrence of `?var$i` with `var$j` if `(i, Left j)` is in in the supplied map. otherwise replace `?var$i` with `@t` if (i, Right t) in m`

Orphan instances