koneko-0.0.2: a concatenative not-quite-lisp for kittens
Safe HaskellNone
LanguageHaskell2010

Koneko.Data

Description

>>> :set -XOverloadedStrings
>>> import Data.Maybe
>>> id = fromJust . ident; q = KQuot . id
>>> nil
nil
>>> false
#f
>>> true
#t
>>> int 42
42
>>> float (-1.23)
-1.23
>>> str "I like 猫s"
"I like 猫s"
>>> kwd "foo"
:foo
>>> pair (Kwd "answer") $ int 42
:answer 42 =>
>>> list [int 42, kwd "foo"]
( 42 :foo )
>>> KIdent $ id "foo"
foo
>>> q "foo"
'foo
>>> block [id "x", id "y"] [q "y", q "x"] Nothing
[ x y . 'y 'x ]

... TODO ...

Synopsis

Documentation

type Module = ModuleLookupTable Source #

data KException Source #

Instances

Instances details
Data KException Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

toConstr :: KException -> Constr #

dataTypeOf :: KException -> DataType #

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

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

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

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

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

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

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

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

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

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

Show KException Source # 
Instance details

Defined in Koneko.Data

Exception KException Source # 
Instance details

Defined in Koneko.Data

newtype Kwd Source #

Constructors

Kwd 

Fields

Instances

Instances details
Eq Kwd Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord Kwd Source # 
Instance details

Defined in Koneko.Data

Methods

compare :: Kwd -> Kwd -> Ordering #

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

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

(>) :: Kwd -> Kwd -> Bool #

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

max :: Kwd -> Kwd -> Kwd #

min :: Kwd -> Kwd -> Kwd #

Show Kwd Source # 
Instance details

Defined in Koneko.Data

Methods

showsPrec :: Int -> Kwd -> ShowS #

show :: Kwd -> String #

showList :: [Kwd] -> ShowS #

Generic Kwd Source # 
Instance details

Defined in Koneko.Data

Associated Types

type Rep Kwd :: Type -> Type #

Methods

from :: Kwd -> Rep Kwd x #

to :: Rep Kwd x -> Kwd #

NFData Kwd Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: Kwd -> () #

FromVal Kwd Source # 
Instance details

Defined in Koneko.Data

ToVal Kwd Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Kwd -> KValue Source #

type Rep Kwd Source # 
Instance details

Defined in Koneko.Data

