huckleberry-0.9.0.2: IchigoJam BASIC expressed in Haskell.

Safe HaskellSafe
LanguageHaskell2010

Language.Huckleberry.V10101

Contents

Description

The EDSL Provides bridge between IchigoJam BASIC and Haskell.

References for IchigoJam BASIC are available at http://ichigojam.net/IchigoJam-1.0.1.html.

For example, "Jumping rome girl Sacchan" http://pcn.club/ns/diprogram.en.html could be expressed like this.

sacchan = do
  label  10 $ y=:25 >> v=:99 >> x=:17 >> u=:5 >> s=:0
  label  20 $ ifThen (v/=99) $ y=:y+v >> v=:v+1
  label  30 $ ifThen (25<y) $ y=:25 >> v=:99 >> s=:s+1
  label  40 $ x=:x+u
  label  50 $ ifThen (17<x) $ u=:u-1
  label  60 $ ifThen (x<17) $ u=:u+1
  label  70 $ k=:inkey
  label  80 $ ifThen (k==32) $ v=:(-3)
  label  90 $ cls
  label 100 $ locate 17 y >> print "@"
  label 110 $ locate x 25 >> print "-"
  label 120 $ locate 0  0 >> print ("SCORE:" ++ s)
  label 130 $ ifThen (pre(y==25)*pre(x==17)) end
  label 140 $ wait 2
  label 150 $ goto 20

Get IchigoJam BASIC code like this.

showSacchan = putStr $ translate sacchan

Also, you can send the code to IchigoJam directly.

sendSacchan = do
  h <- IJ.opend "/dev/ttyUSB0"
  IJ.send h $ translate sacchan
  IJ.close h

To use this, your code should begin with this code block.

