haskell-tools-ast-0.2.0.0: Haskell AST for efficient tooling

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.AST.Stmts

Description

Representation of Haskell statements (both do-notation and comprehensions)

Synopsis

Documentation

data Stmt' expr dom stage Source #

Normal monadic statements

Constructors

BindStmt

Binding statement ( x <- action )

Fields

ExprStmt

Non-binding statement ( action )

Fields

LetStmt

Let statement ( let x = 3; y = 4 )

Fields

RecStmt

A recursive binding statement with ( rec b <- f a c; c <- f b a )

Fields

Instances

type Rep (Stmt' expr dom stage) Source # 
type Rep (Stmt' expr dom stage) = D1 (MetaData "Stmt'" "Language.Haskell.Tools.AST.Stmts" "haskell-tools-ast-0.2.0.0-5y5XIph7fmGIUhHQZ35OfD" False) ((:+:) ((:+:) (C1 (MetaCons "BindStmt" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_stmtPattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Pattern dom stage))) (S1 (MetaSel (Just Symbol "_stmtExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann expr dom stage))))) (C1 (MetaCons "ExprStmt" PrefixI True) (S1 (MetaSel (Just Symbol "_stmtExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann expr dom stage))))) ((:+:) (C1 (MetaCons "LetStmt" PrefixI True) (S1 (MetaSel (Just Symbol "_stmtBinds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnList LocalBind dom stage)))) (C1 (MetaCons "RecStmt" PrefixI True) (S1 (MetaSel (Just Symbol "_cmdStmtBinds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnList (Stmt' expr) dom stage))))))

data ListCompBody dom stage Source #

Body of a list comprehension: ( | x <- [1..10] )

Constructors

ListCompBody 

Fields

Instances

type Rep (ListCompBody dom stage) Source # 
type Rep (ListCompBody dom stage) = D1 (MetaData "ListCompBody" "Language.Haskell.Tools.AST.Stmts" "haskell-tools-ast-0.2.0.0-5y5XIph7fmGIUhHQZ35OfD" False) (C1 (MetaCons "ListCompBody" PrefixI True) (S1 (MetaSel (Just Symbol "_compStmts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnList CompStmt dom stage))))

data CompStmt dom stage Source #

List comprehension statement

Constructors

CompStmt

Normal monadic statement of a list comprehension

Fields

ThenStmt

Then statements by TransformListComp ( then sortWith by (x + y) )

Fields

GroupStmt

Grouping statements by TransformListComp ( then group by (x + y) using groupWith ) Note: either byExpr or usingExpr must have a value

Fields

Instances

type Rep (CompStmt dom stage) Source # 
type Rep (CompStmt dom stage) = D1 (MetaData "CompStmt" "Language.Haskell.Tools.AST.Stmts" "haskell-tools-ast-0.2.0.0-5y5XIph7fmGIUhHQZ35OfD" False) ((:+:) (C1 (MetaCons "CompStmt" PrefixI True) (S1 (MetaSel (Just Symbol "_compStmt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Stmt dom stage)))) ((:+:) (C1 (MetaCons "ThenStmt" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_thenExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Expr dom stage))) (S1 (MetaSel (Just Symbol "_byExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybe Expr dom stage))))) (C1 (MetaCons "GroupStmt" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_byExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybe Expr dom stage))) (S1 (MetaSel (Just Symbol "_usingExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybe Expr dom stage)))))))