| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Parsley.Internal.Core.CombinatorAST
Synopsis
- data MetaCombinator where
- newtype Reg (r :: Type) a = Reg (ΣVar a)
- data PosSelector where- Line :: PosSelector
- Col :: PosSelector
 
- data ScopeRegister (k :: Type -> Type) (a :: Type) where- ScopeRegister :: k a -> (forall r. Reg r a -> k b) -> ScopeRegister k b
 
- data Combinator (k :: Type -> Type) (a :: Type) where- Pure :: Defunc a -> Combinator k a
- Satisfy :: CharPred -> Combinator k Char
- (:<*>:) :: k (a -> b) -> k a -> Combinator k b
- (:*>:) :: k a -> k b -> Combinator k b
- (:<*:) :: k a -> k b -> Combinator k a
- (:<|>:) :: k a -> k a -> Combinator k a
- Empty :: Combinator k a
- Try :: k a -> Combinator k a
- LookAhead :: k a -> Combinator k a
- Let :: Bool -> MVar a -> Combinator k a
- NotFollowedBy :: k a -> Combinator k ()
- Branch :: k (Either a b) -> k (a -> c) -> k (b -> c) -> Combinator k c
- Match :: k a -> [Defunc (a -> Bool)] -> [k b] -> k b -> Combinator k b
- Loop :: k () -> k a -> Combinator k a
- MakeRegister :: ΣVar a -> k a -> k b -> Combinator k b
- GetRegister :: ΣVar a -> Combinator k a
- PutRegister :: ΣVar a -> k a -> Combinator k ()
- Position :: PosSelector -> Combinator k Int
- Debug :: String -> k a -> Combinator k a
- MetaCombinator :: MetaCombinator -> k a -> Combinator k a
 
- newtype Parser a = Parser {- unParser :: Fix (Combinator :+: ScopeRegister) a
 
- traverseCombinator :: Applicative m => (forall a. f a -> m (k a)) -> Combinator f a -> m (Combinator k a)
Documentation
data MetaCombinator where Source #
Constructors
| Cut :: MetaCombinator | After this combinator exits, a cut has happened | 
| RequiresCut :: MetaCombinator | This combinator requires a cut from below to respect parsec semantics | 
| CutImmune :: MetaCombinator | This combinator denotes that within its scope, cut semantics are not enforced Since: 1.6.0.0 | 
Instances
| Show MetaCombinator Source # | |
| Defined in Parsley.Internal.Core.CombinatorAST Methods showsPrec :: Int -> MetaCombinator -> ShowS # show :: MetaCombinator -> String # showList :: [MetaCombinator] -> ShowS # | |
newtype Reg (r :: Type) a Source #
This is an opaque representation of a parsing register. It cannot be manipulated as a user, and the
type parameter r is used to ensure that it cannot leak out of the scope it has been created in.
It is the abstracted representation of a runtime storage location.
Since: 0.1.0.0
data PosSelector where Source #
Constructors
| Line :: PosSelector | |
| Col :: PosSelector | 
data ScopeRegister (k :: Type -> Type) (a :: Type) where Source #
Constructors
| ScopeRegister :: k a -> (forall r. Reg r a -> k b) -> ScopeRegister k b | 
Instances
| IFunctor ScopeRegister Source # | |
| Defined in Parsley.Internal.Core.CombinatorAST Methods imap :: (forall j. a j -> b j) -> ScopeRegister a i -> ScopeRegister b i Source # | |
data Combinator (k :: Type -> Type) (a :: Type) where Source #
Constructors
| Pure :: Defunc a -> Combinator k a | |
| Satisfy :: CharPred -> Combinator k Char | |
| (:<*>:) :: k (a -> b) -> k a -> Combinator k b | |
| (:*>:) :: k a -> k b -> Combinator k b | |
| (:<*:) :: k a -> k b -> Combinator k a | |
| (:<|>:) :: k a -> k a -> Combinator k a | |
| Empty :: Combinator k a | |
| Try :: k a -> Combinator k a | |
| LookAhead :: k a -> Combinator k a | |
| Let :: Bool -> MVar a -> Combinator k a | |
| NotFollowedBy :: k a -> Combinator k () | |
| Branch :: k (Either a b) -> k (a -> c) -> k (b -> c) -> Combinator k c | |
| Match :: k a -> [Defunc (a -> Bool)] -> [k b] -> k b -> Combinator k b | |
| Loop :: k () -> k a -> Combinator k a | |
| MakeRegister :: ΣVar a -> k a -> k b -> Combinator k b | |
| GetRegister :: ΣVar a -> Combinator k a | |
| PutRegister :: ΣVar a -> k a -> Combinator k () | |
| Position :: PosSelector -> Combinator k Int | |
| Debug :: String -> k a -> Combinator k a | |
| MetaCombinator :: MetaCombinator -> k a -> Combinator k a | 
Instances
| IFunctor Combinator Source # | |
| Defined in Parsley.Internal.Core.CombinatorAST Methods imap :: (forall j. a j -> b j) -> Combinator a i -> Combinator b i Source # | |
| Show (Fix Combinator a) Source # | |
| Defined in Parsley.Internal.Core.CombinatorAST | |
The opaque datatype that represents parsers.
Since: 0.1.0.0
Constructors
| Parser | |
| Fields 
 | |
traverseCombinator :: Applicative m => (forall a. f a -> m (k a)) -> Combinator f a -> m (Combinator k a) Source #