Safe Haskell | None |
---|---|
Language | Haskell2010 |
Agda.Syntax.Notation
Description
As a concrete name, a notation is a non-empty list of alternating IdPart
s and holes.
In contrast to concrete names, holes can be binders.
Example:
syntax fmap (λ x → e) xs = for x ∈ xs return e
The declared notation for fmap
is for_∈_return_
where the first hole is a binder.
Synopsis
- data HoleName
- = LambdaHole { }
- | ExprHole { }
- isLambdaHole :: HoleName -> Bool
- type Notation = [GenPart]
- data GenPart
- stringParts :: Notation -> [String]
- holeTarget :: GenPart -> Maybe Int
- isAHole :: GenPart -> Bool
- isNormalHole :: GenPart -> Bool
- isBindingHole :: GenPart -> Bool
- data NotationKind
- notationKind :: Notation -> NotationKind
- mkNotation :: [NamedArg HoleName] -> [RString] -> Either String Notation
- noNotation :: Notation
Documentation
Data type constructed in the Happy parser; converted to GenPart
before it leaves the Happy code.
Constructors
LambdaHole |
|
Fields
| |
ExprHole | Simple named hole with hiding. |
isLambdaHole :: HoleName -> Bool Source #
Is the hole a binder?
Part of a Notation
Constructors
BindHole Range (Ranged Int) | Argument is the position of the hole (with binding) where the binding should occur. First range is the rhs range and second is the binder. |
NormalHole Range (NamedArg (Ranged Int)) | Argument is where the expression should go. |
WildHole (Ranged Int) | An underscore in binding position. |
IdPart RString |
Instances
Eq GenPart Source # | |
Data GenPart Source # | |
Defined in Agda.Syntax.Notation Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenPart -> c GenPart # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GenPart # toConstr :: GenPart -> Constr # dataTypeOf :: GenPart -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GenPart) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GenPart) # gmapT :: (forall b. Data b => b -> b) -> GenPart -> GenPart # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenPart -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenPart -> r # gmapQ :: (forall d. Data d => d -> u) -> GenPart -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GenPart -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenPart -> m GenPart # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenPart -> m GenPart # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenPart -> m GenPart # | |
Ord GenPart Source # | |
Defined in Agda.Syntax.Notation | |
Show GenPart Source # | |
NFData GenPart Source # | |
Defined in Agda.Syntax.Notation | |
Pretty GenPart Source # | |
KillRange GenPart Source # | |
Defined in Agda.Syntax.Notation Methods | |
SetRange GenPart Source # | |
HasRange GenPart Source # | |
EmbPrj GenPart Source # | |
stringParts :: Notation -> [String] Source #
Get a flat list of identifier parts of a notation.
holeTarget :: GenPart -> Maybe Int Source #
Target argument position of a part (Nothing if it is not a hole).
isAHole :: GenPart -> Bool Source #
Is the part a hole? WildHoles don't count since they don't correspond to anything the user writes.
isNormalHole :: GenPart -> Bool Source #
Is the part a normal hole?
isBindingHole :: GenPart -> Bool Source #
Is the part a binder?
data NotationKind Source #
Classification of notations.
Constructors
InfixNotation | Ex: |
PrefixNotation | Ex: |
PostfixNotation | Ex: |
NonfixNotation | Ex: |
NoNotation |
Instances
Eq NotationKind Source # | |
Defined in Agda.Syntax.Notation | |
Show NotationKind Source # | |
Defined in Agda.Syntax.Notation Methods showsPrec :: Int -> NotationKind -> ShowS # show :: NotationKind -> String # showList :: [NotationKind] -> ShowS # |
notationKind :: Notation -> NotationKind Source #
Classify a notation by presence of leading and/or trailing normal holes.
mkNotation :: [NamedArg HoleName] -> [RString] -> Either String Notation Source #
From notation with names to notation with indices.
Example:
ids = ["for", "x", "∈", "xs", "return", "e"]
holes = [ LambdaHole "x" "e", ExprHole "xs" ]
creates the notation
[ IdPart "for" , BindHole 0
, IdPart "∈" , NormalHole 1
, IdPart "return" , NormalHole 0
]