{-# LANGUAGE OverloadedStrings #-}
import Prelude hiding (print,(++),(+),(-),(*),(/),(%),(==),(/=),(>=),(>),(<=),(<),(&&),(||),not,abs,return)
import qualified Prelude as P
import qualified IchigoJam as IJ
import Language.Huckleberry.V10101

For more example. https://github.com/mitsuji/huckleberry

() is pre.

Put line number by label.

[n] is arr.

LET is let'.

= is =:.

; is ++.

IN is in'.

& is .&..

| is .|..

^ is xor.

>> is shiftR.

<< is shiftL.

~ is complement.

Synopsis

Documentation

translate :: Code () -> String Source

Translate huckleberry code to IchigoJam BASIC code.

pre :: Expr Int16 -> Expr Int16 Source

Bracket operator.

the expression

pre(y==25)*pre(x==17)

evaluated as this expression in IchigoJam BASIC.

(Y=25)*(X=17)

label :: Int16 -> Code () -> Code () Source

Line number statement.

this expression

label  40 $ x=:x+u

evaluated as this statement in IchigoJam BASIC.

40 X=X+U

ifThenElse :: Expr Int16 -> Code () -> Code () -> Code () Source

IF .. THEN .. ELSE .. statement.

ifThen :: Expr Int16 -> Code () -> Code () Source

IF .. THEN .. statement.

forStepNext :: Expr Int16 -> Expr Int16 -> Expr Int16 -> Expr Int16 -> Code () -> Code () Source

FOR .. = .. TO .. STEP .. .. NEXT statement.

forNext :: Expr Int16 -> Expr Int16 -> Expr Int16 -> Code () -> Code () Source

FOR .. = .. TO .. .. NEXT statement.

a :: Expr Int16 Source

b :: Expr Int16 Source

c :: Expr Int16 Source

d :: Expr Int16 Source

e :: Expr Int16 Source

f :: Expr Int16 Source

g :: Expr Int16 Source

h :: Expr Int16 Source

i :: Expr Int16 Source

j :: Expr Int16 Source

k :: Expr Int16 Source

l :: Expr Int16 Source

m :: Expr Int16 Source

n :: Expr Int16 Source

o :: Expr Int16 Source

p :: Expr Int16 Source

q :: Expr Int16 Source

r :: Expr Int16 Source

s :: Expr Int16 Source

t :: Expr Int16 Source

u :: Expr Int16 Source

v :: Expr Int16 Source

w :: Expr Int16 Source

x :: Expr Int16 Source

y :: Expr Int16 Source

z :: Expr Int16 Source

arr :: Expr Int16 -> Expr Int16 Source

Array valiables expression.

This expression

arr 3

evaluated as this expression in IchigoJam BASIC.

[3]

Commands for beginners

let' :: Expr Int16 -> [Expr Int16] -> Code () Source

LET statement.

This expression

let' a [3]

evaluated as this statement in IchigoJam BASIC.

LET A,3

Also, this expression

let' (arr 3) [11,12,13]

evaluated as this statement in IchigoJam BASIC.

LET[3],11,12,13

(=:) :: Expr Int16 -> Expr Int16 -> Code () infix 2 Source

Assignment operator.(=)

This expression

x =: x+u

evaluated as this statement in IchigoJam BASIC.

X=X+U

print :: Show r => Expr r -> Code () Source

PRINT statement.

(++) :: (Show a, Show b, IsString c) => Expr a -> Expr b -> Expr c infixl 2 Source

Concatation operator.(;)

led :: Expr Int16 -> Code () Source

wait :: Expr Int16 -> Code () Source

run :: Code () Source

list :: Expr Int16 -> Expr Int16 -> Code () Source

list' :: Code () Source

goto :: Expr Int16 -> Code () Source

end :: Code () Source

btn :: Expr Int16 -> Expr Int16 Source

new :: Code () Source

locate :: Expr Int16 -> Expr Int16 -> Code () Source

cls :: Code () Source

rnd :: Expr Int16 -> Expr Int16 Source

save :: Expr Int16 -> Code () Source

save' :: Code () Source

load :: Expr Int16 -> Code () Source

load' :: Code () Source

files :: Expr Int16 -> Code () Source

beep :: Expr Int16 -> Expr Int16 -> Code () Source

beep' :: Code () Source

play :: String -> Code () Source

play' :: Code () Source

tempo :: Expr Int16 -> Code () Source

(+) :: Expr Int16 -> Expr Int16 -> Expr Int16 infixl 6 Source

(-) :: Expr Int16 -> Expr Int16 -> Expr Int16 infixl 6 Source

(*) :: Expr Int16 -> Expr Int16 -> Expr Int16 infixl 7 Source

(/) :: Expr Int16 -> Expr Int16 -> Expr Int16 infixl 7 Source

(%) :: Expr Int16 -> Expr Int16 -> Expr Int16 infixl 7 Source

input :: String -> Expr Int16 -> Code () Source

tick :: Expr Int16 Source

clt :: Code () Source

chr :: Expr Int16 -> Expr String Source

chr' :: [Expr Int16] -> Expr String Source

asc :: String -> Expr Int16 Source

scroll :: Expr Int16 -> Code () Source

scr :: Expr Int16 -> Expr Int16 -> Expr Int16 Source

scr' :: Expr Int16 Source

vpeek :: Expr Int16 -> Expr Int16 -> Expr Int16 Source

(==) :: Expr Int16 -> Expr Int16 -> Expr Int16 infix 5 Source

(/=) :: Expr Int16 -> Expr Int16 -> Expr Int16 infix 5 Source

(>=) :: Expr Int16 -> Expr Int16 -> Expr Int16 infix 5 Source

(>) :: Expr Int16 -> Expr Int16 -> Expr Int16 infix 5 Source

(<=) :: Expr Int16 -> Expr Int16 -> Expr Int16 infix 5 Source

(<) :: Expr Int16 -> Expr Int16 -> Expr Int16 infix 5 Source

(&&) :: Expr Int16 -> Expr Int16 -> Expr Int16 infixr 4 Source

(||) :: Expr Int16 -> Expr Int16 -> Expr Int16 infixr 3 Source

not :: Expr Int16 -> Expr Int16 Source

Commands for experts

clv :: Code () Source

clear :: Code () Source

clk :: Code () Source

abs :: Expr Int16 -> Expr Int16 Source

gosub :: Expr Int16 -> Code () Source

return :: Code () Source

free :: Expr Int16 Source

ver :: Expr Int16 Source

renum :: Expr Int16 -> Code () Source

renum' :: Code () Source

lrun :: Expr Int16 -> Code () Source

file :: Expr Int16 Source

sleep :: Code () Source

video :: Expr Int16 -> Code () Source

peek :: Expr Int16 -> Expr Int16 Source

poke :: Expr Int16 -> Expr Int16 -> Code () Source

clp :: Code () Source

help :: Code () Source

ana :: Expr Int16 -> Expr Int16 Source

out :: Expr Int16 -> Expr Int16 -> Code () Source

out' :: Expr Int16 -> Code () Source

in' :: Expr Int16 -> Expr Int16 Source

IN expression.

in'' :: Expr Int16 Source

hex :: Expr Int16 -> Expr Int16 -> Expr String Source

hex' :: Expr Int16 -> Expr String Source

bin :: Expr Int16 -> Expr Int16 -> Expr String Source

bin' :: Expr Int16 -> Expr String Source

(.&.) :: Expr Int16 -> Expr Int16 -> Expr Int16 infixl 7 Source

Bitwise AND operator (&)

(.|.) :: Expr Int16 -> Expr Int16 -> Expr Int16 infixl 6 Source

Bitwise OR operator (|)

xor :: Expr Int16 -> Expr Int16 -> Expr Int16 infixl 7 Source

Bitwise XOR expression (^)

shiftR :: Expr Int16 -> Expr Int16 -> Expr Int16 infixl 7 Source

Right shift expression (>>)

shiftL :: Expr Int16 -> Expr Int16 -> Expr Int16 infixl 7 Source

Left shift expression (<<)

complement :: Expr Int16 -> Expr Int16 Source

Complement expression (~)

bps :: Expr Int16 -> Code () Source

i2cr :: Expr Int16 -> Expr Int16 -> Expr Int16 -> Expr Int16 -> Expr Int16 -> Expr Int16 Source

i2cw :: Expr Int16 -> Expr Int16 -> Expr Int16 -> Expr Int16 -> Expr Int16 -> Expr Int16 Source

usr :: Expr Int16 -> Expr Int16 -> Expr Int16 Source