Re: Superclass defaults

2011-08-30 Thread Victor Nazarov
I was thinking about the design of superclass default instances. I
think that we can get relatively far using the following extensions
together:

1) Multiple instance declarations

instance (Functor[a], Monad [a])
  where
fmap = map
(=) = flip concatMap
return = (:[])

-- Declaration above is syntactic sugar for 2 declarations:
-- instance Functor[a]
--  where
--fmap = map
-- instance Monad [a]
--  where
--(=) = flip concatMap
--return = (:[])

2) Context synonyms

-- (MonadAndFunctor a) is synonym for (Functor a, Monad a)
context (Functor a, Monad a) = MonadAndFunctor a

-- Using synonims with multiple class declarations we can define instances like
instance MonadAndFunctor [a]
  where
fmap = map
(=) = flip concatMap
return = (:[])

-- Declaration above is syntactic sugar for
-- instance (Functor[a], Monad [a])
--  where
--fmap = map
--(=) = flip concatMap
--return = (:[])

3) And finally Default superclass instances

Class contains default instances for superclasses:

class Functor m = Monad m
  where
(=) :: m a - (a - m b) - m b
return :: a - m a

-- default superclass instance:
instance Functor m
  where
fmap f m = m = (return . f)

Default superclass implementations are used only when multiple
instance declarations are used:

-- no default superclass instance is used. Error is emitted when there
is no Functor instance
instance Monad [a]
  where
 ...

-- default superclass instance is used:
instance Functor [a], Monad [a]
  where
(=) = ...
return = ...

-- functor instance is generated automatically
-- fmap = ...

Suppose that we make Functor to be Monad's superclass.
Combination of this three extensions allows us to define compatibility modules:

module Control.Monad.Compat (Monad) where

import qualified Control.Monad (Monad(..), Functor(..)) as CM

context CM.Functor m, CM.Monad m = Monad m

When we have compilation failure in client code after our Monad
definition change: No Functor instance found for Foo:

instance Monad Foo
  where ...

, we simply add following two lines to the module:

import Prelude hiding (Monad)
import Control.Monad.Compat (Monad)

and compilation succeeds.

Pros:
Client code can remain Haskell 98/2010 and doesn't require any extensions.
Three extensions seems simple when separate (I think there are many
corner cases)

Cons:
Intervention is required into client code (But I think it is required anyway).

-- 
Victor Nazarov

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCJS

2011-08-04 Thread Victor Nazarov
On Wed, Aug 3, 2011 at 2:44 PM, Simon Marlow marlo...@gmail.com wrote:
 On 03/08/2011 11:09, Victor Nazarov wrote:

 On Wed, Aug 3, 2011 at 11:30 AM, Simon Peyton-Jones
 simo...@microsoft.com  wrote:

 So perhaps that's the problem. parseDynamicFlags could perfectly well
 simply return any un-recognised flags. Indeed, I thought it did just that --
 it certainly returns a list of un-consumed arguments.  If it doesn't perhaps
 that's a bug.

 parseDynamicFlags returns un-consumed arguments if they are something
 like filenames, but it throws error if un-consumed argument starts
 with dash.

 So then parseDynamicFlags should be split into two layers, the lower layer
 returning unused flags, and the upper layer generating errors. You could use
 the lower layer in your front end.

 Please send us a patch...

 OK, so this is harder.  Presumably you want to use an *unmodified*
 Haskell parser to parse the Haskell programs. Adding *syntactic* extensions
 is therefore somewhat invasive:
        - change the lexer
        - change the parser
        - change the HsSyn data structure
        - change every function that traverses HsSyn

 However in this particular case maybe things are not so bad.  I believe
 that perhaps *all* you want is to add a new calling convention. See
 ForeignImport in HsDecls, and CCallConv in ForeignCall.  Simply adding a new
 data constructor to CCallConv, and lexing the token for it, would not be too
 bad.  We could possibly add that part to the mainline compiler. The compiler
 would largely ignore such decls, and they'd just pop out at the other end
 for your back end to consume.

 This would be cool. I will try to provide patch to add all calling
 conventions that backend implementors can use.
 But GHC should report errors about unsupported calling conventions
 sometime during compilation when should it?

 Right, you'll need some backend-specific desugaring of the FFI declarations.
  Maybe we need desugarer plugins? :-) An easier approach would be to have a
 slot in the DynFlags for a callback, like we do for printing error messages,
 so the GHC API client passes in a callback to do whatever backend-specific
 desugaring is required.  The callback mechanism could be used for lots of
 things - I can imagine it growing into a record of backend-specific
 functions that the earlier stages of the compiler might need to call.

 It's hard to predict exactly what's needed.  Again, I suggest you try doing
 this and send us a patch.


