haskell-src-exts-util-0.1.0: Helper functions for working with haskell-src-exts trees

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Exts.Util

Contents

Synopsis

Types annotated with source code locations

class Located a where Source #

Class of types containing source code locations

Minimal complete definition

location

Associated Types

type LocType a Source #

Methods

location :: forall f. Applicative f => (LocType a -> f (LocType a)) -> a -> f a Source #

Traversal providing access to the location details

Instances

Located a => Located [a] Source # 

Associated Types

type LocType [a] :: * Source #

Methods

location :: Applicative f => (LocType [a] -> f (LocType [a])) -> [a] -> f [a] Source #

Located a => Located (Maybe a) Source # 

Associated Types

type LocType (Maybe a) :: * Source #

Methods

location :: Applicative f => (LocType (Maybe a) -> f (LocType (Maybe a))) -> Maybe a -> f (Maybe a) Source #

(Located a, Ord a) => Located (Set a) Source # 

Associated Types

type LocType (Set a) :: * Source #

Methods

location :: Applicative f => (LocType (Set a) -> f (LocType (Set a))) -> Set a -> f (Set a) Source #

Located (Name s) Source # 

Associated Types

type LocType (Name s) :: * Source #

Methods

location :: Applicative f => (LocType (Name s) -> f (LocType (Name s))) -> Name s -> f (Name s) Source #

Located (QOp s) Source # 

Associated Types

type LocType (QOp s) :: * Source #

Methods

location :: Applicative f => (LocType (QOp s) -> f (LocType (QOp s))) -> QOp s -> f (QOp s) Source #

Located (Decl s) Source # 

Associated Types

type LocType (Decl s) :: * Source #

Methods

location :: Applicative f => (LocType (Decl s) -> f (LocType (Decl s))) -> Decl s -> f (Decl s) Source #

Located (Binds s) Source # 

Associated Types

type LocType (Binds s) :: * Source #

Methods

location :: Applicative f => (LocType (Binds s) -> f (LocType (Binds s))) -> Binds s -> f (Binds s) Source #

Located (IPBind s) Source # 

Associated Types

type LocType (IPBind s) :: * Source #

Methods

location :: Applicative f => (LocType (IPBind s) -> f (LocType (IPBind s))) -> IPBind s -> f (IPBind s) Source #

Located (Match s) Source # 

Associated Types

type LocType (Match s) :: * Source #

Methods

location :: Applicative f => (LocType (Match s) -> f (LocType (Match s))) -> Match s -> f (Match s) Source #

Located (Rhs s) Source # 

Associated Types

type LocType (Rhs s) :: * Source #

Methods

location :: Applicative f => (LocType (Rhs s) -> f (LocType (Rhs s))) -> Rhs s -> f (Rhs s) Source #

Located (GuardedRhs s) Source # 

Associated Types

type LocType (GuardedRhs s) :: * Source #

Methods

location :: Applicative f => (LocType (GuardedRhs s) -> f (LocType (GuardedRhs s))) -> GuardedRhs s -> f (GuardedRhs s) Source #

Located (Exp s) Source # 

Associated Types

type LocType (Exp s) :: * Source #

Methods

location :: Applicative f => (LocType (Exp s) -> f (LocType (Exp s))) -> Exp s -> f (Exp s) Source #

Located (Pat s) Source # 

Associated Types

type LocType (Pat s) :: * Source #

Methods

location :: Applicative f => (LocType (Pat s) -> f (LocType (Pat s))) -> Pat s -> f (Pat s) Source #

Located (Stmt s) Source # 

Associated Types

type LocType (Stmt s) :: * Source #

Methods

location :: Applicative f => (LocType (Stmt s) -> f (LocType (Stmt s))) -> Stmt s -> f (Stmt s) Source #

Located (QualStmt s) Source # 

Associated Types

type LocType (QualStmt s) :: * Source #

Methods

location :: Applicative f => (LocType (QualStmt s) -> f (LocType (QualStmt s))) -> QualStmt s -> f (QualStmt s) Source #

Located (Alt s) Source # 

Associated Types

type LocType (Alt s) :: * Source #

Methods

location :: Applicative f => (LocType (Alt s) -> f (LocType (Alt s))) -> Alt s -> f (Alt s) Source #

Ord s => Located (Vars s) Source # 

Associated Types

type LocType (Vars s) :: * Source #

Methods

location :: Applicative f => (LocType (Vars s) -> f (LocType (Vars s))) -> Vars s -> f (Vars s) Source #

(Located a, Located b, (~) * (LocType a) (LocType b)) => Located (a, b) Source # 

Associated Types

type LocType (a, b) :: * Source #

Methods

location :: Applicative f => (LocType (a, b) -> f (LocType (a, b))) -> (a, b) -> f (a, b) Source #

Free variables of ASTs

class Located a => FreeVars a where Source #

Minimal complete definition

freeVars

Methods

freeVars :: a -> Set (Name (LocType a)) Source #

Return the variables, erring on the side of more free variables

Instances

(Data s, Ord s) => FreeVars [IPBind s] Source # 

Methods

freeVars :: [IPBind s] -> Set (Name (LocType [IPBind s])) Source #

(Data s, Ord s) => FreeVars [Exp s] Source # 

Methods

freeVars :: [Exp s] -> Set (Name (LocType [Exp s])) Source #

(Data s, Ord s) => FreeVars [Alt s] Source # 

Methods

freeVars :: [Alt s] -> Set (Name (LocType [Alt s])) Source #

