GHCJS

Victor Nazarov asviraspossible at gmail.com
Thu Aug 4 11:34:20 CEST 2011


On Wed, Aug 3, 2011 at 2:44 PM, Simon Marlow <marlowsd at gmail.com> wrote:
> On 03/08/2011 11:09, Victor Nazarov wrote:
>>
>> On Wed, Aug 3, 2011 at 11:30 AM, Simon Peyton-Jones
>> <simonpj at 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



More information about the Glasgow-haskell-users mailing list