sexpresso-1.2.1.0: A flexible library for parsing and printing S-expression
Copyright© 2019 Vincent Archambault
License0BSD
MaintainerVincent Archambault <archambault.v@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.SExpresso.Language.SchemeR5RS

Description

Module for parsing the Scheme R5RS language.

Scheme R5RS s-expressions are parsed as SExpr SExprType SchemeToken. Such s-expressions can be converted into a Scheme R5RS datum (see Datum) by the function sexpr2Datum.

Synopsis

SchemeToken and Datum related data types and functions

data SExprType Source #

Scheme R5RS defines two types of s-expressions. Standard list beginning with '(' and vector beginning with '#('. The SExprType data type indicates which one was parsed.

Constructors

STList

A standard list

STVector

A vector

Instances

Instances details
Eq SExprType Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Data SExprType Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SExprType -> c SExprType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SExprType #

toConstr :: SExprType -> Constr #

dataTypeOf :: SExprType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SExprType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SExprType) #

gmapT :: (forall b. Data b => b -> b) -> SExprType -> SExprType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SExprType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SExprType -> r #

gmapQ :: (forall d. Data d => d -> u) -> SExprType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SExprType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SExprType -> m SExprType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SExprType -> m SExprType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SExprType -> m SExprType #

Show SExprType Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

data SchemeToken Source #

The SchemeToken data type defines the atoms of an Scheme R5RS s-expression. An SExpr SExprType SchemeToken object containning the atoms TQuote, TQuasiquote, TComma, TCommaAt and TDot need futher processing in order to get what the R5RS report calls a datum. See also Datum.

Constructors

TBoolean Bool

A boolean.

TNumber SchemeNumber

A number. See SchemeNumber.

TChar Char

A unicode character.

TString Text

A string.

TIdentifier Text

A valid R5RS identifier.

TQuote

The quote (') symbol.

TQuasiquote

The quasiquote (`) symbol.

TComma

The comma (,) symbol.

TCommaAt

The comma at (,@) symbol.

TDot

The dot (.) symbol.

Instances

Instances details
Eq SchemeToken Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Data SchemeToken Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SchemeToken -> c SchemeToken #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SchemeToken #

toConstr :: SchemeToken -> Constr #

dataTypeOf :: SchemeToken -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SchemeToken) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SchemeToken) #

gmapT :: (forall b. Data b => b -> b) -> SchemeToken -> SchemeToken #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SchemeToken -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SchemeToken -> r #

gmapQ :: (forall d. Data d => d -> u) -> SchemeToken -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SchemeToken -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SchemeToken -> m SchemeToken #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemeToken -> m SchemeToken #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemeToken -> m SchemeToken #

Show SchemeToken Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

sexpr :: forall e s m. (MonadParsec e s m, Token s ~ Char) => SExprParser m SExprType SchemeToken Source #

The sexpr defines a SExprParser to parse a Scheme R5RS s-expression as an SExpr SExprType SchemeToken. If you also want source position see the withLocation function.

Space is optional before and after the following tokens:

data Datum Source #

The Datum data type implements the Scheme R5RS definition of a Datum. See also sexpr2Datum.

Instances

Instances details
Eq Datum Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

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

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

Data Datum Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Datum -> c Datum #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Datum #

toConstr :: Datum -> Constr #

dataTypeOf :: Datum -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Datum) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Datum) #

gmapT :: (forall b. Data b => b -> b) -> Datum -> Datum #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Datum -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Datum -> r #

gmapQ :: (forall d. Data d => d -> u) -> Datum -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Datum -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Datum -> m Datum #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Datum -> m Datum #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Datum -> m Datum #

Show Datum Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

showsPrec :: Int -> Datum -> ShowS #

show :: Datum -> String #

showList :: [Datum] -> ShowS #

sexpr2Datum :: [SExpr SExprType SchemeToken] -> Either String [Datum] Source #

The sexpr2Datum function takes a list of SchemeToken and returns a list of Datum. In case of failure it will report an error, hence the Either data type in the signature.

As defined in the Scheme R5RS report, the TQuote, TQuasiquote, TComma, TCommaAt and TDot tokens must be followed by another token.

Scheme R5RS whitespace parsers

whitespace :: (MonadParsec e s m, Token s ~ Char) => m () Source #

The whitespace parser parses one space, tab or end of line (\n and \r\n).

comment :: (MonadParsec e s m, Token s ~ Char) => m () Source #

The comment parser parses a semi-colon (;) character and everything until the end of line included.

interTokenSpace :: (MonadParsec e s m, Token s ~ Char) => m () Source #

The interTokenSpace parser parses zero or more whitespace or comment.

interTokenSpace1 :: (MonadParsec e s m, Token s ~ Char) => m () Source #

The interTokenSpace1 parser parses one or more whitespace or comment.

Individual parser for each of the constructors of SchemeToken

identifier :: forall e s m. (MonadParsec e s m, Token s ~ Char) => m Text Source #

The identifier parser parses a Scheme R5RS identifier.

boolean :: forall e s m. (MonadParsec e s m, Token s ~ Char) => m Bool Source #

The boolean parser parses a Scheme R5RS boolean (#t or #f).

character :: forall e s m. (MonadParsec e s m, Token s ~ Char) => m Char Source #

The character parser parses a Scheme R5RS character.

stringParser :: forall e s m. (MonadParsec e s m, Token s ~ Char) => m Text Source #

The stringParser parser parses a Scheme R5RS character.

quote :: (MonadParsec e s m, Token s ~ Char) => m Char Source #

The quote parser parses a quote character (').

quasiquote :: (MonadParsec e s m, Token s ~ Char) => m Char Source #

The quasiquote parser parses a quasiquote character (`).

comma :: (MonadParsec e s m, Token s ~ Char) => m Char Source #

The comma parser parses a comma (,).

commaAt :: forall e s m. (MonadParsec e s m, Token s ~ Char) => m Text Source #

The commaAt parser parses a comma followed by @ (,@).

dot :: (MonadParsec e s m, Token s ~ Char) => m Char Source #

The dot parser parses a single dot character (.).

Scheme Number

Scheme R5RS numbers are quite exotic. They can have exactness prefix, radix prefix and the pound sign (#) can replace a digit. On top of that, you can define integer, rational, decimal and complex numbers of arbitrary precision. Decimal numbers can also have a suffix indicating the machine precision.

Since Haskell does not have native types to express this complexity, this module defines the SchemeNumber data type to encode the parsed number. User of this module can then convert a SchemeNumber object to a more appropriate data type according to their needs.

data SchemeNumber Source #

A Scheme R5RS number is an exact or inexact complex number.

Instances

Instances details
Eq SchemeNumber Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Data SchemeNumber Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SchemeNumber -> c SchemeNumber #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SchemeNumber #

toConstr :: SchemeNumber -> Constr #

dataTypeOf :: SchemeNumber -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SchemeNumber) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SchemeNumber) #

