telescope-0.2.0: Astronomical Observations (FITS, ASDF, WCS, etc)
Safe HaskellNone
LanguageGHC2021

Telescope.Data.Parser

Synopsis

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

Instances details
type DispatchOf Parser Source # 
Instance details

Defined in Telescope.Data.Parser

runParser :: forall (es :: [Effect]) a. Error ParseError :> es => Eff (Parser ': es) a -> Eff es a Source #

newtype Path Source #

Tracks the location of the parser in the document for error messages

Constructors

Path [Ref] 

Instances

Instances details
Monoid Path Source # 
Instance details

Defined in Telescope.Data.Parser

Methods

mempty :: Path #

mappend :: Path -> Path -> Path #

mconcat :: [Path] -> Path #

Semigroup Path Source # 
Instance details

Defined in Telescope.Data.Parser

Methods

(<>) :: Path -> Path -> Path #

sconcat :: NonEmpty Path -> Path #

stimes :: Integral b => b -> Path -> Path #

Show Path Source # 
Instance details

Defined in Telescope.Data.Parser

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Eq Path Source # 
Instance details

Defined in Telescope.Data.Parser

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

data Ref Source #

Constructors

Child Text 
Index Int 

Instances

Instances details
Show Ref Source # 
Instance details

Defined in Telescope.Data.Parser

Methods

showsPrec :: Int -> Ref -> ShowS #

show :: Ref -> String #

showList :: [Ref] -> ShowS #

Eq Ref Source # 
Instance details

Defined in Telescope.Data.Parser

Methods

(==) :: Ref -> Ref -> Bool #

(/=) :: Ref -> Ref -> Bool #

expected :: forall value (es :: [Effect]) a. (Show value, Parser :> es) => String -> value -> Eff es a Source #

Easy error message when we expect a particular type:

instance FromKeyword Int where
  parseKeywordValue = \case
    Integer n -> pure n
    v -> expected "Integer" v

parseFail :: forall (es :: [Effect]) a. Parser :> es => String -> Eff es a Source #

parseAt :: forall (es :: [Effect]) a. Parser :> es => Ref -> Eff es a -> Eff es a Source #

Add a child to the parsing Path