Friday, April 17, 2009

/*

: doub dup + ;
: quad doub doub ;

: swap ( a b -- b a ) ;
: dup ( a -- a a ) ;
: pop ( a -- ) ;
: + ( int int -- int ) ;

int doub(int a)
{
    return a + a;
}

int quad(int a)
{
    return doub(doub(a));
}

*/


#include <iostream>
#include <vector>
#include <string>

struct Object
{
};

typedef Object* ObjectPtr;

struct Int : public Object
{
    int val;
};

typedef Int* IntPtr;

#define DEREF_Int(x) (*static_cast<IntPtr>(x))

std::ostream& operator<<(std::ostream& os, Int const& i)
{
    os<<i.val;
    return os;
}


struct String : public Object
{
    std::string val;
};

typedef String* StringPtr;

#define DEREF_String(x) (*static_cast<StringPtr>(x))

std::ostream& operator<<(std::ostream& os, String const& i)
{
    os<<i.val;
    return os;
}

int main()
{
    std::vector<ObjectPtr> vec;
    Int i;
    i.val = 42;
    vec.push_back(&i);
    String s;
    s.val = "hello world!";
    vec.push_back(&s);
    std::cout<<DEREF_Int(vec[0])<<std::endl
        <<DEREF_String(vec[1])<<std::endl;
    return 0;
}

Tuesday, March 31, 2009

no!!!!!!!!!!!!!!!!!! I could not install firefox addons for sometime now. I was able to on my Windows machine.. But not on Linux.. Then I found this: http://ubuntuforums.org/showpost.php?p=3965149&postcount=21 So, I disabled ipv6 on firefox and now I can install addons. However, Windows' Firefox can install addons with ipv6 enabled.. Weird..............

Friday, March 27, 2009

ATS WHEEEEEEEEEEE

ATS looks cool.

So... to link things that use math functions, you use -lm.

To compile http://www.ats-lang.org/TUTORIAL/contents/basics.dats, you should do the same because it uses sqrt math function.

atscc basics.dats -lm

And I am writing ats.vim

" Vim syntax file
" Language:   ats

if version < 600
  syntax clear
elseif exists("b:current_syntax")
  finish
endif

:runtime! syntax/c.vim
:unlet b:current_syntax

syn case match

" Keywords
syn keyword atsKeyword implement begin end staload
syn keyword atsKeyword prefix postfix infix infixl infixr op nonfix
syn keyword atsKeyword val and fun fn lam fix rec
syn keyword atsKeyword if then else let in where
syn keyword atsKeyword symintr overload with
syn keyword atsKeyword typedef datatype sortdef
syn keyword atsKeyword case of

syn keyword atsSorts bool char int prop type view viewtype

syn keyword atsTypes string float double

" Comments
syn match atsLineComment /\/\/.*$/
syn region atsFileComment start=/\/\/\/\// end=/\%$/
syn region atsMLComment start=/(\*/ end=/\*)/ contains=atsMLComment
syn region atsCComment start=/\/\*/ end=/\*\//

" Literals
syn keyword atsBoolean true false


if version >= 508 || !exists("did_c_syn_inits")
  if version < 508
    let did_c_syn_inits = 1
    command -nargs=+ HiLink hi link <args>
  else
    command -nargs=+ HiLink hi def link <args>
  endif
  HiLink atsLineComment Comment
  HiLink atsFileComment Comment
  HiLink atsMLComment Comment
  HiLink atsCComment Comment
  HiLink atsKeyword Keyword
  HiLink atsSorts Type
  HiLink atsTypes Type
  delcommand HiLink
endif

let b:current_syntax = "ats"

Things to look at:

Speaking of concatenative language, I was trying to do something like this: http://www.bluishcoder.co.nz/xyjs/xylistener.html, which is from this post. Lol I just copied it over and tried to do something... http://wekeywiki.googlepages.com/ascl-listener.html. But I gave up on it.. Anyways, it's another TODO thing :(

Wednesday, December 10, 2008

v8 not build on x86_64

Stupid Google, why would your v8 not build on 64bit system?

scons mode=release library=shared prefix=/usr wordsize=64 || return 1

g++ -o obj/release/third_party/jscre/pcre_compile.os -c -march=x86-64 -mtune=generic -O2 -pipe -ansi -w -O3 -fomit-frame-pointer -m32 -fno-rtti -fno-exceptions -ansi -w -O3 -fomit-frame-pointer -m32 -fPIC -DENABLE_LOGGING_AND_PROFILING -DSUPPORT_UTF8 -DNO_RECURSE -DSUPPORT_UCP

Look at that dreadful -m32 ...

Monday, December 8, 2008

back to archlinux

stupid windows it doesnt' let me fucking build llvm and hssdl doesn't work well on fucking windows fuck fuck fuck.
so, pacman -Syu then
pacman -Sf zsh #for http://www.archlinux.org/news/421/
rm /usr/lib/klibc/include/asm #for http://www.archlinux.org/news/411/
Then,
Section "ServerFlags"
 Option  "AllowEmptyInput" "false"
