hinterface-0.10.0: Haskell / Erlang interoperability library

Safe HaskellNone
LanguageHaskell2010

Foreign.Erlang.Term

Contents

Synopsis

External Term Format

data Term Source #

Bundled Patterns

pattern Tuple2 :: Term -> Term -> Term 
pattern Tuple3 :: Term -> Term -> Term -> Term 
pattern Tuple4 :: Term -> Term -> Term -> Term -> Term 
pattern Tuple5 :: Term -> Term -> Term -> Term -> Term -> Term 
pattern Tuple6 :: Term -> Term -> Term -> Term -> Term -> Term -> Term 
pattern Tuple7 :: Term -> Term -> Term -> Term -> Term -> Term -> Term -> Term 
pattern List1 :: Term -> Term 
pattern List2 :: Term -> Term -> Term 
pattern List3 :: Term -> Term -> Term -> Term 
pattern List4 :: Term -> Term -> Term -> Term -> Term 
pattern List5 :: Term -> Term -> Term -> Term -> Term -> Term 
pattern List6 :: Term -> Term -> Term -> Term -> Term -> Term -> Term 
pattern List7 :: Term -> Term -> Term -> Term -> Term -> Term -> Term -> Term 
pattern Map1 :: MapEntry -> Term 
pattern Map2 :: MapEntry -> MapEntry -> Term 
pattern Map3 :: MapEntry -> MapEntry -> MapEntry -> Term 
pattern Map4 :: MapEntry -> MapEntry -> MapEntry -> MapEntry -> Term 
pattern Map5 :: MapEntry -> MapEntry -> MapEntry -> MapEntry -> MapEntry -> Term 
pattern Map6 :: MapEntry -> MapEntry -> MapEntry -> MapEntry -> MapEntry -> MapEntry -> Term 
pattern Map7 :: MapEntry -> MapEntry -> MapEntry -> MapEntry -> MapEntry -> MapEntry -> MapEntry -> Term 
Instances
IsList Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Associated Types

type Item Term :: Type #

Methods

fromList :: [Item Term] -> Term #

fromListN :: Int -> [Item Term] -> Term #

toList :: Term -> [Item Term] #

Eq Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

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

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

Num Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

(+) :: Term -> Term -> Term #

(-) :: Term -> Term -> Term #

(*) :: Term -> Term -> Term #

negate :: Term -> Term #

abs :: Term -> Term #

signum :: Term -> Term #

fromInteger :: Integer -> Term #

Ord Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

compare :: Term -> Term -> Ordering #

(<) :: Term -> Term -> Bool #

(<=) :: Term -> Term -> Bool #

(>) :: Term -> Term -> Bool #

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

max :: Term -> Term -> Term #

min :: Term -> Term -> Term #

Show Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

showsPrec :: Int -> Term -> ShowS #

show :: Term -> String #

showList :: [Term] -> ShowS #

IsString Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromString :: String -> Term #

Generic Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Associated Types

type Rep Term :: Type -> Type #

Methods

from :: Term -> Rep Term x #

to :: Rep Term x -> Term #

Arbitrary Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

arbitrary :: Gen Term #

shrink :: Term -> [Term] #

Binary Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

put :: Term -> Put #

get :: Get Term #

putList :: [Term] -> Put #

NFData Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

rnf :: Term -> () #

FromTerm Term Source # 
Instance details

Defined in Foreign.Erlang.Term

ToTerm Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: Term -> Term Source #

type Rep Term Source # 
Instance details

Defined in Foreign.Erlang.Term

type Rep Term = D1 (MetaData "Term" "Foreign.Erlang.Term" "hinterface-0.10.0-8ydraPFlj9T1BIVPX8pUtD" False) (((C1 (MetaCons "Integer" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Integer)) :+: (C1 (MetaCons "Float" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Double)) :+: C1 (MetaCons "Atom" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString)))) :+: (C1 (MetaCons "Reference" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word32) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word8))) :+: (C1 (MetaCons "Port" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word32) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word8))) :+: C1 (MetaCons "Pid" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word32)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word32) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word8)))))) :+: ((C1 (MetaCons "Tuple" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector Term))) :+: (C1 (MetaCons "Map" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector MapEntry))) :+: C1 (MetaCons "Nil" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "String" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString)) :+: C1 (MetaCons "List" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector Term)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Term))) :+: (C1 (MetaCons "Binary" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString)) :+: C1 (MetaCons "NewReference" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word8) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Word32])))))))
type Item Term Source # 
Instance details

Defined in Foreign.Erlang.Term

type Item Term = Term

putTerm :: ToTerm t => t -> Put Source #

data MapEntry Source #

Constructors

MapEntry 

Fields

Bundled Patterns

