Safe Haskell | None |
---|---|
Language | Haskell2010 |
Definitions for fixity, precedence levels, and declared syntax.
Synopsis
- data ThingWithFixity x = ThingWithFixity x Fixity'
- data ParenPreference
- preferParen :: ParenPreference -> Bool
- preferParenless :: ParenPreference -> Bool
- data Precedence
- type PrecedenceStack = [Precedence]
- pushPrecedence :: Precedence -> PrecedenceStack -> PrecedenceStack
- headPrecedence :: PrecedenceStack -> Precedence
- argumentCtx_ :: Precedence
- opBrackets :: Fixity -> PrecedenceStack -> Bool
- opBrackets' :: Bool -> Fixity -> PrecedenceStack -> Bool
- lamBrackets :: PrecedenceStack -> Bool
- appBrackets :: PrecedenceStack -> Bool
- appBrackets' :: Bool -> PrecedenceStack -> Bool
- withAppBrackets :: PrecedenceStack -> Bool
- piBrackets :: PrecedenceStack -> Bool
- roundFixBrackets :: PrecedenceStack -> Bool
Documentation
data ThingWithFixity x Source #
Decorating something with Fixity'
.
Instances
data ParenPreference Source #
Do we prefer parens around arguments like λ x → x
or not?
See lamBrackets
.
Instances
preferParen :: ParenPreference -> Bool Source #
preferParenless :: ParenPreference -> Bool Source #
Precendence
data Precedence Source #
Precedence is associated with a context.
TopCtx | |
FunctionSpaceDomainCtx | |
LeftOperandCtx Fixity | |
RightOperandCtx Fixity ParenPreference | |
FunctionCtx | |
ArgumentCtx ParenPreference | |
InsideOperandCtx | |
WithFunCtx | |
WithArgCtx | |
DotPatternCtx |
Instances
Pretty Precedence Source # | |||||
Defined in Agda.Syntax.Fixity pretty :: Precedence -> Doc Source # prettyPrec :: Int -> Precedence -> Doc Source # prettyList :: [Precedence] -> Doc Source # | |||||
EmbPrj Precedence Source # | |||||
Defined in Agda.TypeChecking.Serialise.Instances.Abstract icode :: Precedence -> S Int32 Source # icod_ :: Precedence -> S Int32 Source # value :: Int32 -> R Precedence Source # | |||||
NFData Precedence Source # | |||||
Defined in Agda.Syntax.Fixity rnf :: Precedence -> () | |||||
Generic Precedence Source # | |||||
Defined in Agda.Syntax.Fixity
from :: Precedence -> Rep Precedence x to :: Rep Precedence x -> Precedence | |||||
Show Precedence Source # | |||||
Defined in Agda.Syntax.Fixity showsPrec :: Int -> Precedence -> ShowS show :: Precedence -> String showList :: [Precedence] -> ShowS | |||||
Eq Precedence Source # | |||||
Defined in Agda.Syntax.Fixity (==) :: Precedence -> Precedence -> Bool (/=) :: Precedence -> Precedence -> Bool | |||||
type Rep Precedence Source # | |||||
Defined in Agda.Syntax.Fixity type Rep Precedence = D1 ('MetaData "Precedence" "Agda.Syntax.Fixity" "Agda-2.6.20240714-inplace" 'False) (((C1 ('MetaCons "TopCtx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FunctionSpaceDomainCtx" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LeftOperandCtx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fixity)) :+: (C1 ('MetaCons "RightOperandCtx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fixity) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParenPreference)) :+: C1 ('MetaCons "FunctionCtx" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ArgumentCtx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParenPreference)) :+: C1 ('MetaCons "InsideOperandCtx" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WithFunCtx" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WithArgCtx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DotPatternCtx" 'PrefixI 'False) (U1 :: Type -> Type))))) |
type PrecedenceStack = [Precedence] Source #
When printing we keep track of a stack of precedences in order to be able
to decide whether it's safe to leave out parens around lambdas. An empty
stack is equivalent to TopCtx
. Invariant: `notElem TopCtx`.
argumentCtx_ :: Precedence Source #
Argument context preferring parens.
opBrackets :: Fixity -> PrecedenceStack -> Bool Source #
Do we need to bracket an operator application of the given fixity in a context with the given precedence.
opBrackets' :: Bool -> Fixity -> PrecedenceStack -> Bool Source #
Do we need to bracket an operator application of the given fixity in a context with the given precedence.
lamBrackets :: PrecedenceStack -> Bool Source #
Does a lambda-like thing (lambda, let or pi) need brackets in the
given context? A peculiar thing with lambdas is that they don't
need brackets in certain right operand contexts. To decide we need to look
at the stack of precedences and not just the current precedence.
Example: m₁ >>= (λ x → x) >>= m₂
(for _>>=_
left associative).
appBrackets :: PrecedenceStack -> Bool Source #
Does a function application need brackets?
appBrackets' :: Bool -> PrecedenceStack -> Bool Source #
Does a function application need brackets?
withAppBrackets :: PrecedenceStack -> Bool Source #
Does a with application need brackets?
piBrackets :: PrecedenceStack -> Bool Source #
Does a function space need brackets?
roundFixBrackets :: PrecedenceStack -> Bool Source #