I think I should do it. From GHCJS perspective I need to abstract out
literal desugaring and foreign exports/imports desugaring. Desugarer
uses these functions from MkCore module now:

mkIntExpr  :: Integer- CoreExpr
mkIntExprInt   :: Int- CoreExpr
mkWordExpr :: Integer- CoreExpr
mkWordExprWord :: Word   - CoreExpr
mkIntegerExpr  :: MonadThings m = Integer- m CoreExpr
mkFloatExpr :: Float - CoreExpr
mkDoubleExpr :: Double - CoreExpr
mkCharExpr :: Char - CoreExpr
mkStringExpr   :: MonadThings m = String - m CoreExpr
mkStringExprFS :: MonadThings m = FastString - m CoreExpr

We should create some record like:

data LiteralDesugaring m =
  LiteralDesugaring
{ desugarInt :: MonadThings m = Integer - m CoreExpr
, desugarWord :: MonadThings m = Integer - m CoreExpr
, desugarInteger :: MonadThings m = Integer - m CoreExpr
, desugarFloat :: MonadThings m = Float - m CoreExpr
, desugarDouble :: MonadThings m = Double - m CoreExpr
, desugarChar :: MonadThings m = Char - m CoreExpr
, desugarString :: MonadThings m = String - m CoreExpr
}

and some constant like

defaultLiteralDesugaring :: MonadThings m = LiteralDesugaring m
defaultLiteralDesugaring =
  LiteralDesugaring
{ desugarInt = return . mkIntExpr,
...
}

and make desugaring take LitaralDesugaring as an argument, with
defaultLiteralDesugaring being default.

But I don't still understand what can I do with foreign
imports/exports. DsForeign module seems to be too complicated. As I
can see, I shouldn't make whole dsForeigns function replaceable, but I
can't understand what part of it should be replaceble.

-- 
Victor Nazarov

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCJS

