cubix-0.1.0.0: A framework for multi-language transformation
Safe HaskellNone
LanguageHaskell2010

Cubix.Language.Info

Synopsis

Documentation

data SourcePos Source #

Instances

Instances details
Eq SourcePos Source # 
Instance details

Defined in Cubix.Language.Info

Data SourcePos Source # 
Instance details

Defined in Cubix.Language.Info

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 #

Ord SourcePos Source # 
Instance details

Defined in Cubix.Language.Info

Read SourcePos Source # 
Instance details

Defined in Cubix.Language.Info

Show SourcePos Source # 
Instance details

Defined in Cubix.Language.Info

Generic SourcePos Source # 
Instance details

Defined in Cubix.Language.Info

Associated Types

type Rep SourcePos :: Type -> Type #

NFData SourcePos Source # 
Instance details

Defined in Cubix.Language.Info

Methods

rnf :: SourcePos -> () #

type Rep SourcePos Source # 
Instance details

Defined in Cubix.Language.Info

type Rep SourcePos = D1 ('MetaData "SourcePos" "Cubix.Language.Info" "cubix-0.1.0.0-GE3qzSJT6A0CUj1veI8jGO" 'False) (C1 ('MetaCons "SourcePos" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sourceFile") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: (S1 ('MetaSel ('Just "_sourceRow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "_sourceCol") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))))

sourceFile :: HasSourcePos c => Lens' c String Source #

sourceRow :: HasSourcePos c => Lens' c Int Source #

sourceCol :: HasSourcePos c => Lens' c Int Source #

data SourceSpan Source #

Instances

Instances details
Eq SourceSpan Source # 
Instance details

Defined in Cubix.Language.Info

Data SourceSpan Source # 
Instance details

Defined in Cubix.Language.Info

Methods

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

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

toConstr :: SourceSpan -> Constr #

dataTypeOf :: SourceSpan -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SourceSpan Source # 
Instance details

Defined in Cubix.Language.Info

Read SourceSpan Source # 
Instance details

Defined in Cubix.Language.Info

Show SourceSpan Source # 
Instance details

Defined in Cubix.Language.Info

Generic SourceSpan Source # 
Instance details

Defined in Cubix.Language.Info

Associated Types

type Rep SourceSpan :: Type -> Type #

type Rep SourceSpan Source # 
Instance details

Defined in Cubix.Language.Info

type Rep SourceSpan = D1 ('MetaData "SourceSpan" "Cubix.Language.Info" "cubix-0.1.0.0-GE3qzSJT6A0CUj1veI8jGO" 'False) (C1 ('MetaCons "SourceSpan" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sourceStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos) :*: S1 ('MetaSel ('Just "_sourceEnd") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos)))

sourceStart :: HasSourceSpan c => Lens' c SourcePos Source #

sourceEnd :: HasSourceSpan c => Lens' c SourcePos Source #

attrLabel :: HasAttrs c => Lens' c Label Source #

attrSpan :: HasAttrs c => Lens' c (Maybe SourceSpan) Source #

data Label Source #

Provides unique labels for AST nodes

Instances

Instances details
Eq Label Source # 
Instance details

Defined in Cubix.Language.Info

Methods

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

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

Data Label Source # 
Instance details

Defined in Cubix.Language.Info

Methods

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

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

toConstr :: Label -> Constr #

dataTypeOf :: Label -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Label Source # 
Instance details

Defined in Cubix.Language.Info

Methods

compare :: Label -> Label -> Ordering #

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

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

(>) :: Label -> Label -> Bool #

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

max :: Label -> Label -> Label #

min :: Label -> Label -> Label #

Read Label Source # 
Instance details

Defined in Cubix.Language.Info

Show Label Source # 
Instance details

Defined in Cubix.Language.Info

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

Generic Label Source # 
Instance details

Defined in Cubix.Language.Info

Associated Types

type Rep Label :: Type -> Type #

Methods

from :: Label -> Rep Label x #

to :: Rep Label x -> Label #

NFData Label Source # 
Instance details

Defined in Cubix.Language.Info

Methods

rnf :: Label -> () #

HasLabel Label Source # 
Instance details

Defined in Cubix.Language.Info

Methods

label :: Lens' Label Label Source #

(Monad m, MonadLabeler s m) => MonadAnnotater Label m Source # 
Instance details

Defined in Cubix.Language.Info

Methods

annM :: forall f (e :: Type -> Type) l. f e l -> m ((f :&: Label) e l) Source #

type Rep Label Source # 
Instance details

Defined in Cubix.Language.Info

type Rep Label = D1 ('MetaData "Label" "Cubix.Language.Info" "cubix-0.1.0.0-GE3qzSJT6A0CUj1veI8jGO" 'True) (C1 ('MetaCons "Label" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

class HasLabel c where Source #

Methods

label :: Lens' c Label Source #

Instances

Instances details
HasLabel Label Source # 
Instance details

Defined in Cubix.Language.Info

Methods

label :: Lens' Label Label Source #

class (MonadState s m, HasLabelGen s) => MonadLabeler s m | m -> s Source #

Instances

Instances details
(MonadState s m, HasLabelGen s) => MonadLabeler s m Source # 
Instance details

Defined in Cubix.Language.Info

data LabelGen Source #

Instances

Instances details
HasLabelGen LabelGen Source # 
Instance details

Defined in Cubix.Language.Info

class HasLabelGen s where Source #

Methods

labelGen :: Lens' s LabelGen Source #

Instances

Instances details
HasLabelGen LabelGen Source # 
Instance details

Defined in Cubix.Language.Info

annotateLabel :: (HTraversable f, MonadAnnotater Label m) => CxtFunM m f (f :&: Label) Source #

Fully annotates a term with fresh labels

annotateOuter :: (HTraversable f, MonadAnnotater a m) => Context f (AnnHFix a f) l -> m (AnnHFix a f l) Source #

annotateTop' :: (f :<: g, MonadAnnotater Label m) => f (HFixLab g) l -> m (HFixLab g l) Source #

type Project fs = Map FilePath (E (TermLab fs)) Source #

parseProject :: forall fs l. (All HFoldable fs, All HFunctor fs, All HTraversable fs) => LabelGen -> (FilePath -> IO (Maybe (Term fs l))) -> [FilePath] -> IO (Maybe (Project fs)) Source #

rewriteProjectM :: Applicative m => (forall l. TermLab fs l -> m (TermLab fs l)) -> Project fs -> m (Project fs) Source #

rewriteProjectWithFilM :: Applicative m => (forall l. FilePath -> TermLab fs l -> m (TermLab fs l)) -> Project fs -> m (Project fs) Source #

putProject :: (forall l. TermLab fs l -> String) -> Project fs -> IO () Source #