diff options
author | Dan Frumin <difrumin@gmail.com> | 2013-08-29 20:14:02 +0000 |
---|---|---|
committer | Jan Stolarek <jan.stolarek@p.lodz.pl> | 2013-08-30 14:31:03 +0100 |
commit | 064e1010e2624b269cc64beecd32b205843e7cb2 (patch) | |
tree | 83f903a02ad16413e3822590ccfd95cef2670932 /compiler/hsSyn | |
parent | 25f1bda7cd854493404798c07a8b5ec99be0567f (diff) | |
download | haskell-064e1010e2624b269cc64beecd32b205843e7cb2.tar.gz |
Haddockify documentation in HsBinds and HsExpr
Fixes #8201
Diffstat (limited to 'compiler/hsSyn')
-rw-r--r-- | compiler/hsSyn/HsBinds.lhs | 127 | ||||
-rw-r--r-- | compiler/hsSyn/HsExpr.lhs | 60 |
2 files changed, 110 insertions, 77 deletions
diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index cb2538f574..db4c177b90 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -53,8 +53,9 @@ Global bindings (where clauses) type HsLocalBinds id = HsLocalBindsLR id id -data HsLocalBindsLR idL idR -- Bindings in a 'let' expression - -- or a 'where' clause +-- | Bindings in a 'let' expression +-- or a 'where' clause +data HsLocalBindsLR idL idR = HsValBinds (HsValBindsLR idL idR) | HsIPBinds (HsIPBinds idR) | EmptyLocalBinds @@ -62,15 +63,20 @@ data HsLocalBindsLR idL idR -- Bindings in a 'let' expression type HsValBinds id = HsValBindsLR id id -data HsValBindsLR idL idR -- Value bindings (not implicit parameters) - = ValBindsIn -- Before renaming RHS; idR is always RdrName - (LHsBindsLR idL idR) [LSig idR] -- Not dependency analysed - -- Recursive by default - - | ValBindsOut -- After renaming RHS; idR can be Name or Id - [(RecFlag, LHsBinds idL)] -- Dependency analysed, later bindings - -- in the list may depend on earlier - -- ones. +-- | Value bindings (not implicit parameters) +data HsValBindsLR idL idR + = -- | Before renaming RHS; idR is always RdrName + -- Not dependency analysed + -- Recursive by default + ValBindsIn + (LHsBindsLR idL idR) [LSig idR] + + -- | After renaming RHS; idR can be Name or Id + -- Dependency analysed, + -- later bindings in the list may depend on earlier + -- ones. + | ValBindsOut + [(RecFlag, LHsBinds idL)] [LSig Name] deriving (Data, Typeable) @@ -121,35 +127,38 @@ data HsBindLR idL idR fun_tick :: Maybe (Tickish Id) -- ^ Tick to put on the rhs, if any } - | PatBind { -- The pattern is never a simple variable; - -- That case is done by FunBind + -- | The pattern is never a simple variable; + -- That case is done by FunBind + | PatBind { pat_lhs :: LPat idL, pat_rhs :: GRHSs idR (LHsExpr idR), - pat_rhs_ty :: PostTcType, -- Type of the GRHSs - bind_fvs :: NameSet, -- See Note [Bind free vars] + pat_rhs_ty :: PostTcType, -- ^ Type of the GRHSs + bind_fvs :: NameSet, -- ^ See Note [Bind free vars] pat_ticks :: (Maybe (Tickish Id), [Maybe (Tickish Id)]) -- ^ Tick to put on the rhs, if any, and ticks to put on -- the bound variables. } - | VarBind { -- Dictionary binding and suchlike - var_id :: idL, -- All VarBinds are introduced by the type checker - var_rhs :: LHsExpr idR, -- Located only for consistency - var_inline :: Bool -- True <=> inline this binding regardless + -- | Dictionary binding and suchlike. + -- All VarBinds are introduced by the type checker + | VarBind { + var_id :: idL, + var_rhs :: LHsExpr idR, -- ^ Located only for consistency + var_inline :: Bool -- ^ True <=> inline this binding regardless -- (used for implication constraints only) } - | AbsBinds { -- Binds abstraction; TRANSLATION + | AbsBinds { -- Binds abstraction; TRANSLATION abs_tvs :: [TyVar], - abs_ev_vars :: [EvVar], -- Includes equality constraints + abs_ev_vars :: [EvVar], -- ^ Includes equality constraints - -- AbsBinds only gets used when idL = idR after renaming, + -- | AbsBinds only gets used when idL = idR after renaming, -- but these need to be idL's for the collect... code in HsUtil -- to have the right type abs_exports :: [ABExport idL], - abs_ev_binds :: TcEvBinds, -- Evidence bindings - abs_binds :: LHsBinds idL -- Typechecked user bindings + abs_ev_binds :: TcEvBinds, -- ^ Evidence bindings + abs_binds :: LHsBinds idL -- ^ Typechecked user bindings } deriving (Data, Typeable) @@ -166,15 +175,15 @@ data HsBindLR idL idR -- See Note [AbsBinds] data ABExport id - = ABE { abe_poly :: id -- Any INLINE pragmas is attached to this Id + = ABE { abe_poly :: id -- ^ Any INLINE pragmas is attached to this Id , abe_mono :: id - , abe_wrap :: HsWrapper -- See Note [AbsBinds wrappers] + , abe_wrap :: HsWrapper -- ^ See Note [AbsBinds wrappers] -- Shape: (forall abs_tvs. abs_ev_vars => abe_mono) ~ abe_poly - , abe_prags :: TcSpecPrags -- SPECIALISE pragmas + , abe_prags :: TcSpecPrags -- ^ SPECIALISE pragmas } deriving (Data, Typeable) +-- | Used for the NameSet in FunBind and PatBind prior to the renamer placeHolderNames :: NameSet --- Used for the NameSet in FunBind and PatBind prior to the renamer placeHolderNames = panic "placeHolderNames" \end{code} @@ -501,43 +510,55 @@ serves for both. \begin{code} type LSig name = Located (Sig name) -data Sig name -- Signatures and pragmas - = -- An ordinary type signature - -- f :: Num a => a -> a +-- | Signatures and pragmas +data Sig name + = -- | An ordinary type signature + -- @f :: Num a => a -> a@ TypeSig [Located name] (LHsType name) - -- A type signature for a default method inside a class - -- default eq :: (Representable0 a, GEq (Rep0 a)) => a -> a -> Bool + -- | A type signature for a default method inside a class + -- + -- > default eq :: (Representable0 a, GEq (Rep0 a)) => a -> a -> Bool + -- | GenericSig [Located name] (LHsType name) - -- A type signature in generated code, notably the code + -- | A type signature in generated code, notably the code -- generated for record selectors. We simply record -- the desired Id itself, replete with its name, type -- and IdDetails. Otherwise it's just like a type -- signature: there should be an accompanying binding | IdSig Id - -- An ordinary fixity declaration - -- infixl *** 8 + -- | An ordinary fixity declaration + -- + -- > infixl *** 8 + -- | FixSig (FixitySig name) - -- An inline pragma - -- {#- INLINE f #-} + -- | An inline pragma + -- + -- > {#- INLINE f #-} + -- | InlineSig (Located name) -- Function name InlinePragma -- Never defaultInlinePragma - -- A specialisation pragma - -- {-# SPECIALISE f :: Int -> Int #-} - | SpecSig (Located name) -- Specialise a function or datatype ... + -- | A specialisation pragma + -- + -- > {-# SPECIALISE f :: Int -> Int #-} + -- + | SpecSig (Located name) -- Specialise a function or datatype ... (LHsType name) -- ... to these types - InlinePragma -- The pragma on SPECIALISE_INLINE form + InlinePragma -- The pragma on SPECIALISE_INLINE form. -- If it's just defaultInlinePragma, then we said -- SPECIALISE, not SPECIALISE_INLINE - -- A specialisation pragma for instance declarations only - -- {-# SPECIALISE instance Eq [Int] #-} - | SpecInstSig (LHsType name) -- (Class tys); should be a specialisation of the - -- current instance decl + -- | A specialisation pragma for instance declarations only + -- + -- > {-# SPECIALISE instance Eq [Int] #-} + -- + -- (Class tys); should be a specialisation of the + -- current instance declaration + | SpecInstSig (LHsType name) deriving (Data, Typeable) @@ -545,9 +566,9 @@ type LFixitySig name = Located (FixitySig name) data FixitySig name = FixitySig (Located name) Fixity deriving (Data, Typeable) --- TsSpecPrags conveys pragmas from the type checker to the desugarer +-- | TsSpecPrags conveys pragmas from the type checker to the desugarer data TcSpecPrags - = IsDefaultMethod -- Super-specialised: a default method should + = IsDefaultMethod -- ^ Super-specialised: a default method should -- be macro-expanded at every call site | SpecPrags [LTcSpecPrag] deriving (Data, Typeable) @@ -556,9 +577,11 @@ type LTcSpecPrag = Located TcSpecPrag data TcSpecPrag = SpecPrag - Id -- The Id to be specialised - HsWrapper -- An wrapper, that specialises the polymorphic function - InlinePragma -- Inlining spec for the specialised function + Id + HsWrapper + InlinePragma + -- ^ The Id to be specialised, an wrapper that specialises the + -- polymorphic function, and inlining spec for the specialised function deriving (Data, Typeable) noSpecPrags :: TcSpecPrags @@ -572,9 +595,7 @@ isDefaultMethod :: TcSpecPrags -> Bool isDefaultMethod IsDefaultMethod = True isDefaultMethod (SpecPrags {}) = False -\end{code} -\begin{code} isFixityLSig :: LSig name -> Bool isFixityLSig (L _ (FixSig {})) = True isFixityLSig _ = False diff --git a/compiler/hsSyn/HsExpr.lhs b/compiler/hsSyn/HsExpr.lhs index ccbfc63a31..27286ca928 100644 --- a/compiler/hsSyn/HsExpr.lhs +++ b/compiler/hsSyn/HsExpr.lhs @@ -121,19 +121,19 @@ is Less Cool because \begin{code} -- | A Haskell expression. data HsExpr id - = HsVar id -- ^ variable - | HsIPVar HsIPName -- ^ implicit parameter + = HsVar id -- ^ Variable + | HsIPVar HsIPName -- ^ Implicit parameter | HsOverLit (HsOverLit id) -- ^ Overloaded literals | HsLit HsLit -- ^ Simple (non-overloaded) literals - | HsLam (MatchGroup id (LHsExpr id)) -- Currently always a single match + | HsLam (MatchGroup id (LHsExpr id)) -- ^ Lambda abstraction. Currently always a single match - | HsLamCase PostTcType (MatchGroup id (LHsExpr id)) -- Lambda-case + | HsLamCase PostTcType (MatchGroup id (LHsExpr id)) -- ^ Lambda-case - | HsApp (LHsExpr id) (LHsExpr id) -- Application + | HsApp (LHsExpr id) (LHsExpr id) -- ^ Application - -- Operator applications: + -- | Operator applications: -- NB Bracketed ops such as (+) come out as Vars. -- NB We need an expr for the operator in an OpApp/Section since @@ -144,17 +144,20 @@ data HsExpr id Fixity -- Renamer adds fixity; bottom until then (LHsExpr id) -- right operand - | NegApp (LHsExpr id) -- negated expr - (SyntaxExpr id) -- Name of 'negate' + -- | Negation operator. Contains the negated expression and the name + -- of 'negate' + | NegApp (LHsExpr id) + (SyntaxExpr id) - | HsPar (LHsExpr id) -- Parenthesised expr; see Note [Parens in HsSyn] + | HsPar (LHsExpr id) -- ^ Parenthesised expr; see Note [Parens in HsSyn] | SectionL (LHsExpr id) -- operand; see Note [Sections in HsSyn] (LHsExpr id) -- operator | SectionR (LHsExpr id) -- operator; see Note [Sections in HsSyn] (LHsExpr id) -- operand - | ExplicitTuple -- Used for explicit tuples and sections thereof + -- | Used for explicit tuples and sections thereof + | ExplicitTuple [HsTupArg id] Boxity @@ -168,9 +171,11 @@ data HsExpr id (LHsExpr id) -- then part (LHsExpr id) -- else part - | HsMultiIf PostTcType [LGRHS id (LHsExpr id)] -- Multi-way if + -- | Multi-way if + | HsMultiIf PostTcType [LGRHS id (LHsExpr id)] - | HsLet (HsLocalBinds id) -- let(rec) + -- | let(rec) + | HsLet (HsLocalBinds id) (LHsExpr id) | HsDo (HsStmtContext Name) -- The parameterisation is unimportant @@ -179,22 +184,24 @@ data HsExpr id [ExprLStmt id] -- "do":one or more stmts PostTcType -- Type of the whole expression - | ExplicitList -- syntactic list + -- | Syntactic list: [a,b,c,...] + | ExplicitList PostTcType -- Gives type of components of list (Maybe (SyntaxExpr id)) -- For OverloadedLists, the fromListN witness [LHsExpr id] - | ExplicitPArr -- syntactic parallel array: [:e1, ..., en:] + -- | Syntactic parallel array: [:e1, ..., en:] + | ExplicitPArr PostTcType -- type of elements of the parallel array [LHsExpr id] - -- Record construction + -- | Record construction | RecordCon (Located id) -- The constructor. After type checking -- it's the dataConWrapId of the constructor PostTcExpr -- Data con Id applied to type args (HsRecordBinds id) - -- Record update + -- | Record update | RecordUpd (LHsExpr id) (HsRecordBinds id) -- (HsMatchGroup Id) -- Filled in by the type checker to be @@ -207,7 +214,8 @@ data HsExpr id -- For a type family, the arg types are of the *instance* tycon, -- not the family tycon - | ExprWithTySig -- e :: type + -- | Expression with an explicit type signature. @e :: type@ + | ExprWithTySig (LHsExpr id) (LHsType id) @@ -216,12 +224,14 @@ data HsExpr id (LHsType Name) -- Retain the signature for -- round-tripping purposes - | ArithSeq -- Arithmetic sequence + -- | Arithmetic sequence + | ArithSeq PostTcExpr (Maybe (SyntaxExpr id)) -- For OverloadedLists, the fromList witness (ArithSeqInfo id) - | PArrSeq -- arith. sequence for parallel array + -- | Arithmetic sequence for parallel array + | PArrSeq PostTcExpr -- [:e1..e2:] or [:e1, e2..e3:] (ArithSeqInfo id) @@ -250,6 +260,7 @@ data HsExpr id ----------------------------------------------------------- -- Arrow notation extension + -- | @proc@ notation for Arrows | HsProc (LPat id) -- arrow abstraction, proc (LHsCmdTop id) -- body of the abstraction -- always has an empty stack @@ -315,20 +326,21 @@ data HsExpr id | HsUnboundVar RdrName deriving (Data, Typeable) --- HsTupArg is used for tuple sections +-- | HsTupArg is used for tuple sections -- (,a,) is represented by ExplicitTuple [Mising ty1, Present a, Missing ty3] -- Which in turn stands for (\x:ty1 \y:ty2. (x,a,y)) data HsTupArg id - = Present (LHsExpr id) -- The argument - | Missing PostTcType -- The argument is missing, but this is its type + = Present (LHsExpr id) -- ^ The argument + | Missing PostTcType -- ^ The argument is missing, but this is its type deriving (Data, Typeable) tupArgPresent :: HsTupArg id -> Bool tupArgPresent (Present {}) = True tupArgPresent (Missing {}) = False -type PendingSplice = (Name, LHsExpr Id) -- Typechecked splices, waiting to be - -- pasted back in by the desugarer +-- | Typechecked splices, waiting to be +-- pasted back in by the desugarer +type PendingSplice = (Name, LHsExpr Id) \end{code} |