atto-lisp-0.2.2: Efficient parsing and serialisation of S-Expressions.

Safe HaskellNone
LanguageHaskell2010

Data.AttoLisp

Contents

Description

Efficient parsing and serialisation of S-Expressions (as used by Lisp).

This module is intended to be imported qualified, e.g.:

import qualified Data.AttoLisp as L

Synopsis

Core Lisp Types

data Lisp Source

A Lisp expression (S-expression).

Symbols are case-sensitive.

NOTE: The Number type is deprecated in "attoparsec", so a future version of "atto-lisp" will switch to the Scientific type from the "scientific" package.

Constructors

Symbol Text

A symbol (including keyword)

String Text

A string.

Number Number

A number

List [Lisp]

A proper list: (foo x 42)

DotList [Lisp] Lisp

A list with a non-nil tail: (foo x . 42). The list argument must be non-empty and the tail must be non-nil.

nil :: Lisp Source

The empty list.

isNull :: Lisp -> Bool Source

Returns True if the expression is nil or the empty list.

Type Conversion

class FromLisp a where Source

A type that can be converted from an S-expression, with the possibility of failure.

When writing an instance, use mzero or fail to make a conversion fail, e.g. the value is of the wrong type.

An example type and instance:

@data Coord { x :: Double, y :: Double }

instance FromLisp Coord where parseLisp (DotList [x] y) = pure (Coord x y) -- A non-DotList value is of the wrong shape, so use mzero to fail. parseLisp _ = mzero @

The above instance expects that Coord 4 5 is encoded as (4 . 5). This makes sense for a few special types, but most of the time the standard encoding should be used: (coord 4 5). The struct combinator provides special support for this use case:

instance FromLisp Coord where
   parseLisp = struct "coord" Coord

It uses some special type class magic to figure out the arity of its second argument.

Methods

parseLisp :: Lisp -> Parser a Source

data Result a Source

The result of running a Parser.

Constructors

Error String 
Success a 

type Failure f r = String -> f r Source

Failure continuation.

type Success a f r = a -> f r Source

Success continuation.

data Parser a Source

A continuation-based parser type.

parse :: (a -> Parser b) -> a -> Result b Source

Run a Parser.

parseMaybe :: (a -> Parser b) -> a -> Maybe b Source

Run a Parser with a Maybe result type.

parseEither :: (a -> Parser b) -> a -> Either String b Source

Run a Parser with an Either result type.

typeMismatch Source

Arguments

:: String

The name of the type you are trying to parse.

-> Lisp

The actual value encountered.

-> Parser a 

Fail parsing due to a type mismatch, with a descriptive message.

class ToLisp a where Source

A type that can be converted to an S-expression.

An example type and instance:

@data Coord { x :: Double, y :: Double }

instance ToLisp Coord where toLisp (Coord x y) = struct "coord" [toLisp x, toLisp y] @

Methods

toLisp :: a -> Lisp Source

Instances

ToLisp Bool 
ToLisp Char 
ToLisp Double 
ToLisp Float 
ToLisp Int 
ToLisp Int8 
ToLisp Int16 
ToLisp Int32 
ToLisp Int64 
ToLisp Integer 
ToLisp Word 
ToLisp Word8 
ToLisp Word16 
ToLisp Word32 
ToLisp Word64 
ToLisp () 
ToLisp Text 
ToLisp Number 
ToLisp Lisp 
ToLisp [Char] 
ToLisp a => ToLisp [a] 
ToLisp (Ratio Integer) 
ToLisp a => ToLisp (Maybe a) 
(ToLisp a, ToLisp b) => ToLisp (Either a b)

No tag is used, hence type a and b must be different.

(ToLisp a, ToLisp b) => ToLisp (a, b) 
(ToLisp a, ToLisp b) => ToLisp (Map a b) 
(ToLisp a, ToLisp b, ToLisp c) => ToLisp (a, b, c) 

Constructors and destructors

mkStruct :: Text -> [Lisp] -> Lisp Source

Create a Lisp struct in a standardised format.

Fields in a struct are accessed by position.

struct :: ParseList f a => Text -> f -> Lisp -> Parser a Source

Decode structure serialised with mkStruct.

The second argument should be a function, usually a constructor. The resulting parser automatically figures out the arity of the function. For example:

@data Foo = Foo Int deriving (Eq, Show)

parseFoo :: Lisp -> Parser Foo parseFoo = struct "foo" Foo

test = parseMaybe parseFoo val == Just (Foo 23) where val = List [Symbol "foo", Number 23] @

Encoding and parsing

lisp :: Parser Lisp Source

Parse an arbitrary lisp expression.

atom :: Parser Lisp Source

Parse a symbol or a number. Symbols are expected to be utf8.