HsExpStruct.hs

Plain Haskell source file: HsExpStruct.hs

-- $Id: HsExpStruct.hs,v 1.31 2001/10/08 20:23:43 hallgren Exp $

module HsExpStruct where

import SrcLoc
import HsIdent
import HsLiteral
import HsGuardsStruct
import HsAssoc
--import HsModule


-------- Expressions --------------------------------------------------------

data EI i e p ds t c
    = HsId (HsIdentI i) -- collapsing HsVar and HsCon
    | HsLit HsLiteral
    | HsInfixApp e (HsIdentI i) e
    | HsApp e e
    | HsNegApp e
    | HsLambda [p] e
    | HsLet ds e
    | HsIf e e e
    | HsCase e [HsAlt e p ds]
    | HsDo (HsStmt e p ds)
    | HsTuple [e]
    | HsList [e]
    | HsParen e
    | HsLeftSection e (HsIdentI i)
    | HsRightSection (HsIdentI i) e
    | HsRecConstr i [HsFieldUpdateI i e] -- qcon { fbind1, ..., fbindn }
    | HsRecUpdate e [HsFieldUpdateI i e] -- exp_<qcon> { fbind1, ..., fbindn }
    | HsEnumFrom e
    | HsEnumFromTo e e
    | HsEnumFromThen e e
    | HsEnumFromThenTo e  e e
    | HsListComp (HsStmt e p ds)
    | HsExpTypeSig SrcLoc e c t
    | HsAsPat i e   -- pattern only
    | HsWildCard         -- ditto
    | HsIrrPat e         -- ditto
      deriving (Eq, Show)

data HsStmt e p ds
    = HsGenerator p e (HsStmt e p ds)
    | HsQualifier e (HsStmt e p ds)
    | HsLetStmt ds (HsStmt e p ds)
    | HsLast e
      deriving (Eq, Show) 

data HsStmtAtom e p ds
    = HsGeneratorAtom p e
    | HsQualifierAtom e
    | HsLetStmtAtom ds
    | HsLastAtom e
      deriving (Eq, Show) 
		   
data HsFieldUpdateI i e 
    = HsFieldBind i       -- This doesn't seem to match anything in the
                               -- Report; selection is represented by
			       --     qvar exp_<qcon>
			       -- where qcon has a field named qvar.
    | HsFieldUpdate i e   -- qvar = exp
      deriving (Eq, Show)

Index