EndSection
for http://www.archlinux.org/news/424/

Saturday, December 6, 2008

todo

http://alien.luaforge.net/
http://luaforge.net/projects/luaffi/
http://cython.org/
http://code.google.com/apis/v8/embed.html

installing cabal packages on windows vista

http://www.haskell.org/ghc/docs/latest/html/Cabal/builders.html
By default on windows, --datadir=C:\Program Files\Haskell. And vista complains.
So,

runghc Setup.lhs configure --prefix=C:\Users\sam\haskell --datadir=$prefix\share

Thursday, April 17, 2008

Niffy Template Haskell trick for better trace

This trick is by EvilTerran from #haskell freenode IRC channel.

A quick and dirty way to debug Haskell code is to use trace function from Debug.Trace module.

For example,

f (trace ("arg1: " ++ show arg1) arg1) arg2

would print

arg1: <actual value of arg1>

Usung Template Haskell, above code can be shortened.

> {-# LANGUAGE TemplateHaskell #-}

This means this code uses TemplateHaskell extension.

> module Trace where

Let's call the module Trace.

> import Language.Haskell.TH
> import Debug.Trace (trace)

And, import some modules.

> t name = [| trace ($(litE . StringL $ nameBase name)
>    ++ ": " ++ show $(varE name)) $(varE name) |]

Then, define the macro t that can be called as:

$(t 'varName)

And it'll be expanded to:

trace ("varName" ++ ": " ++ show varName) varName

Let's actually use Trace.t in Main module.

> {-# LANGUAGE TemplateHaskell #-}

Main module also needs to use TemplateHaskell extension because it'll include macro call like $(t 'a).

> module Main where
> import Trace (t)
> import Debug.Trace (trace)

> main = do
>     let a = 2
>     let bravo = 40
>     putStrLn $ show ((trace ("a: " ++ show a) a) + bravo)

compare this with

>     putStrLn $ show ($(t 'bravo) + $(t 'a))

>     return ()

Shorter.

Now, I need vim keyboard shortcut that'll replace the word under cursor with $(t 'wordUnderCuror). And, another keyboard shortcut that'll turn $(t 'word) into word.

Edit: Alok commented with vim function below:

" word <===> $(t 'word)
" by Alok
function! ToggleTrace()
    call searchpos('\|)')
    let b = searchpos('\<', 'b')
    let s = searchpos("\$(t '", 'b')
    if s[0] == b[0] && b[1] - s[1] == len("$(t '")
        " remove trace
        norm df'f)x
    else
        " add trace
        call insert (b, 0, 0)
        call add (b, 0)
        call setpos('.', b)
        let @z = "$(t '"
        norm "zP
        let @z = ")"
        norm f "zP
    endif
endfunction

nmap <leader>t :call ToggleTrace()<cr>

Thank you Alok.

Monday, March 10, 2008

factor listner font size

in ~/.factor-rc
for 0.91
IN:  ui.freetype
: dpi 120 ;

for git version
USE: namespaces
USE: ui.freetype
120 dpi set-global

Thursday, March 6, 2008

Staque

Accompanying presentation

I was thinking about how to let users mix up prefix, infix, and postfix syntax.

For example, + (+ 1 2) 3, 1 + 2 + 3, and 1 2 + 3 + would all be grammatical.

Using a stack and a queue, it might be possible:

  • Each token (value) is pushed on to the stack.
  • If the value is a function, pop from the stack to get arguments.
  • If stack doesn't have enough arguments, pop from the queue.

Basically, it is stack based evaluation (postfix) with look ahead to give users illusion of prefix or infix.

1 + 2 + 3, for example, would be evaluated as follows:

Queue: 1 + 2 + 3
Stack:
--
Queue: + 2 + 3
Stack: 1
--
Queue: + 3
Stack: 3
--
Queue:
Stack: 6

I name the language Staque and here is prototype:

> module Main where

Import stuff for parser.

> import qualified Text.ParserCombinators.Parsec as P
> import Text.ParserCombinators.Parsec ( (<|>) )

Import stuff for printing.

> import qualified Text.PrettyPrint.HughesPJ as PP

Import stuff for repl.

> import System.IO ( stdout, hFlush )

Let's define values for the language.

> data Val = Int Integer
>     | Ident String
>     | Expr [Val]

Let Val to be showable.

> ppVal (Ident s) = PP.text s
> ppVal (Int i) = PP.integer i
> ppVal (Expr xs) = PP.parens (PP.hsep $ map ppVal xs)
> instance Show Val where show = PP.render . ppVal

Let's write a parser. Expression is just a list of tokens separated by whitespaces.

> parseExpr = do
>     toks <- P.sepEndBy parseToken ws
>     return $ Expr toks
> ws = P.skipMany1 P.space

Expression can be parenthesized.

> parseParenExpr = do
>     lparen
>     e <- P.sepEndBy parseToken ws
>     rparen
>     return $ Expr e
>     where
>         lparen = P.char '(' >> P.spaces
>         rparen = P.spaces >> P.char ')'