gmapT :: (forall b. Data b => b -> b) -> SchemeNumber -> SchemeNumber #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SchemeNumber -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SchemeNumber -> r #

gmapQ :: (forall d. Data d => d -> u) -> SchemeNumber -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SchemeNumber -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SchemeNumber -> m SchemeNumber #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemeNumber -> m SchemeNumber #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SchemeNumber -> m SchemeNumber #

Show SchemeNumber Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

data Exactness Source #

A Scheme R5RS number is either exact or inexact. The paragraph 6.4.2 from the R5RS report should clarify the meaning of exact and inexact :

"""A numerical constant may be specified to be either exact or inexact by a prefix. The prefixes are #e for exact, and #i for inexact. An exactness prefix may appear before or after any radix prefix that is used. If the written representation of a number has no exactness prefix, the constant may be either inexact or exact. It is inexact if it contains a decimal point, an exponent, or a “#” character in the place of a digit, otherwise it is exact."""

Constructors

Exact 
Inexact 

Instances

Instances details
Eq Exactness Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Data Exactness Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exactness -> c Exactness #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exactness #

toConstr :: Exactness -> Constr #

dataTypeOf :: Exactness -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Exactness) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exactness) #

gmapT :: (forall b. Data b => b -> b) -> Exactness -> Exactness #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exactness -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exactness -> r #

gmapQ :: (forall d. Data d => d -> u) -> Exactness -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Exactness -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exactness -> m Exactness #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exactness -> m Exactness #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exactness -> m Exactness #

Show Exactness Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

data Complex Source #

The Complex data type represents a Scheme R5RS complex number.

Constructors

CReal SReal

A real number.

CAngle SReal SReal

A complex number in angular notation.

CAbsolute SReal SReal

A complex number in absolute notation.

Instances

Instances details
Eq Complex Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

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

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

Data Complex Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Complex -> c Complex #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Complex #

toConstr :: Complex -> Constr #

dataTypeOf :: Complex -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Complex) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Complex) #

gmapT :: (forall b. Data b => b -> b) -> Complex -> Complex #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Complex -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Complex -> r #

gmapQ :: (forall d. Data d => d -> u) -> Complex -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Complex -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Complex -> m Complex #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Complex -> m Complex #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Complex -> m Complex #