pattern (:=>) :: Term -> Term -> MapEntry 
Instances
Eq MapEntry Source # 
Instance details

Defined in Foreign.Erlang.Term

Ord MapEntry Source # 
Instance details

Defined in Foreign.Erlang.Term

Show MapEntry Source # 
Instance details

Defined in Foreign.Erlang.Term

Generic MapEntry Source # 
Instance details

Defined in Foreign.Erlang.Term

Associated Types

type Rep MapEntry :: Type -> Type #

Methods

from :: MapEntry -> Rep MapEntry x #

to :: Rep MapEntry x -> MapEntry #

Binary MapEntry Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

put :: MapEntry -> Put #

get :: Get MapEntry #

putList :: [MapEntry] -> Put #

NFData MapEntry Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

rnf :: MapEntry -> () #

type Rep MapEntry Source # 
Instance details

Defined in Foreign.Erlang.Term

type Rep MapEntry = D1 (MetaData "MapEntry" "Foreign.Erlang.Term" "hinterface-0.10.0-8ydraPFlj9T1BIVPX8pUtD" False) (C1 (MetaCons "MapEntry" PrefixI True) (S1 (MetaSel (Just "key") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Term) :*: S1 (MetaSel (Just "value") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Term)))

Conversion to and from External Term Format

class ToTerm a where Source #

Methods

toTerm :: a -> Term Source #

Instances
ToTerm Bool Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: Bool -> Term Source #

ToTerm Double Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: Double -> Term Source #

ToTerm Integer Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: Integer -> Term Source #

ToTerm () Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: () -> Term Source #

ToTerm String Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: String -> Term Source #

ToTerm Pid Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: Pid -> Term Source #

ToTerm Term Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: Term -> Term Source #

ToTerm a => ToTerm (Maybe a) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: Maybe a -> Term Source #

ToTerm a => ToTerm (NonEmpty a) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: NonEmpty a -> Term Source #

ToTerm a => ToTerm (Tuple1 a) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: Tuple1 a -> Term Source #

KnownSymbol atom => ToTerm (SAtom atom) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: SAtom atom -> Term Source #

KnownNat n => ToTerm (SInteger n) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: SInteger n -> Term Source #

(ToTerm a, ToTerm b) => ToTerm (Either a b) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: Either a b -> Term Source #

(ToTerm a, ToTerm b) => ToTerm (a, b) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: (a, b) -> Term Source #

(ToTerm a, ToTerm b, ToTerm c) => ToTerm (a, b, c) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: (a, b, c) -> Term Source #

(ToTerm a, ToTerm b, ToTerm c, ToTerm d) => ToTerm (a, b, c, d) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: (a, b, c, d) -> Term Source #

(ToTerm a, ToTerm b, ToTerm c, ToTerm d, ToTerm e) => ToTerm (a, b, c, d, e) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: (a, b, c, d, e) -> Term Source #

toTerms :: ToTerm a => [a] -> Term Source #

class FromTerm a where Source #

Methods

fromTerm :: Term -> Maybe a Source #

Instances
FromTerm Bool Source # 
Instance details

Defined in Foreign.Erlang.Term

FromTerm Double Source # 
Instance details

Defined in Foreign.Erlang.Term

FromTerm Integer Source # 
Instance details

Defined in Foreign.Erlang.Term

FromTerm () Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe () Source #

FromTerm String Source # 
Instance details

Defined in Foreign.Erlang.Term

FromTerm Pid Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe Pid Source #

FromTerm Term Source # 
Instance details

Defined in Foreign.Erlang.Term

FromTerm a => FromTerm (Maybe a) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (Maybe a) Source #

FromTerm a => FromTerm (NonEmpty a) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (NonEmpty a) Source #

FromTerm a => FromTerm (Tuple1 a) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (Tuple1 a) Source #

KnownSymbol atom => FromTerm (SAtom atom) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (SAtom atom) Source #

KnownNat n => FromTerm (SInteger n) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (SInteger n) Source #

(FromTerm a, FromTerm b) => FromTerm (Either a b) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (Either a b) Source #

(FromTerm a, FromTerm b) => FromTerm (a, b) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (a, b) Source #

(FromTerm a, FromTerm b, FromTerm c) => FromTerm (a, b, c) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (a, b, c) Source #

(FromTerm a, FromTerm b, FromTerm c, FromTerm d) => FromTerm (a, b, c, d) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (a, b, c, d) Source #

(FromTerm a, FromTerm b, FromTerm c, FromTerm d, FromTerm e) => FromTerm (a, b, c, d, e) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (a, b, c, d, e) Source #

Constructors

integer Source #

Arguments

:: Integer

Int

-> Term 

Construct an integer

Static numbers

data SInteger (n :: Nat) Source #