A token can be an integer literal, an identifier, or a parenthesized expression.

> parseToken = do
>     P.try parseParenExpr
>     <|> P.try parseInt
>     <|> P.try parseIdent

Let's parse integer literal. An integer literal can start with -.

> parseInt = do
>     sign <- P.string "-" <|> return ""
>     val <- nat
>     return $ Int (read $ sign ++ val)
> nat = P.many1 P.digit

Let's parse identifier. Identifier can be operator or name.

> parseIdent = do
>     ident <- parseOp <|> parseName
>     return $ Ident ident
>     where
>         parseOp = parseHeadBody opChar opChar
>         parseName = parseHeadBody nameChar nameChar
>         parseHeadBody hChar bChar = do
>             h <- hChar
>             b <- P.many bChar
>             return (h : b)
>         opChar = P.oneOf ":!#$%&*+./<=>?@\\^|-~"
>         nameChar = P.alphaNum <|> P.oneOf "_-'"

Now, onto actual evaluation.

Let's define stack and implement push and pop:

> type Stack = [Val]
> push v s = v : s
> pop (x:xs) = (x, xs)

Here is queue. We only consume a queue. Never push element to the queue.

> type Queue = [Val]
> front (x:xs) = (x, xs)

Evaluation function. Finally!

> eval :: Stack -> Queue -> Val

When the queue is empty, evaluation is done. Make sure the stack has only 1 element and return the element as the result of evaluation.

> eval s [] | length s == 1 = (fst . pop) s

When the queue contains an expression, evaluate the expression.

> eval s [Expr q] = eval s q

Now, the queue's front is an identifier. Let's look it up and call the function bound to the identifier. Also, we make sure the rest of the queue is evaluated with the updated stack.

> eval s (Ident fname : args) = let
>     (s', q) = funcall fname s args
>     in
>         eval s' q

The queue's front is not an identifier. Assume it's a literal and push it to the stack and evaluate the rest of the queue.

> eval s (x : xs) = let
>     s' = push x s
>     in
>         eval s' xs

Funcall just looks up a function. If found, it calls the function with stack and queue. The called function returns updated (Stack, Queue).

> funcall fname s q = case lookup fname primitives of
>     Nothing -> error $ fname ++ " not defined"
>     Just f -> f s q

Funcall looks up this map.

> primitives = [
>     ("+", binNumOp (+))
>     , ("-", binNumOp (-))
>     , ("/", binNumOp div)
>     , ("*", binNumOp (*))
>     ]

Before we define a function that uses stack and queue to evaluate binary numeric operations, let's define helper functions.

To unpack and pack integers from and to Val.

> fromVal (Int a) = a
> toVal a = Int a

To evaluate values popped from stack or queue. If the popped value is an expression, evaluate the expression using a new stack. Otherwise, just return the popped value.

> evalVal val = case val of
>     Expr q -> eval [] q
>     otherwise -> val

Now, onto evaluation of binary numeric operation.

First, stack has 2 elements. So, both arguments to the binary operation can be popped from the stack. The arguments popped are evaluated because they can be nested expressions. Then push the result of operation to the stack and return it with queue.

> binNumOp op s q | length s >= 2 = let
>     (b, s') = pop s
>     (a, s'') = pop s'
>     a' = evalVal a
>     b' = evalVal b
>     result = toVal $ fromVal a' `op` fromVal b'
>     in
>         (push result s'', q)

When stack has only 1 element, we should pop from the queue, too.

> binNumOp op s q | length s >= 1 = let
>     (a, s') = pop s
>     (b, q') = front q
>     a' = evalVal a
>     b' = evalVal b
>     result = toVal $ fromVal a' `op` fromVal b'
>     in
>         (push result s', q')

Stack is empty. So, pop 2 arguments from the queue.

> binNumOp op s q = let
>     (a, q') = front q
>     (b, q'') = front q'
>     a' = evalVal a
>     b' = evalVal b
>     result = toVal $ fromVal a' `op` fromVal b'
>     in
>         (push result s, q'')

Now, let's make a repl.

> repl = do
>     input <- prompt "staque> "
>     if input == ":q"
>         then putStrLn "bye"
>         else do
>             putStrLn $ evaluate input
>             repl
>     where
>         prompt p = do
>             putStr p
>             hFlush stdout
>             getLine

Actual evaluate function that transforms user input to string.

> evaluate s = case P.parse parseExpr "staque" s of
>     Left err -> show err
>     Right (Expr q) -> show $ eval [] q

Finally, main function.

> main = repl

Let's run it!

$ runhaskell staque.lhs
staque> 1 + 2
3
staque> + 1 2
3
staque> 1 2 +
3
staque> 1 + 2 + ((1 - -2) * 3) 3 / (+ 1 2) *
12
staque> :q
bye

For exercises:

  • Add more types like string, float, list, char, bool... to the language.
  • Add function definition and lambda abstraction.
  • Add static type checking with user defined types.
  • Get fancier with type system.
  • Add foreign function interface.
  • Add OpenGL binding.
  • Make a first point shooter.