Show Complex Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

data SReal Source #

The SReal data type represents a Scheme R5RS real number.

Constructors

SInteger Sign UInteger

A signed integer.

SRational Sign UInteger UInteger

A signed rational. The first number is the numerator and the second one the denominator.

SDecimal Sign UInteger UInteger (Maybe Suffix)

A signed decimal number. The first number appears before the dot, the second one after the dot.

Instances

Instances details
Eq SReal Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

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

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

Data SReal Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SReal -> c SReal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SReal #

toConstr :: SReal -> Constr #

dataTypeOf :: SReal -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SReal) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SReal) #

gmapT :: (forall b. Data b => b -> b) -> SReal -> SReal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SReal -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SReal -> r #

gmapQ :: (forall d. Data d => d -> u) -> SReal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SReal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SReal -> m SReal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SReal -> m SReal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SReal -> m SReal #

Show SReal Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

showsPrec :: Int -> SReal -> ShowS #

show :: SReal -> String #

showList :: [SReal] -> ShowS #

data Sign Source #

The Sign datatype indicates if a number is positive (Plus) or negative (Minus)

Constructors

Plus 
Minus 

Instances

Instances details
Eq Sign Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

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

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

Data Sign Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sign -> c Sign #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sign #

toConstr :: Sign -> Constr #

dataTypeOf :: Sign -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Sign) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sign) #

gmapT :: (forall b. Data b => b -> b) -> Sign -> Sign #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r #

gmapQ :: (forall d. Data d => d -> u) -> Sign -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sign -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sign -> m Sign #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign #

Show Sign Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

data UInteger Source #

A Scheme R5RS unsigned integer can be written in three ways.

  • With digits only
  • With digits and # signs
  • With only # signs in some special context.

Constructors

UInteger Integer

Integer made only of digits

UIntPounds Integer Pounds

Integer made of digits and #. The first argument is the number that was parsed and the second the number of # signs. For example, 123## is represented as UIntPounds 123 2. Do not take the first argument as a good approximation of the number. It needs to be shifted by the number of pounds.

UPounds Pounds

Integer made only of #. It can only appear as the third argument in numbers of the form SDecimal _ _ _ _.

Instances

Instances details
Eq UInteger Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Data UInteger Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UInteger -> c UInteger #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UInteger #

toConstr :: UInteger -> Constr #

dataTypeOf :: UInteger -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UInteger) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UInteger) #

gmapT :: (forall b. Data b => b -> b) -> UInteger -> UInteger #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UInteger -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UInteger -> r #

gmapQ :: (forall d. Data d => d -> u) -> UInteger -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UInteger -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UInteger -> m UInteger #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UInteger -> m UInteger #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UInteger -> m UInteger #

Show UInteger Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

type Pounds = Integer Source #

A Scheme R5RS number can have many # signs at the end. This type alias indicates the number of # signs parsed.

data Precision Source #

Scheme R5RS defines 5 types of machine precision for a decimal number. The machine precision is specified in the suffix (see Suffix).

Constructors

PDefault

Suffix starting with e.

PShort

Suffix starting with s.

PSingle

Suffix starting with f.

PDouble

Suffix starting with d.

PLong

Suffix starting with l.

Instances

Instances details
Eq Precision Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Data Precision Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Precision -> c Precision #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Precision #

toConstr :: Precision -> Constr #

dataTypeOf :: Precision -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Precision) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Precision) #

gmapT :: (forall b. Data b => b -> b) -> Precision -> Precision #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Precision -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Precision -> r #

gmapQ :: (forall d. Data d => d -> u) -> Precision -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Precision -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Precision -> m Precision #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Precision -> m Precision #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Precision -> m Precision #

Show Precision Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

data Suffix Source #

The Suffix data type represents the suffix for a Scheme R5RS decimal number. It is a based 10 exponent.

Instances

Instances details
Eq Suffix Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

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

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

Data Suffix Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Suffix -> c Suffix #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Suffix #

toConstr :: Suffix -> Constr #

dataTypeOf :: Suffix -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Suffix) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Suffix) #

gmapT :: (forall b. Data b => b -> b) -> Suffix -> Suffix #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Suffix -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Suffix -> r #

gmapQ :: (forall d. Data d => d -> u) -> Suffix -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Suffix -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Suffix -> m Suffix #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Suffix -> m Suffix #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Suffix -> m Suffix #

Show Suffix Source # 
Instance details

Defined in Data.SExpresso.Language.SchemeR5RS

number :: (MonadParsec e s m, Token s ~ Char) => m SchemeNumber Source #

The number parser parses a Scheme R5RS number.