jaskell: Stack-based concatenative language embedded in Haskell

[ language, library, mit ] [ Propose Tags ]

Jaskell is a stack-based programming language implemented using normal Haskell types and functions, along with a quasiquoter that allows for a more elegant syntax than what pure Haskell supports. Since it is embedded in Haskell, Jaskell is purely functional and, unlike other stack-based languages, statically typed. The standard library is based on that of Joy, and the name "Jaskell" is a portmanteau of "Joy" and "Haskell."

A Jaskell program is a sequence of commands. Each command is a function which takes a stack — represented in Haskell as a left-nested tuple — and returns another stack. In order to accomodate side effects, commands need not actually be functions; any arrow is allowed as a command. The two most useful arrow types are (->) and Kleisli IO.

Two example programs are shown below. The first program asks for the user's name and then prints a greeting. The second program defines a qsort function and then uses it to sort a list.

{-# LANGUAGE QuasiQuotes #-}
import qualified Jaskell
import Jaskell.Quote (jsl)
import Jaskell.Prelude

main :: IO ()
main = Jaskell.runK [jsl|
  "What's your name?" !putStrLn [ "Hello, ", ?getLine, "!" ] $concat !putStrLn
  |]

sorted :: ((), [Int])
sorted = Jaskell.run [jsl|
  DEF small =
    { $null } { uncons $null } disjoin ;
  DEF qsort =
    small { } { uncons { < } split rolldown }
    { swap cons ++ } binrec' ;
  [3,5,1,6,4,2] qsort
  |]

[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0
Change log CHANGELOG.md
Dependencies base (>=4.13.0.0 && <5), megaparsec (>=9.0.0 && <10), template-haskell (>=2.16.0.0 && <2.21) [details]
License MIT
Author Owen Bechtel
Maintainer ombspring@gmail.com
Category Language
Home page https://github.com/UnaryPlus/jaskell
Bug tracker https://github.com/UnaryPlus/jaskell/issues
Source repo head: git clone https://github.com/UnaryPlus/jaskell.git
Uploaded by OwenBechtel at 2023-06-27T18:23:22Z
Distributions
Downloads 600 total (5 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
All reported builds failed as of 2023-08-25 [all 1 reports]

Readme for jaskell-0.1.0.0

[back to package description]

Jaskell

A stack-based concatenative language embedded in Haskell.

Documentation is available on Hackage.