HsDeclStruct.hs

Plain Haskell source file: HsDeclStruct.hs

-- $Id: HsDeclStruct.hs,v 1.37 2001/10/13 00:02:56 hallgren Exp $

-------- Declarations ------------------------------------------------------

module HsDeclStruct where

import SrcLoc
import HsIdent
import HsGuardsStruct
import HsAssoc

-- D e      expression recursion type
--   p      pattern recursion type
--   ds     declaration recursion type
--   t      type recursion type
--   c      context recursion type
--   tp     type pattern recursion type
-- This type seems to be full of awkward inconsistencies... /TH
data DI i e p ds t c tp
    = HsTypeDecl    SrcLoc   [tp] t
    | HsNewTypeDecl SrcLoc c [tp] (HsConDeclI i t) {-deriving-} [i]
    | HsDataDecl    SrcLoc c [tp] [HsConDeclI i t] {-deriving-} [i]
    | HsClassDecl   SrcLoc c tp -- Why tp and not [tp]??
		    (HsFunDeps t) {-where-} ds
    | HsInstDecl    SrcLoc c tp   {-where-} ds
    | HsDefaultDecl SrcLoc t
    | HsTypeSig     SrcLoc [i] c tp -- Why tp and not t?? /TH
    | HsFunBind     SrcLoc [HsMatchI i e p ds]
    | HsPatBind     SrcLoc p (HsRhs e) {-where-} ds
    | HsInfixDecl   SrcLoc HsFixity [i] -- Haskell 98

    -- Hugs compatibility:
    | HsPrimitiveTypeDecl SrcLoc c i -- why not [tp] as for HsDataDecl??
    | HsPrimitiveBind     SrcLoc i t -- why not tp as for HsTypeSig??
      deriving (Eq, Show)

data HsMatchI i e p ds
    = HsMatch SrcLoc i [p] (HsRhs e) {-where-} ds   
      deriving (Eq, Show)
  
data HsConDeclI i t 
    = HsConDecl SrcLoc i [HsBangType t]
    | HsRecDecl SrcLoc i [([i], HsBangType t)]
      deriving (Eq, Show)   
   
data HsBangType t 
    = HsBangedType t
    | HsUnBangedType t
      deriving (Eq, Show)   

type HsFunDeps v = [HsFunDep v] -- ..., a b-> c d,f->g h, ->i, ...
type HsFunDep v = ([v],[v]) -- a b-> c d

Index