[Hs-Generics] RE: Generics

José Pedro Magalhães jpm at cs.uu.nl
Thu Dec 11 03:53:48 EST 2008


Hello Neil,

On Thu, Dec 11, 2008 at 09:49, Neil Mitchell <ndmitchell at gmail.com> wrote:

> Hi Pedro,
>
> >> I'm not sure there is a nice solution - reflection at the type level
> >> (using _|_ at the value level), combined with strictness at the value
> >> level, has limitations. It may be that the reflection machinery in SYB
> >> can be tweaked to either alert the user in advance (i.e. by getting
> >> the strictness of various fields), or providing some operation
> >> combining gmapQ and fromConstr which isn't strict. To see my use case
> >> take a look at "contains" in:
> >>
> >> http://www.cs.york.ac.uk/fp/darcs/uniplate/Data/Generics/PlateData.hs
> >
> > I'm not sure there's an easy solution either. As you say, the problem
> here
> > seems to be caused by the strictness. Getting the strictness of each
> field
> > would require changes to the representation types and to the deriving
> > mechanism.
> >
> > Would your problem be solved if you used fromConstrB instead of simply
> > fromConstr and built an entirely determined (without bottoms) value?
>
> I might be able to use fromConstrB, but it requires a lot more work -
> initialising lots of things and creating lots of dummy values. I'll
> look into it.


Would this help?

{-# LANGUAGE ScopedTypeVariables  #-}
> {-# LANGUAGE FlexibleContexts     #-}
>
> module Data.Generics.Builders (empty) where
>
> import Data.Data
> import Data.Generics.Aliases (extB)
>
> -- | Construct the empty value for a datatype. For algebraic datatypes, the
> -- leftmost constructor is chosen.
> empty :: forall a. Data a => a
> empty = general
>       `extB` char
>       `extB` int
>       `extB` integer
>       `extB` float
>       `extB` double where
>   -- Generic case
>   general :: Data a => a
>   general = fromConstrB empty (indexConstr (dataTypeOf general) 1)
>
>   -- Base cases
>   char    = '\NUL'
>   int     = 0      :: Int
>   integer = 0      :: Integer
>   float   = 0.0    :: Float
>   double  = 0.0    :: Double
>



>
> I also note that the documentation for fromConstrB seems to have
> disappeared. See:
> http://haskell.org/ghc/docs/latest/html/libraries/syb/doc-index.html -
> the entry is still there but the link is gone.


fromConstrB is not in the syb package. It's in base4, in Data.Data:
http://www.haskell.org/ghc/dist/stable/docs/libraries/base/Data-Data.html#v%3AfromConstrB


Thanks,
Pedro


>
>
> (I'm also aware that the Hoogle documentation for it is missing, but
> hope to fix that this weekend - I've had issues trying to build
> things)
>
> Thanks
>
> Neil
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/generics/attachments/20081211/7e57b321/attachment-0001.htm


More information about the Generics mailing list