Correct.  And when dealing with an imported DataCon, it must slavishly follow the decisions taken in the defining module

 

S

 

From: Johan Tibell [mailto:johan.tibell@gmail.com]
Sent: 11 January 2015 22:27
To: Simon Peyton Jones
Cc: ghc-devs@haskell.org
Subject: Re: Clarification of HsBang and isBanged

 

Yet more questions.

 

I think I'm on the wrong track. I was trying to change MkId.dataConArgRep in order to make user-defined fields get the right strictness. However, some debug tracing suggests that this function isn't used (or isn't only used) to compute the strictness and "unpackedness" of a data constructor defined in the module being compiled, but also for modules being imported. Is that correct?

 

The code (including tests) is here: https://github.com/ghc/ghc/compare/601e345e5df6%5E...1cee34c71e80

 

The parser changes I'm making seem to not be quite right. I've changed the strict_mark parser in Parser.y to read:

 

    strict_mark :: { Located ([AddAnn],HsBang) }

            : '!'                        { sL1 $1    ([],            HsSrcBang Nothing      (Just True)) }

            | '~'                        { sL1 $1    ([],            HsSrcBang Nothing      (Just False)) }

            | '{-# UNPACK' '#-}'         { sLL $1 $> ([mo $1,mc $2], HsSrcBang (Just True)  Nothing) }

            | '{-# NOUNPACK' '#-}'       { sLL $1 $> ([mo $1,mc $2], HsSrcBang (Just False) Nothing) }

            | '{-# UNPACK' '#-}' '!'     { sLL $1 $> ([mo $1,mc $2], HsSrcBang (Just True)  (Just True)) }

            | '{-# NOUNPACK' '#-}' '!'   { sLL $1 $> ([mo $1,mc $2], HsSrcBang (Just False) (Just True)) }

            | '{-# UNPACK' '#-}' '~'     { sLL $1 $> ([mo $1,mc $2], HsSrcBang (Just True)  (Just False)) }

            | '{-# NOUNPACK' '#-}' '~'   { sLL $1 $> ([mo $1,mc $2], HsSrcBang (Just False) (Just False)) }

            -- Although UNPACK with no '!' and UNPACK with '~' are illegal, we get a

            -- better error message if we parse them here

 

but parsing this data type

 

    data Lazy a = L ~a

 

gives this error

 

    DsStrictData.hs:14:1:

        parse error (possibly incorrect indentation or mismatched brackets)

 

-- Johan

 

 

On Sun, Jan 11, 2015 at 8:11 PM, Johan Tibell <johan.tibell@gmail.com> wrote:

Yet another one. TcSplice.reifyStrict doesn't take the unboxing flags into account either. Should it?

 

    reifyStrict :: DataCon.HsSrcBang -> TH.Strict

    reifyStrict HsNoBang                     = TH.NotStrict

    reifyStrict (HsSrcBang _ False)          = TH.NotStrict

    reifyStrict (HsSrcBang (Just True) True) = TH.Unpacked

    reifyStrict (HsSrcBang _     True)       = TH.IsStrict

    reifyStrict HsStrict                     = TH.IsStrict

    reifyStrict (HsUnpack {})                = TH.Unpacked

 

Should

 

    reifyStrict (HsSrcBang _     True)       = TH.IsStrict

 

be TH.Unpacked if we have -funbox-strict-fields?

 

On Sun, Jan 11, 2015 at 6:28 PM, Johan Tibell <johan.tibell@gmail.com> wrote:

Those comments and the renaming really help. Here are a couple of more questions I got after exploring some more:

 

DsMeta.repBangTy look wrong to me:

 

    repBangTy :: LBangType Name -> DsM (Core (TH.StrictTypeQ))

    repBangTy ty= do

      MkC s <- rep2 str []

      MkC t <- repLTy ty'

      rep2 strictTypeName [s, t]

      where

        (str, ty') = case ty of

                       L _ (HsBangTy (HsSrcBang (Just True) True) ty) -> (unpackedName,  ty)

                       L _ (HsBangTy (HsSrcBang _     True) ty)       -> (isStrictName,  ty)

                       _                                              -> (notStrictName, ty)

 

Shouldn't the second case look at whether -funbox-strict-fields or -funbox-small-strict-fields is set and use unpackedName instead of isStrictName if so? What is repBangTy for?

 

A related question, in MkId.dataConArgRep we have:

 

    dataConArgRep _ _ arg_ty HsStrict

      = strict_but_not_unpacked arg_ty

 

Here we're not looking at -funbox-strict-fields and -funbox-small-strict-fields. Is it the case that we only need to look at these flags in the case of HsSrcBang, because HsStrict can only be generated by us (and we presumably looked at the flags when we converted a HsSrcBang to a HsStrict)?

 

On Thu, Jan 8, 2015 at 4:09 PM, Simon Peyton Jones <simonpj@microsoft.com> wrote:

I’m glad you are getting back to strictness.

 

Good questions.

 

I’ve pushed (or will as soon as I have validated) a patch that adds type synonyms, updates comments (some of which were indeed misleading), and changes a few names for clarity and consistency.  I hope that answers all your questions.

 

Except these:

 

·         Why is there a coercion in `HsUnpack` but not in `HsUserBang (Just True) True`?  Because the former is implementation generated but the latter is source code specified.

·         Why isn't this information split over two data types.  Because there’s a bit of overlap. See comments with HsSrcBang

 

Simon

 

From: Johan Tibell [mailto:johan.tibell@gmail.com]
Sent: 08 January 2015 07:36
To: ghc-devs@haskell.org
Cc: Simon Peyton Jones
Subject: Clarification of HsBang and isBanged

 

HsBang is defined as:

    -- HsBang describes what the *programmer* wrote

    -- This info is retained in the DataCon.dcStrictMarks field

    data HsBang

      = HsUserBang   -- The user's source-code request

           (Maybe Bool)       -- Just True    {-# UNPACK #-}

                              -- Just False   {-# NOUNPACK #-}

                              -- Nothing      no pragma

           Bool               -- True <=> '!' specified

 

      | HsNoBang              -- Lazy field

                              -- HsUserBang Nothing False means the same as HsNoBang

 

      | HsUnpack              -- Definite commitment: this field is strict and unboxed

           (Maybe Coercion)   --    co :: arg-ty ~ product-ty

 

      | HsStrict              -- Definite commitment: this field is strict but not unboxed


This data type is a bit unclear to me:

 * What are the reasons for the following constructor overlaps?
   * `HsNoBang` and `HsUserBang Nothing False`
   * `HsStrict` and `HsUserBang Nothing True`
   * `HsUnpack mb_co` and `HsUserBang (Just True) True`


* Why is there a coercion in `HsUnpack` but not in `HsUserBang (Just True) True`?

 

* Is there a difference in what the user wrote in the case of HsUserBang and HsNoBang/HsUnpack/HsStrict e.g are the latter three generated by the compiler as opposed to being written by the user (the function documentation notwithstanding)?

A very related function is isBanged:

    isBanged :: HsBang -> Bool

    isBanged HsNoBang                  = False

    isBanged (HsUserBang Nothing bang) = bang

    isBanged _                         = True

 

What's the meaning of this function? Is it intended to communicate what the user wrote or whether result of what the user wrote results in a strict function?


Context: I'm adding a new StrictData language pragma [1] that makes fields strict by default and a '~' annotation of fields to reverse the default behavior. My intention is to change HsBang like so:

    -       Bool               -- True <=> '!' specified
    +       (Maybe Bool)       -- True <=> '!' specified, False <=> '~'
    +                          -- specified, Nothing <=> unspecified

1. https://ghc.haskell.org/trac/ghc/wiki/StrictPragma


-- Johan