sifflet-lib-1.0: Library of modules shared by sifflet and its tests and its exporters.Source codeContentsIndex
Sifflet.Foreign.ToScheme
Synopsis
data SExpr
= SAtom Atom
| SList [SExpr]
data Atom
= SFloat Double
| SInt Integer
| SSymbol String
| SString String
| SChar Char
| SBool Bool
| SFunction Function
type Indent = Int
type Exporter = Functions -> FilePath -> IO ()
data SchemeOptions = SchemeOptions {
defineWithLambda :: Bool
}
defaultSchemeOptions :: SchemeOptions
exprToSExpr :: Expr -> SExpr
functionNameToSchemeName :: String -> String
valueToSExpr :: Value -> SExpr
exprToSchemeRepr :: Expr -> String
exprToSchemePretty :: Expr -> String
exprToScheme :: Expr -> String
inl :: Int -> String
sepLines2 :: [String] -> String
functionsToSExprs :: SchemeOptions -> Functions -> [SExpr]
functionsToPrettyScheme :: SchemeOptions -> Functions -> String
defToSExpr :: SchemeOptions -> FunctionDefTuple -> SExpr
exportScheme :: SchemeOptions -> Exporter
Documentation
data SExpr Source
Constructors
SAtom Atom
SList [SExpr]
show/hide Instances
data Atom Source
Constructors
SFloat Double
SInt Integer
SSymbol String
SString String
SChar Char
SBool Bool
SFunction Function
show/hide Instances
type Indent = IntSource
type Exporter = Functions -> FilePath -> IO ()Source
The type of a function to export (user) functions to a file.
data SchemeOptions Source
Constructors
SchemeOptions
defineWithLambda :: Booluse explicit lambda in function definitions, (define f (lambda (a b) ...)
show/hide Instances
defaultSchemeOptions :: SchemeOptionsSource
exprToSExpr :: Expr -> SExprSource
functionNameToSchemeName :: String -> StringSource
valueToSExpr :: Value -> SExprSource
exprToSchemeRepr :: Expr -> StringSource
exprToSchemePretty :: Expr -> StringSource
exprToScheme :: Expr -> StringSource
inl :: Int -> StringSource
Newline and indent
sepLines2 :: [String] -> StringSource
sepLines2 is like sepLines, but adds an extra n between each pair of lines so they are double spaced.
functionsToSExprs :: SchemeOptions -> Functions -> [SExpr]Source
Convert Sifflet Functions to Scheme SExprs
functionsToPrettyScheme :: SchemeOptions -> Functions -> StringSource
Convert Sifflet Functions to pretty Scheme
defToSExpr :: SchemeOptions -> FunctionDefTuple -> SExprSource
Convert a FunctionDefTuple to a Scheme SExpr. Use the form (define (name . args) body) except when there are zero arguments, which becomes a Scheme constant rather than a function, use (define name expr).
exportScheme :: SchemeOptions -> ExporterSource
Export functions to a Scheme file.
Produced by Haddock version 2.6.1