type Rep Kwd = D1 ('MetaData "Kwd" "Koneko.Data" "koneko-0.0.2-83yCJUTvCgkNrPx5HFN9s" 'True) (C1 ('MetaCons "Kwd" 'PrefixI 'True) (S1 ('MetaSel ('Just "unKwd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Identifier)))

data Ident Source #

Instances

Instances details
Eq Ident Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord Ident Source # 
Instance details

Defined in Koneko.Data

Methods

compare :: Ident -> Ident -> Ordering #

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

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

(>) :: Ident -> Ident -> Bool #

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

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Show Ident Source # 
Instance details

Defined in Koneko.Data

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Generic Ident Source # 
Instance details

Defined in Koneko.Data

Associated Types

type Rep Ident :: Type -> Type #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

NFData Ident Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: Ident -> () #

type Rep Ident Source # 
Instance details

Defined in Koneko.Data

type Rep Ident = D1 ('MetaData "Ident" "Koneko.Data" "koneko-0.0.2-83yCJUTvCgkNrPx5HFN9s" 'True) (C1 ('MetaCons "Ident_" 'PrefixI 'True) (S1 ('MetaSel ('Just "unIdent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Identifier)))

data Pair Source #

Constructors

Pair 

Fields

Instances

Instances details
Eq Pair Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord Pair Source # 
Instance details

Defined in Koneko.Data

Methods

compare :: Pair -> Pair -> Ordering #

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

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

(>) :: Pair -> Pair -> Bool #

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

max :: Pair -> Pair -> Pair #

min :: Pair -> Pair -> Pair #

Show Pair Source # 
Instance details

Defined in Koneko.Data

Methods

showsPrec :: Int -> Pair -> ShowS #

show :: Pair -> String #

showList :: [Pair] -> ShowS #

Generic Pair Source # 
Instance details

Defined in Koneko.Data

Associated Types

type Rep Pair :: Type -> Type #

Methods

from :: Pair -> Rep Pair x #

to :: Rep Pair x -> Pair #

NFData Pair Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: Pair -> () #

FromVal Pair Source # 
Instance details

Defined in Koneko.Data

ToVal Pair Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Pair -> KValue Source #

ToVal [Pair] Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: [Pair] -> KValue Source #

type Rep Pair Source # 
Instance details

Defined in Koneko.Data

type Rep Pair = D1 ('MetaData "Pair" "Koneko.Data" "koneko-0.0.2-83yCJUTvCgkNrPx5HFN9s" 'False) (C1 ('MetaCons "Pair" 'PrefixI 'True) (S1 ('MetaSel ('Just "key") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kwd) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KValue)))

newtype List Source #

Constructors

List 

Fields

Instances

Instances details
Eq List Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord List Source # 
Instance details

Defined in Koneko.Data

Methods

compare :: List -> List -> Ordering #

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

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

(>) :: List -> List -> Bool #

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

max :: List -> List -> List #

min :: List -> List -> List #

Show List Source # 
Instance details

Defined in Koneko.Data

Methods

showsPrec :: Int -> List -> ShowS #

show :: List -> String #

showList :: [List] -> ShowS #

Generic List Source # 
Instance details

Defined in Koneko.Data

Associated Types

type Rep List :: Type -> Type #

Methods

from :: List -> Rep List x #

to :: Rep List x -> List #

NFData List Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: List -> () #

type Rep List Source # 
Instance details

Defined in Koneko.Data

type Rep List = D1 ('MetaData "List" "Koneko.Data" "koneko-0.0.2-83yCJUTvCgkNrPx5HFN9s" 'True) (C1 ('MetaCons "List" 'PrefixI 'True) (S1 ('MetaSel ('Just "unList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [KValue])))

newtype Dict Source #

Constructors

Dict 

Fields

Instances

Instances details
Eq Dict Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord Dict Source # 
Instance details

Defined in Koneko.Data

Methods

compare :: Dict -> Dict -> Ordering #

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

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

(>) :: Dict -> Dict -> Bool #

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

max :: Dict -> Dict -> Dict #

min :: Dict -> Dict -> Dict #

Show Dict Source # 
Instance details

Defined in Koneko.Data

Methods

showsPrec :: Int -> Dict -> ShowS #

show :: Dict -> String #

showList :: [Dict] -> ShowS #

Generic Dict Source # 
Instance details

Defined in Koneko.Data

Associated Types

type Rep Dict :: Type -> Type #

Methods

from :: Dict -> Rep Dict x #

to :: Rep Dict x -> Dict #

NFData Dict Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: Dict -> () #

FromVal Dict Source # 
Instance details

Defined in Koneko.Data

ToVal Dict Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Dict -> KValue Source #

type Rep Dict Source # 
Instance details

Defined in Koneko.Data

type Rep Dict

data Block Source #

Constructors

Block 

Instances

Instances details
Eq Block Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord Block Source # 
Instance details

Defined in Koneko.Data

Methods

compare :: Block -> Block -> Ordering #

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

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

(>) :: Block -> Block -> Bool #

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

max :: Block -> Block -> Block #

min :: Block -> Block -> Block #

Show Block Source # 
Instance details

Defined in Koneko.Data

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Generic Block Source # 
Instance details

Defined in Koneko.Data

Associated Types

type Rep Block :: Type -> Type #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

NFData Block Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: Block -> () #

FromVal Block Source # 
Instance details

Defined in Koneko.Data

ToVal Block Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Block -> KValue Source #

type Rep Block Source # 
Instance details

Defined in Koneko.Data

type Rep Block = D1 ('MetaData "Block" "Koneko.Data" "koneko-0.0.2-83yCJUTvCgkNrPx5HFN9s" 'False) (C1 ('MetaCons "Block" 'PrefixI 'True) (S1 ('MetaSel ('Just "blkParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Ident]) :*: (S1 ('MetaSel ('Just "blkCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [KValue]) :*: S1 ('MetaSel ('Just "blkScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Scope)))))

data Builtin Source #

Constructors

Builtin 

Instances

Instances details
Eq Builtin Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord Builtin Source # 
Instance details

Defined in Koneko.Data

Show Builtin Source # 
Instance details

Defined in Koneko.Data

NFData Builtin Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: Builtin -> () #

ToVal Builtin Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Builtin -> KValue Source #

data Multi Source #

Constructors

Multi 

Fields

Instances

Instances details
Eq Multi Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord Multi Source # 
Instance details

Defined in Koneko.Data

Methods

compare :: Multi -> Multi -> Ordering #

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

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

(>) :: Multi -> Multi -> Bool #

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

max :: Multi -> Multi -> Multi #

min :: Multi -> Multi -> Multi #

Show Multi Source # 
Instance details

Defined in Koneko.Data

Methods

showsPrec :: Int -> Multi -> ShowS #

show :: Multi -> String #

showList :: [Multi] -> ShowS #

NFData Multi Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: Multi -> () #

data RecordT Source #

Constructors

RecordT 

Instances

Instances details
Eq RecordT Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord RecordT Source # 
Instance details

Defined in Koneko.Data

Show RecordT Source # 
Instance details

Defined in Koneko.Data

Generic RecordT Source # 
Instance details

Defined in Koneko.Data

Associated Types

type Rep RecordT :: Type -> Type #

Methods

from :: RecordT -> Rep RecordT x #

to :: Rep RecordT x -> RecordT #

NFData RecordT Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: RecordT -> () #

FromVal RecordT Source # 
Instance details

Defined in Koneko.Data

type Rep RecordT Source # 
Instance details

Defined in Koneko.Data

type Rep RecordT = D1 ('MetaData "RecordT" "Koneko.Data" "koneko-0.0.2-83yCJUTvCgkNrPx5HFN9s" 'False) (C1 ('MetaCons "RecordT" 'PrefixI 'True) (S1 ('MetaSel ('Just "recName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "recFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Identifier])))

data Record Source #

Instances

Instances details
Eq Record Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord Record Source # 
Instance details

Defined in Koneko.Data

Show Record Source # 
Instance details

Defined in Koneko.Data

Generic Record Source # 
Instance details

Defined in Koneko.Data

Associated Types

type Rep Record :: Type -> Type #

Methods

from :: Record -> Rep Record x #

to :: Rep Record x -> Record #

NFData Record Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: Record -> () #

FromVal Record Source # 
Instance details

Defined in Koneko.Data

type Rep Record Source # 
Instance details

Defined in Koneko.Data

type Rep Record = D1 ('MetaData "Record" "Koneko.Data" "koneko-0.0.2-83yCJUTvCgkNrPx5HFN9s" 'False) (C1 ('MetaCons "Record" 'PrefixI 'True) (S1 ('MetaSel ('Just "recType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RecordT) :*: S1 ('MetaSel ('Just "recValues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [KValue])))

data Thunk Source #

Instances

Instances details
Eq Thunk Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord Thunk Source # 
Instance details

Defined in Koneko.Data

Methods

compare :: Thunk -> Thunk -> Ordering #

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

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

(>) :: Thunk -> Thunk -> Bool #

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

max :: Thunk -> Thunk -> Thunk #

min :: Thunk -> Thunk -> Thunk #

NFData Thunk Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: Thunk -> () #

data Scope Source #

Constructors

Scope 

Fields

Instances

Instances details
NFData Scope Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: Scope -> () #

data KPrim Source #

Instances

Instances details
Eq KPrim Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord KPrim Source # 
Instance details

Defined in Koneko.Data

Methods

compare :: KPrim -> KPrim -> Ordering #

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

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

(>) :: KPrim -> KPrim -> Bool #

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

max :: KPrim -> KPrim -> KPrim #

min :: KPrim -> KPrim -> KPrim #

Show KPrim Source # 
Instance details

Defined in Koneko.Data

Methods

showsPrec :: Int -> KPrim -> ShowS #

show :: KPrim -> String #

showList :: [KPrim] -> ShowS #

Generic KPrim Source # 
Instance details

Defined in Koneko.Data

Associated Types

type Rep KPrim :: Type -> Type #

Methods

from :: KPrim -> Rep KPrim x #

to :: Rep KPrim x -> KPrim #

NFData KPrim Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: KPrim -> () #

Cmp KPrim Source # 
Instance details

Defined in Koneko.Data

Methods

cmp :: KPrim -> KPrim -> Ordering Source #

type Rep KPrim Source # 
Instance details

Defined in Koneko.Data

data KValue Source #

Instances

Instances details
Eq KValue Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord KValue Source # 
Instance details

Defined in Koneko.Data

Show KValue Source # 
Instance details

Defined in Koneko.Data

Generic KValue Source # 
Instance details

Defined in Koneko.Data

Associated Types

type Rep KValue :: Type -> Type #

Methods

from :: KValue -> Rep KValue x #

to :: Rep KValue x -> KValue #

NFData KValue Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: KValue -> () #

FromVal KValue Source # 
Instance details

Defined in Koneko.Data

ToVal KValue Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: KValue -> KValue Source #

Cmp KValue Source # 
Instance details

Defined in Koneko.Data

Methods

cmp :: KValue -> KValue -> Ordering Source #

FromVal [KValue] Source # 
Instance details

Defined in Koneko.Data

ToVal [KValue] Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: [KValue] -> KValue Source #

Cmp [KValue] Source # 
Instance details

Defined in Koneko.Data

Methods

cmp :: [KValue] -> [KValue] -> Ordering Source #

type Rep KValue Source # 
Instance details

Defined in Koneko.Data

type Rep KValue = D1 ('MetaData "KValue" "Koneko.Data" "koneko-0.0.2-83yCJUTvCgkNrPx5HFN9s" 'False) (((C1 ('MetaCons "KPrim" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KPrim)) :+: (C1 ('MetaCons "KPair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pair)) :+: C1 ('MetaCons "KList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 List)))) :+: (C1 ('MetaCons "KDict" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dict)) :+: (C1 ('MetaCons "KIdent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: C1 ('MetaCons "KQuot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))))) :+: ((C1 ('MetaCons "KBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)) :+: (C1 ('MetaCons "KBuiltin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Builtin)) :+: C1 ('MetaCons "KMulti" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Multi)))) :+: (C1 ('MetaCons "KRecordT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RecordT)) :+: (C1 ('MetaCons "KRecord" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Record)) :+: C1 ('MetaCons "KThunk" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Thunk))))))

data KType Source #

Instances

Instances details
Eq KType Source # 
Instance details

Defined in Koneko.Data

Methods

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

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

Ord KType Source # 
Instance details

Defined in Koneko.Data

Methods

compare :: KType -> KType -> Ordering #

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

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

(>) :: KType -> KType -> Bool #

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

max :: KType -> KType -> KType #

min :: KType -> KType -> KType #

Show KType Source # 
Instance details

Defined in Koneko.Data

Methods

showsPrec :: Int -> KType -> ShowS #

show :: KType -> String #

showList :: [KType] -> ShowS #

Generic KType Source # 
Instance details

Defined in Koneko.Data

Associated Types

type Rep KType :: Type -> Type #

Methods

from :: KType -> Rep KType x #

to :: Rep KType x -> KType #

NFData KType Source # 
Instance details

Defined in Koneko.Data

Methods

rnf :: KType -> () #

type Rep KType Source # 
Instance details

Defined in Koneko.Data

type Rep KType = D1 ('MetaData "KType" "Koneko.Data" "koneko-0.0.2-83yCJUTvCgkNrPx5HFN9s" 'False) ((((C1 ('MetaCons "TNil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TBool" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TFloat" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TStr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TKwd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TPair" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TList" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "TDict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TIdent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TQuot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TBlock" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TBuiltin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TMulti" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TRecordT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TRecord" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TThunk" 'PrefixI 'False) (U1 :: Type -> Type))))))

type Stack = [KValue] Source #

class Cmp a where Source #

Methods

cmp :: a -> a -> Ordering Source #

Instances

Instances details
Cmp KValue Source # 
Instance details

Defined in Koneko.Data

Methods

cmp :: KValue -> KValue -> Ordering Source #

Cmp KPrim Source # 
Instance details

Defined in Koneko.Data

Methods

cmp :: KPrim -> KPrim -> Ordering Source #

Cmp [KValue] Source # 
Instance details

Defined in Koneko.Data

Methods

cmp :: [KValue] -> [KValue] -> Ordering Source #

class ToVal a Source #

Minimal complete definition

toVal

Instances

Instances details
ToVal Bool Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Bool -> KValue Source #

ToVal Double Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Double -> KValue Source #

ToVal Integer Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Integer -> KValue Source #

ToVal () Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: () -> KValue Source #

ToVal Text Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Text -> KValue Source #

ToVal KValue Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: KValue -> KValue Source #

ToVal Builtin Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Builtin -> KValue Source #

ToVal Block Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Block -> KValue Source #

ToVal Dict Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Dict -> KValue Source #

ToVal Pair Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Pair -> KValue Source #

ToVal Kwd Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Kwd -> KValue Source #

ToVal [KValue] Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: [KValue] -> KValue Source #

ToVal [Pair] Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: [Pair] -> KValue Source #

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

Defined in Koneko.Data

Methods

toVal :: Maybe a -> KValue Source #

ToVal a => ToVal (Either e a) Source # 
Instance details

Defined in Koneko.Data

Methods

toVal :: Either e a -> KValue Source #

toVal :: ToVal a => a -> KValue Source #

class FromVal a Source #

Minimal complete definition

fromVal

Instances

Instances details
FromVal Bool Source # 
Instance details

Defined in Koneko.Data

FromVal Double Source # 
Instance details

Defined in Koneko.Data

FromVal Integer Source # 
Instance details

Defined in Koneko.Data

FromVal () Source # 
Instance details

Defined in Koneko.Data

FromVal Text Source # 
Instance details

Defined in Koneko.Data

FromVal KValue Source # 
Instance details

Defined in Koneko.Data

FromVal Record Source # 
Instance details

Defined in Koneko.Data

FromVal RecordT Source # 
Instance details

Defined in Koneko.Data

FromVal Block Source # 
Instance details

Defined in Koneko.Data

FromVal Dict Source # 
Instance details

Defined in Koneko.Data

FromVal Pair Source # 
Instance details

Defined in Koneko.Data

FromVal Kwd Source # 
Instance details

Defined in Koneko.Data

FromVal [KValue] Source # 
Instance details

Defined in Koneko.Data

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

Defined in Koneko.Data

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

Defined in Koneko.Data

toVals :: ToVal a => [a] -> [KValue] Source #

push :: ToVal a => Stack -> a -> Stack Source #

rpush :: ToVal a => Stack -> [a] -> IO Stack Source #

rpush1 :: ToVal a => Stack -> a -> IO Stack Source #

pop2 :: (FromVal a, FromVal b) => Stack -> Either KException ((a, b), Stack) Source #

NB: returns popped items in "reverse" order

>>> s = emptyStack `push` 1 `push` 2
>>> fst <$> pop' s :: IO Integer
2
>>> fst <$> pop2' s :: IO (Integer, Integer)
(1,2)

stack: ... 1 2 <- top

pop3 :: (FromVal a, FromVal b, FromVal c) => Stack -> Either KException ((a, b, c), Stack) Source #

NB: returns popped items in "reverse" order

>>> s = emptyStack `push` 1 `push` 2 `push` 3
>>> fst <$> pop3' s :: IO (Integer, Integer, Integer)
(1,2,3)

stack: ... 1 2 3 <- top

pop4 :: (FromVal a, FromVal b, FromVal c, FromVal d) => Stack -> Either KException ((a, b, c, d), Stack) Source #

pop' :: FromVal a => Stack -> IO (a, Stack) Source #

pop2' :: (FromVal a, FromVal b) => Stack -> IO ((a, b), Stack) Source #

pop3' :: (FromVal a, FromVal b, FromVal c) => Stack -> IO ((a, b, c), Stack) Source #

pop4' :: (FromVal a, FromVal b, FromVal c, FromVal d) => Stack -> IO ((a, b, c, d), Stack) Source #

popN' :: FromVal a => Int -> Stack -> IO ([a], Stack) Source #

pop1push :: (FromVal a, ToVal b) => (a -> [b]) -> Evaluator Source #

pop2push :: (FromVal a, FromVal b, ToVal c) => (a -> b -> [c]) -> Evaluator Source #

pop1push1 :: (FromVal a, ToVal b) => (a -> b) -> Evaluator Source #

pop2push1 :: (FromVal a, FromVal b, ToVal c) => (a -> b -> c) -> Evaluator Source #

pair :: ToVal a => Kwd -> a -> KValue Source #

list :: ToVal a => [a] -> KValue Source #