[Hs-Generics] Proposal #2875: Correct SYB's representation of Char

Neil Mitchell ndmitchell at gmail.com
Thu Dec 11 10:16:29 EST 2008


Hi,

I agree with the idea. However, remember that this won't be fully
backwards compatible as anyone who performs a pattern match will now
get a crash. Given that, I think I'd be more in favour of renaming
StringRep to CharRep in one single step, otherwise you are going to
allow the old code to compile fine and crash at runtime. Having
mkStringRep be deprecated is a good idea though.

Thanks

Neil



On Thu, Dec 11, 2008 at 3:06 PM, José Pedro Magalhães <jpm at cs.uu.nl> wrote:
> Hello all,
>
> SYB uses DataRep to represent datatypes:
>
>     -- | Public representation of datatypes
>     data DataRep = AlgRep [Constr]
>                  | IntRep
>                  | FloatRep
>                  | StringRep
>                  | NoRep
>
> I believe that StringRep should be CharRep. Note that IntRep is used for the
> primitive Int and Integer datatypes, FloatRep for Float and Double, and
> StringRep (apparently) for Char. String, however, is represented as AlgRep
> [[],(:)]:
>
>     *Main> dataTypeOf 'p'
>     DataType {tycon = "Prelude.Char", datarep = StringRep}
>     *Main> dataTypeOf "p"
>     DataType {tycon = "Prelude.[]", datarep = AlgRep [[],(:)]}
>
> This makes sense, since String is not a primitive datatype. But it causes
> the apparently wrong behavior:
>
>     *Main> fromConstr (mkStringConstr (dataTypeOf "a") "ab") :: String
>     "*** Exception: mkStringConstr
>     *Main> fromConstr (mkStringConstr (dataTypeOf 'a') "ab") :: String
>     "*** Exception: constrIndex
>
> The correct way of using mkStringConstr is to construct a Char. This,
> however, only works for strings with a single character:
>
>     *Main> fromConstr (mkStringConstr (dataTypeOf 'a') "b")  :: Char
>     'b'
>     *Main> fromConstr (mkStringConstr (dataTypeOf 'a') "ab") :: Char
>     *** Exception: gunfold
>     *Main> fromConstr (mkStringConstr (dataTypeOf 'a') "")   :: Char
>     *** Exception: gunfold
>
> I find this behavior counterintuitive. Therefore I propose to rename
> StringRep to CharRep and mkStringConstr to mkCharConstr. For backwards
> compatibility, this entails:
>
>     * Deprecating mkStringConstr and StringConstr
>     * Deprecating mkStringRep and StringRep
>     * Introducing mkCharConstr and CharConstr
>     * Introducing mkCharRep and CharRep
>
> Additionally, due to deprecation warnings, the following have to change as
> well:
>
>     * libraries/template-haskell/Language/Haskell/TH/Quote.hs
>     * compiler/utils/Serialized.hs
>
> A patch is attached in #2875
> (http://hackage.haskell.org/trac/ghc/ticket/2875). I propose a discussion
> period of 4 weeks, therefore until the 8th of January.
>
>
> Thanks,
> Pedro
>
> _______________________________________________
> Generics mailing list
> Generics at haskell.org
> http://www.haskell.org/mailman/listinfo/generics
>
>


More information about the Libraries mailing list