A static/constant number.

Constructors

SInteger 
Instances
KnownNat n => Show (SInteger n) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

showsPrec :: Int -> SInteger n -> ShowS #

show :: SInteger n -> String #

showList :: [SInteger n] -> ShowS #

KnownNat n => FromTerm (SInteger n) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (SInteger n) Source #

KnownNat n => ToTerm (SInteger n) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: SInteger n -> Term Source #

float Source #

Arguments

:: Double

IEEE float

-> Term 

Construct a float

atom Source #

Arguments

:: ByteString

AtomName

-> Term 

Construct an atom

Static atoms

data SAtom (atom :: Symbol) Source #

A static/constant atom.

Constructors

SAtom 
Instances
KnownSymbol atom => Show (SAtom atom) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

showsPrec :: Int -> SAtom atom -> ShowS #

show :: SAtom atom -> String #

showList :: [SAtom atom] -> ShowS #

KnownSymbol atom => FromTerm (SAtom atom) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (SAtom atom) Source #

KnownSymbol atom => ToTerm (SAtom atom) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: SAtom atom -> Term Source #

port Source #

Arguments

:: ByteString

Node name

-> Word32

ID

-> Word8

Creation

-> Term 

Construct a port

pid Source #

Arguments

:: ByteString

Node name

-> Word32

ID

-> Word32

Serial

-> Word8

Creation

-> Pid 

newtype Pid Source #

Constructors

MkPid Term 
Instances
Eq Pid Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

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

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

Ord Pid Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

compare :: Pid -> Pid -> Ordering #

(<) :: Pid -> Pid -> Bool #

(<=) :: Pid -> Pid -> Bool #

(>) :: Pid -> Pid -> Bool #

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

max :: Pid -> Pid -> Pid #

min :: Pid -> Pid -> Pid #

Show Pid Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

showsPrec :: Int -> Pid -> ShowS #

show :: Pid -> String #

showList :: [Pid] -> ShowS #

Arbitrary Pid Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

arbitrary :: Gen Pid #

shrink :: Pid -> [Pid] #

FromTerm Pid Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe Pid Source #

ToTerm Pid Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: Pid -> Term Source #

tuple Source #

Arguments

:: [Term]

Elements

-> Term 

Construct a tuple

newtype Tuple1 a Source #

Constructors

Tuple1 a 
Instances
Eq a => Eq (Tuple1 a) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

(==) :: Tuple1 a -> Tuple1 a -> Bool #

(/=) :: Tuple1 a -> Tuple1 a -> Bool #

Ord a => Ord (Tuple1 a) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

compare :: Tuple1 a -> Tuple1 a -> Ordering #

(<) :: Tuple1 a -> Tuple1 a -> Bool #

(<=) :: Tuple1 a -> Tuple1 a -> Bool #

(>) :: Tuple1 a -> Tuple1 a -> Bool #

(>=) :: Tuple1 a -> Tuple1 a -> Bool #

max :: Tuple1 a -> Tuple1 a -> Tuple1 a #

min :: Tuple1 a -> Tuple1 a -> Tuple1 a #

Show a => Show (Tuple1 a) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

showsPrec :: Int -> Tuple1 a -> ShowS #

show :: Tuple1 a -> String #

showList :: [Tuple1 a] -> ShowS #

FromTerm a => FromTerm (Tuple1 a) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

fromTerm :: Term -> Maybe (Tuple1 a) Source #

ToTerm a => ToTerm (Tuple1 a) Source # 
Instance details

Defined in Foreign.Erlang.Term

Methods

toTerm :: Tuple1 a -> Term Source #

string Source #

Arguments

:: ByteString

Characters

-> Term 

Construct a list

list Source #

Arguments

:: [Term]

Elements

-> Term 

Construct a list

improperList Source #

Arguments

:: [Term]

Elements

-> Term

Tail

-> Term 

Construct an improper list (if Tail is not Nil)

ref Source #

Arguments

:: ByteString

Node name

-> Word8

Creation

-> [Word32]

ID ...

-> Term 

Construct a new reference

Recognizers

is_integer :: Term -> Bool Source #

Test if term is an integer

is_float :: Term -> Bool Source #

Test if term is a float

is_atom :: Term -> Bool Source #

Test if term is an atom

is_reference :: Term -> Bool Source #

Test if term is a reference

is_port :: Term -> Bool Source #

Test if term is a port

is_pid :: Term -> Bool Source #

Test if term is a pid

is_tuple :: Term -> Bool Source #

Test if term is a tuple

is_map :: Term -> Bool Source #

Test if term is a map

is_list :: Term -> Bool Source #

Test if term is a list

is_binary :: Term -> Bool Source #

Test if term is a binary

Accessors

Matchers