2011-08-04 Thread Victor Nazarov
On Fri, Aug 5, 2011 at 12:02 AM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 |  data LiteralDesugaring m =
 |    LiteralDesugaring
 |      { desugarInt :: MonadThings m = Integer - m CoreExpr
 |      , desugarWord :: MonadThings m = Integer - m CoreExpr
 ...

 I am not sure why you want to control the desugaring of literals.  Why 
 literals?  And why is literals enough?


I'm not sure if literals are enough, but literals essentially as
dependencies on ghc-prim package:

5

is desugared to something like

GHC.Num.fromInteger (GHC.Integer.SmallInteger (5# :: Int#))

and

Hello

is desugared to something like

GHC.String.unpackCString (Hello# :: Addr#)

Fore backends other than
drop-in-replacement-for-current-native-code-ghc-backend we may want
an alternative desugarings. For example,
 * we may want to use some very simple Integer implementation. We can
use doubles instead of integers at first to get things rolling.
 * in javascript we better use other unpacking function for strings,
since Javascript strings doesn't have terminating NUL and have length
built-in.

-- 
Victor Nazarov

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCJS

2011-08-03 Thread Victor Nazarov
On Wed, Aug 3, 2011 at 11:30 AM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 Victor

 GHC is supposed to be extensible, via its API, so your questions are good 
 ones.  However, there are things that that the API doesn't support, or 
 supports badly, so it is not cast in stone.  Please suggest improvements -- 
 and better still implement them. GHC evolves largely in response to your 
 suggestions and help.

 In particular I don't think anyone has implemented a new back end via the API 
 (rather than by building it into GHC itself) before.  So this is good.  It 
 would be cool to have a compiler that behaved as if it had a JavaScript 
 backend built in, but was actually built in a modular way on the API. Then 
 people could use that as a model to build new back ends.


 I imagine that your general plan is:
  - use the GHC API to parse Hasekll, typecheck it, optimise it
  - finishing with a [CoreBind] of optimised definitions
  - then use your own code generator to convert that [CoreBind] into JavaScript

Yes, I'm doing it, but I'm moving slightly fearther

- I convert [CoreBind] to [StgBind] through GHC API.
- then convert StgBindings to Javascript.


 | == Command line interface ==
 | This works, but I'm not allowed to parse some custom flags used by
 | GHCJS code and not by GHC API.
 | ParseDynamicFlags throws UsageError if it encounters some unknown flags.

 So perhaps that's the problem. parseDynamicFlags could perfectly well simply 
 return any un-recognised flags. Indeed, I thought it did just that -- it 
 certainly returns a list of un-consumed arguments.  If it doesn't perhaps 
 that's a bug.

parseDynamicFlags returns un-consumed arguments if they are something
like filenames, but it throws error if un-consumed argument starts
with dash.


 | == Foreign Function Interface ==
 |
 | What I want is to provide FFI for Javascript, But GHC doesn't allow to
 | extend FFI declaration syntax.
 | I'd like to create some new FFI calling convention (javascript) like this:
 |
 | foreign import javascript alert
 |   jsalert :: Ptr JSString - IO ()

 OK, so this is harder.  Presumably you want to use an *unmodified* Haskell 
 parser to parse the Haskell programs. Adding *syntactic* extensions is 
 therefore somewhat invasive:
        - change the lexer
        - change the parser
        - change the HsSyn data structure
        - change every function that traverses HsSyn

 However in this particular case maybe things are not so bad.  I believe that 
 perhaps *all* you want is to add a new calling convention. See ForeignImport 
 in HsDecls, and CCallConv in ForeignCall.  Simply adding a new data 
 constructor to CCallConv, and lexing the token for it, would not be too bad.  
 We could possibly add that part to the mainline compiler. The compiler would 
 largely ignore such decls, and they'd just pop out at the other end for your 
 back end to consume.

This would be cool. I will try to provide patch to add all calling
conventions that backend implementors can use.
But GHC should report errors about unsupported calling conventions
sometime during compilation when should it?


 There might be complications -- see DsForeign in particular -- but I expect 
 they'd be minor.

 | For now I'm using (abusing) ccall calling convention and simple
 | imports works pretty well, but I would like to support
 | exports and static/dynamic wrappers. GHC generates C-code to support
 | them, and GHCJS should generate Javascript-code,
 | but I have no idea how to use GHC API to generate custom (Javascript)
 | stubs. Is it possible at all?

 Well, GHC generates the stub code in its code generator, doesn't it?  If you 
 don't call the code generator, because you are using yours instead, then 
 it'll be up to you to generate the stub code, no?

I can access ForeignStubs datatype, but I think it already have
generated C-code in it, havn't it? What step during compilation I
should generate stubs on?

-- 
Victor Nazarov

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHCJS

2011-08-03 Thread Victor Nazarov
On Wed, Aug 3, 2011 at 8:56 AM, John Lask jvl...@hotmail.com wrote:
 On 3/08/2011 2:10 PM, Brandon Allbery wrote:

 On Wed, Aug 3, 2011 at 00:31, John Laskjvl...@hotmail.com  wrote:

 What is really required is a pluggable back-end infrastructure -
 whereby
 various back-ends could be maintained (or not) at the discretion of their
 originators and separate to the official ghc back-ends.


 I guess I'm confused; I thought the current back-end system *was* that
 kind
 of pluggable architecture.  I recall a JVM backend being proposed based on
 it some time back.


 my thoughts of pluggable infrastructure include consideration of ffi
 bindings and library integration as well as command line options i.e. as
 discussed in this thread with respect of GHC-JS, rather than just backend
 code generation - i.e. considerations of broader scope than those currently
 handled.



Yes, I can enumerate following cosideration when developing non
drop-in replacement for current GHC backend:

* command line support. Developers should be able to emulate ghc and
ghc-pkg to gain cabal support. Another way would be to standatize
compiler command line interface in Cabal and to provide command line
parsing library with it.

* library support. New backend should really behave like stand-alone
compiler, rather then GHC

* ffi support, custom ffi calling conventions and custom format for
call specification, Javascript or JVM will require radically different
call specification then simple function-name as used with C-call.

* cross-compilation. GHCJS doesn't work properly on 64bit systems.
Javascript lacks real integers and we need to emulate them with
Javascript bit-operations. But all javascript bit-operations work with
32 bits. To make Javascript code readable and fast we need to make
Haskell Int type to be 32bit-integer, but it is imposible on 64bit
system.

* Built-in desugaring. Some desugaring provided by GHC is
backend-specific. For instance string literals are desugared into
application of

GHC.unpackCString :: Addr# - String

to some address wich points to '\0' terminated C-string.

In GHCJS we better provide our own desugaring, then add terminating
'\0' to strings to emulate C-string with Javascript-strings.

-- 
Victor Nazarov

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GHCJS

2011-08-02 Thread Victor Nazarov
Hello,

I'm a maintainer and creator of GHCJS tool [1].
GHCJS currently uses GHC API to produce Javascript code from Haskell sources.
There is a great interest to the project, but there have been little
progress recently.
I'm considering the future of it and I'd like to get some advices or
suggestions from GHC maintainers.

GHCJS originally was fork of GHC 6.6 with javascript generation built in.
Since javascript generation is very experimental, I wasn't trying to
push it into GHC mainline.
Besides it was expressed several times [2] that GHC HQ doesn't want to
support another backend
which brings lots of interoperability problems with it.

Since then GHCJS switched to GHC API. For now code generation works
decently well.
But I have many problems that I'd like to solve and I'm not sure if it
is feasible using GHC API,

== Command line interface ==

I'd like to reproduce GHC command line interface for GHCJS tool. For
now I'm using something like this:

main :: IO ()
main =
  do args - getArgs
 defaultErrorHandler defaultDynFlags $ runGhc (Just GHC.Paths.libdir) $
   do sdflags - getSessionDynFlags
  (dflags, fileargs, _) - parseDynamicFlags sdflags (map noLoc args)
  _ - setSessionDynFlags dflags
  let fileargs' = map unLoc fileargs
  targets - mapM (flip guessTarget Nothing) fileargs

This works, but I'm not allowed to parse some custom flags used by
GHCJS code and not by GHC API.
ParseDynamicFlags throws UsageError if it encounters some unknown flags.

What can I do to extend GHC's command line arguments' syntax with some
custom arguments used by GHCJS?

I can parse arguments myself
and throw the rest of them to parseDynamicFlags, but GHC's flags are
really complicated and I'm not aware
of any argument parsing library that can be used to filter out some
specified flags and return the rest GHC's flags untouched.

== Foreign Function Interface ==

What I want is to provide FFI for Javascript, But GHC doesn't allow to
extend FFI declaration syntax.
I'd like to create some new FFI calling convention (javascript) like this:

foreign import javascript alert
  jsalert :: Ptr JSString - IO ()

But GHC always emit parse error on javascript keyword.

For now I'm using (abusing) ccall calling convention and simple
imports works pretty well, but I would like to support
exports and static/dynamic wrappers. GHC generates C-code to support
them, and GHCJS should generate Javascript-code,
but I have no idea how to use GHC API to generate custom (Javascript)
stubs. Is it possible at all?

== Packages support ==

It will be very handy if users can use Cabal to install and build
packages with GHCJS.
It should work if I replicate ghc and ghc-pkg command line interface,
but remaining problem is that
package index and package directories will be shared with GHC,

I'd like to create ghcjs and ghcjs-pkg tools that will use their own
directories and package index and will
not interfere with ghc. Is it possible with GHC API? How can I do it?

[1] https://github.com/sviperll/ghcjs
[2] 
http://www.haskell.org/haskellwiki/GHC:FAQ#Why_isn.27t_GHC_available_for_.NET_or_on_the_JVM.3F

-- 
Victor Nazarov

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: StgExpr AST

2011-02-10 Thread Victor Nazarov
On Thu, Feb 10, 2011 at 1:09 PM, Chris Nicholls
chrisnichol...@gmail.com wrote:
 Hello,

 Is there a way to get access to the STG syntax tree of a program using
 the GHC api? i.e. a function that returns something of type `StgExpr'
 that can be used in a way similar to this:

 example module =
     defaultErrorHandler defaultDynFlags $ do
   runGhc (Just libdir) $ do
     dflags - getSessionDynFlags
     setSessionDynFlags dflags
     target - guessTarget targetFile Nothing
     setTargets [target]
     load LoadAllTargets
     modSum - getModSummary $ mkModuleName module
     p - parseModule modSum
     t - typecheckModule p
     d - desugarModule t
     c - return $ coreModule d
     s - coreToStg c
     return s


I've written Haskell to Javascript translator using GHC API. And I've
ended with the following code to access STG:

https://github.com/sviperll/ghcjs/blob/master/src/Compiler/Main.hs

-- 
Victor Nazarov

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


generating C stubs with GHC API

2010-11-03 Thread Victor Nazarov
I would like to get access to functions exported from Haskell module
and to generate custom stubs for them using GHC API.
As I understand, I need to obtain a list of ForeignDecl's (data
structure defined in HsDecls GHC module) for given source module.
How to achieve this with GHC API?

-- 
Victor Nazarov
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Compiling base with custom compilation script

2010-09-01 Thread Victor Nazarov
I have some custom compilation script that uses GHC API
The aim is to extract some info from every module in dependency graph
and to write this information to the file lying near module-file.
Script goes like this:

main :: IO ()
main =
  do args - getArgs
 defaultErrorHandler defaultDynFlags $ runGhc (Just libdir) $
   do sdflags - getSessionDynFlags
  (dflags, fileargs', _) - parseDynamicFlags sdflags (map noLoc args)
  when (null fileargs') $ ghcError (UsageError No input files.)
  _ - setSessionDynFlags dflags
  let fileargs = map unLoc fileargs'
  targets - mapM (\x - guessTarget x Nothing) fileargs
  setTargets targets
  mgraph - depanal [] False
  let files = filter (not . isSuffixOf boot)
  . map (extractPath . ms_location) $ mgraph
  extractPath l = fromMaybe (ml_hi_file l) (ml_hs_file l)
  setTargets []
  flip mapM_ files $ \file -
do core - compileToCoreSimplified file
   HscTypes.liftIO $
let info = show (generateInfo core)
fp = replaceExtension file .info
putStrLn $ Writing  ++ fp
writeFile fp program

The problem is processing base-4 package. I'd like to run something like:

$ cd base-4.2.0.1
$ compiler -fglasgow-exts -cpp -package-name base -I./include Prelude.hs

and to receive Prelude.info and .info files for every other modules
that prelude depends on.

At first I've got errors like missing .h file. I've downloaded GHC
source distribution and get
missing headers from GHC.

But now I get errors like trying to load Prelude module which is not
loadable. I don't remember the exact text
and I have no access to my developing-machine. I think it's caused by
circular dependencies between modules.
And I think my compilation script is not quite correct for this case.
What do you think?

-- 
Victor Nazarov
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


DataCon workers and wrapers through GHC API

2010-08-24 Thread Victor Nazarov
Is it possible to generate bindings for worker and wrapper of data
constructor through GHC API? How can I do it?
I want CoreBindings or StgBindings for workers and wrappers for all
data constructors of the module...

-- 
Victor Nazarov
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Redefining built in syntax

2008-01-01 Thread Victor Nazarov
On Dec 31, 2007 7:58 PM, Neil Mitchell [EMAIL PROTECTED] wrote:
 Hi,

 I'm getting errors such as:

 C:/Documents/Uni/packages/base/GHC/Base.lhs:270:12:
 Illegal binding of built-in syntax: []

 When I try and compile GHC/Base.lhs using the GHC API. Is there some
 flag I can pass to allow the rebinding of built in syntax?


-package-name base

should do the thing
-- 
vir
http://vir.comtv.ru/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


The order if bindings generated by GHC

2007-11-19 Thread Victor Nazarov
I use STG-bindings generated by GHC during CoreToSTG phase. What is
the order of this bindings is it random or does it correspond to
original source code or does it reflect the dependency structure of
the program?
If I define the following in my program:

data Numeral = Zero | Succ Numeral

zero = Zero
one = Succ zero
...
ten = Succ nine

the order of zero .. ten definition will remain the same, but the
special Zero binding will be generated and added to the end of the
bindings list. But Zero is used by binding of one (strangely enough)
so order doesn't reflect dependency. What is the order of bindings? If
I need the order reflecting dependency, should I sort it myself by SRT
tables or there is an easier way?

-- 
vir
http://vir.comtv.ru/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: The order if bindings generated by GHC

2007-11-19 Thread Victor Nazarov
On Nov 19, 2007 9:39 PM,  [EMAIL PROTECTED] wrote:
 I always - naively - thought that it is a non-problem. How many times have
 I written stuff like that:...

 ping = 0 : pong
 pong = 1 : ping

 It seems that I don't understand the question of Victor Nazarov, nor the
 answer of SPJ...


This is the question about GHC internals, not programing style or smth.
-- 
vir
http://vir.comtv.ru/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


The order if bindings generated by GHC

2007-11-19 Thread Victor Nazarov
  STG syntax: 
 Foo.zero = NO_CCS Foo.Zero! [];
 SRT(Foo.zero): []
 Foo.one = NO_CCS Foo.Succ! [Foo.Zero];
 SRT(Foo.one): []
 Foo.ten = NO_CCS Foo.Succ! [Foo.one];
 SRT(Foo.ten): []
 Foo.Zero = NO_CCS Foo.Zero! [];
 SRT(Foo.Zero): []
 Foo.Succ = \r [eta_s68] Foo.Succ [eta_s68];
 SRT(Foo.Succ): []


In this output the dependecy is as follows:
Foo.zero `depends_on` []
Foo.one  `depends_on` [Foo.Zero] -- this is the source of my question
Foo.ten `depends_on` [Foo.one]
Foo.Zero `depends_on` []
Foo.Succ `depends_on` []

Foo.one here saves the Foo.Zero as an argument of constructor
application, i. e. saves Foo.Zero's address in one of the allocated
closure's field. So I think Foo.Zero must be defined before Foo.one.
--

vir
http://vir.comtv.ru/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Building a prelude

2007-11-07 Thread Victor Nazarov
Is it possible to build Prelude from scratch. Or just some modules
like GHC.Base.

For example when I do
% ghcjs-inplace.bat -fglasgow-exts -fjavascript -cpp -c Err.lhs-boot
% ghcjs-inplace.bat -fglasgow-exts -fjavascript -cpp -c Base.lhs

I've got this error:

Base.lhs:94:0:
Bad interface file: C:/Program Files/Visual Haskell\imports/GHC/Err.hi-boot
Something is amiss; requested module  base:GHC.Err differs from name
found in the interface file main:GHC.Err

What can I do to overcome this.

Really what I want is to build some runtime system for my
ghc-derived-javascript-compiler. And to embed JavaScript integers into
it. I understand that I need to write some primitive operations in
JavaScript like addition. I can build some numerals on the top of
Haskell, but I'd like to get access to underlying javascript features
and integers is a good point to start. Can you recommend me some
strategy or smth?

-- 
vir
http://vir.comtv.ru/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Additional thunk for function

2007-09-21 Thread Victor Nazarov
What is the purpose for GHC to allocate a thunk for some functions?
Why Test.map is not a function, but updatable thunk, which should
become equal to the function just after the first call? Here is the
details:

 % ghc -c test.hs -ddump-stg

  STG syntax: 
 Test.map =
 \u []
   let {
 map1_sdR =
 \r [f_sdN ds_sdI]
 case ds_sdI of wild_sdU {
   [] - [] [];
   : x_sdM xs_sdQ -
   let { sat_sdT = \u [] map1_sdR f_sdN xs_sdQ; } in
   let { sat_sdP = \u [] f_sdN x_sdM; } in  : [sat_sdP 
 sat_sdT];
 };
   } in  map1_sdR;
 SRT(Test.map): []


 % cat test.hs
 module Test where

 map f [] = []
 map f (x:xs) = f x : Test.map f xs

--
Thanks in advance
Victor
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Additional thunk for function

2007-09-21 Thread Victor Nazarov
I have reproduced it on 2 Windows machines with ghc 6.6 and 6.6.1

Here is the version information for ghc used to generate output in
original message.

% ghc -v
Glasgow Haskell Compiler, Version 6.6, for Haskell 98, compiled by GHC
version 6.6
Using package config file: C:\Program Files\Visual Haskell\package.conf
wired-in package base mapped to base-2.0
wired-in package rts mapped to rts-1.0
wired-in package haskell98 mapped to haskell98-1.0
wired-in package template-haskell mapped to template-haskell-2.0
Hsc static flags: -static


-- 
vir
http://vir.comtv.ru/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Additional thunk for function

2007-09-21 Thread Victor Nazarov
Here is some more details:

% ghc -c -ddump-stg T1.hs

 STG syntax: 
T1.map =
\u []
let {
  map1_sdR =
  \r [f_sdN ds_sdI]
  case ds_sdI of wild_sdU {
[] - [] [];
: x_sdM xs_sdQ -
let { sat_sdT = \u [] map1_sdR f_sdN xs_sdQ; } in
let { sat_sdP = \u [] f_sdN x_sdM; } in  : [sat_sdP 
sat_sdT];
  };
} in  map1_sdR;
SRT(T1.map): []


% ghc -c -ddump-stg T1.hs -O

 STG syntax: 
T1.map =
\r [f_sel ds_seg]
case ds_seg of wild_ser {
  [] - [] [];
  : x_sek xs_seo -
  let { sat_seq = \u [] T1.map f_sel xs_seo; } in
  let { sat_sen = \u [] f_sel x_sek; } in  : [sat_sen sat_seq];
};
SRT(T1.map): []
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] GHC 6.7 on Windows / containers-0.1 package?

2007-09-21 Thread Victor Nazarov
 Is this still up-to-date with the way GHC/GHCi work internally? Then
 I'll certainly check it out.

I think it isn't since STG is pretty much different with the G-machine
describes in the book. The original paper about Spineless Tagless
G-machine is here [1].
It is quite verbose. Recent paper How to make a fast curry:
push/enter vs eval/apply [2] is much smaller, but it represents more
recent state of GHC and can be read independently with the first
paper. The book from 1987 [3] is a very good and detailed overview of
the subject and it is valuable as itself, no matter how it actually
implemented now.

--
1. 
https://research.microsoft.com/users/simonpj/papers/spineless-tagless-gmachine.ps.gz
2. https://research.microsoft.com/users/simonpj/Papers/eval-apply/index.htm
3. https://research.microsoft.com/users/simonpj/Papers/slpj-book-1987/index.htm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: STG to JavaScript translation

2007-09-19 Thread Victor Nazarov
I still have some questions regarding the GHC internals.
There is a description of STG language in the Making a Fast Curry:
Push/Enter vs. Eval/Apply for Higher-oder Languages (2004) by Simon
Marlow and Simon Peyton Jones paper. In this description the
constructor application (CONS closure) can only appear on the right
hand side of the bindings. This is totally reasonable if let is the
only construct that allocates objects. But in the GHC's StgSyn.hs any
expression can be constructor application. How does constructor
applications are compiled? Are they implicitly transformed to let?
For example:

f =
  let g = (THUNK h x)
  in (CONS g y)

Is this exactly the same as (right variant following the paper)

f =
  let g = (THUNK h x)
  in let freshvar = (CONS g y)
  in freshvar

?

And the second question is how does constructor tag is passed to case
when non-vector return is used? In register? In constructor closure?
Are there any cases when closure is not build for constructor
application? What the case binder is bound to if there is no closure
for constructor application?

-- 
vir
http://vir.comtv.ru/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


STG to JavaScript translation

2007-09-19 Thread Victor Nazarov
I still have some questions regarding the GHC internals.
There is a description of STG language in the Making a Fast Curry:
Push/Enter vs. Eval/Apply for Higher-oder Languages (2004) by Simon
Marlow and Simon Peyton Jones paper. In this description the
constructor application (CONS closure) can only appear on the right
hand side of the bindings. This is totally reasonable if let is the
only construct that allocates objects. But in the GHC's StgSyn.hs any
expression can be constructor application. How does constructor
applications are compiled? Are they implicitly transformed to let?
For example:

f =
  let g = (THUNK h x)
  in (CONS g y)

Is this exactly the same as (right variant following the paper)

f =
  let g = (THUNK h x)
  in let freshvar = (CONS g y)
  in freshvar

?

And the second question is how does constructor tag is passed to case
when non-vector return is used? In register? In constructor closure?
Are there any cases when closure is not build for constructor
application? What the case binder is bound to if there is no closure
for constructor application?

--
vir
http://vir.comtv.ru/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


STG to JavaScript translation

2007-09-17 Thread Victor Nazarov
Hello.
I'm working on the translation of GHC's STG language to
JavaScript. I've started my implementation, but I've got stuck with
the STG case statements. The problem is the binder in case expression.

StgCase expr livevars liverhsvars bndr srt alttype alts

Operationally, I need to save continuation and evaluate expr
expression, but I have no idea what to do with the bndr. It seems to
me that I need to build a closure binded by bndr with the body of
expr evaluate it, update it, and use it in RHSs of alternatives.
But It seems that this behavior isn't intended by GHC. Can you explain briefly
how GHC implements this binder and what this binder points to.

Here are some notes about Dmitries last year activity and my activity:
http://haskell.org/haskellwiki/STG_in_Javascript

-- 
vir
http://vir.comtv.ru/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users