| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Telescope.Data.Parser
Synopsis
- data Parser (a :: Type -> Type) b where
- runParser :: forall (es :: [Effect]) a. Error ParseError :> es => Eff (Parser ': es) a -> Eff es a
- runPureParser :: Eff '[Parser, Error ParseError] a -> Either ParseError a
- data ParseError = ParseFailure Path String
- newtype Path = Path [Ref]
- data Ref
- expected :: forall value (es :: [Effect]) a. (Show value, Parser :> es) => String -> value -> Eff es a
- parseFail :: forall (es :: [Effect]) a. Parser :> es => String -> Eff es a
- parseAt :: forall (es :: [Effect]) a. Parser :> es => Ref -> Eff es a -> Eff es a
Documentation
data Parser (a :: Type -> Type) b where Source #
Constructors
| ParseFail :: forall (a :: Type -> Type) b. String -> Parser a b | |
| PathAdd :: forall (a :: Type -> Type) b. Ref -> a b -> Parser a b |
Instances
| type DispatchOf Parser Source # | |
Defined in Telescope.Data.Parser | |
runParser :: forall (es :: [Effect]) a. Error ParseError :> es => Eff (Parser ': es) a -> Eff es a Source #
runPureParser :: Eff '[Parser, Error ParseError] a -> Either ParseError a Source #
data ParseError Source #
Constructors
| ParseFailure Path String |
Instances
| Exception ParseError Source # | |
Defined in Telescope.Data.Parser Methods toException :: ParseError -> SomeException # fromException :: SomeException -> Maybe ParseError # displayException :: ParseError -> String # | |
| Show ParseError Source # | |
Defined in Telescope.Data.Parser Methods showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # | |
| Eq ParseError Source # | |
Defined in Telescope.Data.Parser | |
Tracks the location of the parser in the document for error messages