(Data s, Ord s) => FreeVars (Set (Name s)) Source # 

Methods

freeVars :: Set (Name s) -> Set (Name (LocType (Set (Name s)))) Source #

(Data s, Ord s) => FreeVars (IPBind s) Source # 

Methods

freeVars :: IPBind s -> Set (Name (LocType (IPBind s))) Source #

(Data s, Ord s) => FreeVars (Rhs s) Source # 

Methods

freeVars :: Rhs s -> Set (Name (LocType (Rhs s))) Source #

(Data s, Ord s) => FreeVars (GuardedRhs s) Source # 
(Data s, Ord s) => FreeVars (Exp s) Source # 

Methods

freeVars :: Exp s -> Set (Name (LocType (Exp s))) Source #

(Data s, Ord s) => FreeVars (Alt s) Source # 

Methods

freeVars :: Alt s -> Set (Name (LocType (Alt s))) Source #

data Vars s Source #

Constructors

Vars 

Fields

Instances

(Data s, Ord s) => Monoid (Vars s) Source # 

Methods

mempty :: Vars s #

mappend :: Vars s -> Vars s -> Vars s #

mconcat :: [Vars s] -> Vars s #

Ord s => Located (Vars s) Source # 

Associated Types

type LocType (Vars s) :: * Source #

Methods

location :: Applicative f => (LocType (Vars s) -> f (LocType (Vars s))) -> Vars s -> f (Vars s) Source #

(Data s, Ord s) => AllVars (Vars s) Source # 

Methods

allVars :: Vars s -> Vars (LocType (Vars s)) Source #

type LocType (Vars s) Source # 
type LocType (Vars s) = s

class Located a => AllVars a where Source #

Minimal complete definition

allVars

Methods

allVars :: a -> Vars (LocType a) Source #

Return the variables, erring on the side of more free variables

Instances

(Data s, Ord s) => AllVars [Decl s] Source # 

Methods

allVars :: [Decl s] -> Vars (LocType [Decl s]) Source #

(Data s, Ord s) => AllVars [Match s] Source # 

Methods

allVars :: [Match s] -> Vars (LocType [Match s]) Source #

(Data s, Ord s) => AllVars [Pat s] Source # 

Methods

allVars :: [Pat s] -> Vars (LocType [Pat s]) Source #

(Data s, Ord s) => AllVars [Stmt s] Source # 

Methods

allVars :: [Stmt s] -> Vars (LocType [Stmt s]) Source #

(Data s, Ord s) => AllVars [QualStmt s] Source # 

Methods

allVars :: [QualStmt s] -> Vars (LocType [QualStmt s]) Source #

(Data s, Ord s) => AllVars (Maybe (Binds s)) Source # 

Methods

allVars :: Maybe (Binds s) -> Vars (LocType (Maybe (Binds s))) Source #

(Data s, Ord s) => AllVars (Decl s) Source # 

Methods

allVars :: Decl s -> Vars (LocType (Decl s)) Source #

(Data s, Ord s) => AllVars (Binds s) Source # 

Methods

allVars :: Binds s -> Vars (LocType (Binds s)) Source #

(Data s, Ord s) => AllVars (Match s) Source # 

Methods

allVars :: Match s -> Vars (LocType (Match s)) Source #

(Data s, Ord s) => AllVars (Pat s) Source # 

Methods

allVars :: Pat s -> Vars (LocType (Pat s)) Source #

(Data s, Ord s) => AllVars (Stmt s) Source # 

Methods

allVars :: Stmt s -> Vars (LocType (Stmt s)) Source #

(Data s, Ord s) => AllVars (QualStmt s) Source # 
(Data s, Ord s) => AllVars (Vars s) Source # 

Methods

allVars :: Vars s -> Vars (LocType (Vars s)) Source #

Rebracketing of ASTs

class Brackets a where Source #

Minimal complete definition

remParen, addParen, isAtom, needBracket

Methods

remParen :: a -> Maybe a Source #

addParen :: a -> a Source #

isAtom :: a -> Bool Source #

Is this item lexically requiring no bracketing ever i.e. is totally atomic

needBracket :: Int -> a -> a -> Bool Source #

Is the child safe free from brackets in the parent position. Err on the side of caution, True = don't know

Instances

Default l => Brackets (Type l) Source # 

Methods

remParen :: Type l -> Maybe (Type l) Source #

addParen :: Type l -> Type l Source #

isAtom :: Type l -> Bool Source #

needBracket :: Int -> Type l -> Type l -> Bool Source #

(Data l, Default l) => Brackets (Exp l) Source # 

Methods

remParen :: Exp l -> Maybe (Exp l) Source #

addParen :: Exp l -> Exp l Source #

isAtom :: Exp l -> Bool Source #

needBracket :: Int -> Exp l -> Exp l -> Bool Source #

Default l => Brackets (Pat l) Source # 

Methods

remParen :: Pat l -> Maybe (Pat l) Source #

addParen :: Pat l -> Pat l Source #

isAtom :: Pat l -> Bool Source #

needBracket :: Int -> Pat l -> Pat l -> Bool Source #

paren :: (Data l, Default l) => Exp l -> Exp l Source #

Add a Paren around something if it is not atomic

transformBracket :: (Data l, Default l) => (Exp l -> Maybe (Exp l)) -> Exp l -> Exp l Source #

rebracket1 :: (Data l, Default l) => Exp l -> Exp l Source #

Add/remove brackets as suggested needBracket at 1-level of depth

appsBracket :: (Data l, Default l) => [Exp l] -> Exp l Source #