Re: [Haskell-cafe] ANNOUNCE: luachunk-0.1

2012-10-10 Thread Anupam Jain
On Mon, Oct 8, 2012 at 6:48 AM, Kristopher Micinski
 wrote:
> Oh, this is nice, we have our undergrads implement a compiler to Lua
> bytecode as part of their term projects, and currently use a homebrew
> OCaml package.  This seems to be pretty complete, however, and it
> would be interesting for me to reimplement some stuff with this..

Please do! It would be great to have some real world testing.

>
> Unfortunately the Lua bytecode isn't really documented or intended to
> be generated, meaning that you essentially have to reverse engineer
> it.  (Maybe not "unfortunately;" it's not meant to be used like that,
> but unfortunately for people looking to find projects to assign
> people...)

I used the excellent "A No-Frills Introduction to Lua 5.1 VM
Instructions" (http://scholar.google.com/scholar?cluster=14039839166840129336).
Highly recommended to get a quick overview of the entire bytecode format.

-- Anupam

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: luachunk-0.1

2012-10-05 Thread Anupam Jain
Hi all,

I just released luachunk-0.1 on Hackage
(http://github.com/ajnsit/luachunk). Luachunk is a small library to
read and write Lua 5.1 bytecode chunks. It is modeled after
ChunkSpy.lua (http://luaforge.net/projects/chunkspy/) though the code
is written from scratch. A pretty listing printer for lua bytecode is
in the works.

I used LuaChunk in a project to generate Lua bytecode via a DSL, and
then interpret it with HsLua. I hope to release the DSL itself
sometime in the future.

-- Anupam

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskellers in Delhi, India

2012-01-24 Thread Anupam Jain
On Tue, Jan 24, 2012 at 3:40 PM, Sean Leather  wrote:
> On Tue, Jan 24, 2012 at 10:21, Anupam Jain wrote:
>>
>> Are there any haskellers in Delhi or nearby areas interested in a
>> meetup? I've been dabbling in Haskell for a long time
>
>
> I'm not in India, but I am curious about the use of Haskell or other FP
> languages for teaching/research there. Do you (or does anyone else) happen
> to know which schools have courses that teach/use FP/Haskell?

I don't have a formal CS degree and I don't really know how popular
Haskell/FP is in the academia here. I do suspect that Scheme would be
a lot more popular than Haskell or any other FPL.

However, I recall Piyush from IITK recently posting on the Yesod list.
A quick google search reveals that he teaches a Haskell FP course -
http://www.cse.iitk.ac.in/users/ppk/teaching/cs653/.

Thanks,
Anupam Jain

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskellers in Delhi, India

2012-01-24 Thread Anupam Jain
Hi all,

Are there any haskellers in Delhi or nearby areas interested in a
meetup? I've been dabbling in Haskell for a long time but only
recently became interested in creating large "real world" programs
with it. It would be interesting to meet folks who already have such
experience (or are looking to get such experience).

Thanks,
Anupam Jain

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to split this string.

2012-01-02 Thread Anupam Jain
On Mon, Jan 2, 2012 at 5:52 PM, Felipe Almeida Lessa
 wrote:
> On Mon, Jan 2, 2012 at 10:12 AM, max  wrote:
>> This is the simplest solution of the proposed, in my opinion. Thank you
>> very much.
>
> Better yet, don't use String and use Text.  Then you just need
> T.splitOn "\r\n" [1].

That is actually the opposite of what the OP wants, however it's
interesting that Text has a function like that and not the String
functions in the standard
library.

-- Anupam

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to split this string.

2012-01-02 Thread Anupam Jain
On Mon, Jan 2, 2012 at 3:14 PM, max  wrote:
> I want to write a function whose behavior is as follows:
>
> foo "string1\nstring2\r\nstring3\nstring4" = ["string1",
> "string2\r\nstring3", "string4"]
>
> Note the sequence "\r\n", which is ignored. How can I do this?

Here's a simple way (may not be the most efficient) -

import Data.List (isSuffixOf)

split = reverse . foldl f [] . lines
  where
f [] w = [w]
f (x:xs) w = if "\r" `isSuffixOf` x then ((x++"\n"++w):xs) else (w:x:xs)

Testing -

ghci> split "ab\r\ncd\nefgh\nhijk"
["ab\r\ncd","efgh","hijk"]


-- Anupam

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Putting constraints on "internal" type variables in GADTs

2011-11-08 Thread Anupam Jain
Hi all,

I was trying to do something very simple with GADTs when I ran into this
problem -

-- My datatype
data T o where
  Only ∷ o → T o
  TT ∷ T o1 → (o1 → o2) → T o2

-- Show instance for debugging
instance Show o ⇒ Show (T o) where
  show (Only o) = "Only " ⊕ (show o)
  show (TT t1 f) = "TT (" ⊕ (show t1) ⊕ ")"


When I try to compile this I get the following -

Could not deduce (Show o1) arising from a use of `show'
from the context (Show o)



While I understand why I get this error, I have no idea how to fix it! I
cannot put a Show constraint on o1 because that variable is not exposed in
the type of the expression.

I can work around this by changing my data type declaration to include Show
constraints but I don't want to restrict my data type to only Showable
things just so I could have a "Show" instance for debugging -

Only ∷ Show o ⇒ o → T o
TT ∷ (Show o1, Show o2) ⇒ T o1 → (o1 → o2) → T o2


What else can I do to declare a Show instance for my datatype?

Thanks,
Anupam Jain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Problem with types

2011-08-19 Thread Anupam Jain
Hi all,

Suppose I have a compound data type -

data M o = M (String,o)

Now, I can define a function that works for ALL M irrespective of o. For
example -

f :: M o -> M o
f (M (s,o)) = M (s++"!", o)

I can also use this function in an expression, applying it to different
types without problem -

p = (m1',m2') where
  m1 = M ("1", ())
  m2 = M ("2", True)
  m1' = f m1
  m2' = f m2

Main*> p
(M ("1!",()),M ("2!",True))

However, if I try to parameterise over the function 'f' it does not work!  -

p f = (m1',m2') where
  m1 = M ("1", ())
  m2 = M ("2", True)
  m1' = f m1
  m2' = f m2

It doesn't even typecheck, producing the error - "Couldn't match expected
type 'Bool' with actual type '()'"

Is there a particular reason for this? How can I define a function like 'p'
within Haskell?

Thanks,
Anupam Jain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficient object identity (aka symbols as data)

2011-05-29 Thread Anupam Jain
On Thu, May 26, 2011 at 7:26 PM, Gregory Collins wrote:

> Based on the description it looks like you could be looking for:
>
>http://hackage.haskell.org/package/simple-atom
>
> G
>
>
Coincidentally, I put up a question at stackoverflow for this just yesterday
-
http://stackoverflow.com/questions/6164260/why-doesnt-haskell-have-symbols-a-la-ruby-atoms-a-la-erlang
.

Why doesn't Haskell have built in syntactic sugar for atoms?

-- Anupam
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Problem with haskell types

2010-07-30 Thread Anupam Jain
Hi,

I am having trouble getting a small program to compile. The helpful folks at
#haskell created a version of the program that does compile -
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28406#a28408 but it is not
very clear to them (and to me) why the original program wouldn't type
compile in the first place.

Here's the program that refuses to compile -

module Delme () wheredata DecisionState = A | B | C | Dd_test :: Eq b
=> b -> b -> DecisionState -> DecisionState -> ()d_test test testVal
trueState falseState =if (test == testVal) then d trueState
 else d falseStated :: DecisionState -> ()d A = d_test True True B Cd
B = d_test 1 2 C Dd C = d_test True False A Bd D = ()

I get an error like -

Delme.hs:13:0:
Contexts differ in length
  (Use -XRelaxedPolyRec to allow this)
When matching the contexts of the signatures for
  d_test :: forall b.
(Eq b) =>
b -> b -> DecisionState -> DecisionState -> ()
  d :: DecisionState -> ()
The signature contexts in a mutually recursive group should all be
identical
When generalising the type(s) for d_test, d

Putting in the extension does get the program to type check but the original
program should have type compiled in the first place.

The ironic thing we discovered is that if we remove the type declaration for
'd', the program type checks, and GHC then derives the exact same type which
we removed!

Can some of the smarter people in the room please shed more light on this?

-- Anupam
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe