[Haskell-beginners] Re: Advice wanted on parallel processing
Daniel Fischer
daniel.is.fischer at web.de
Wed Mar 18 12:11:25 EDT 2009
Am Mittwoch, 18. März 2009 16:49 schrieb Colin Paul Adams:
> >>>>> "Daniel" == Daniel Fischer <daniel.is.fischer at web.de> writes:
>
> Daniel> If e.g.
>
> Daniel> data Move = Move {from :: Position, to :: Position}
>
> Daniel> , the instance would be
>
> Daniel> instance NFData Move where rnf (Move f t) = rnf f `seq`
> Daniel> rnf t `seq` ()
>
> Daniel> That might require NFData instances for Position and its
> Daniel> components, but specifying these should be automatic.
>
> <switched to beginners list>
>
> Move is somewhat more complicated than that, but it comes down to
> specifying instances for
>
> data Piece_colour
> = Black
>
> | White
>
> and
>
> data Piece_type
> = Lance
>
> | Reverse_chariot
> | Side_mover
> | Vertical_mover
> | White_horse
> | Rook
>
> ... many more
>
> which I'm not sure how to do. I tried added a deriving clause, but the
> compiler complains:
>
> Can't make a derived instance of `NFData Piece_colour'
> (`NFData' is not a derivable class)
> In the data type declaration for `Piece_colour'
For a newtype-wrapper of a type which is an instance of NFData, you can do
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
newtype Thing = T nfdata
deriving NFData
, but for
data Thingummy = ...
you have to write the instance yourself.
>
> here I don't have and fields to force.
For an enumeration like Piece_colour or Piece_type,
instance NFData Piece_colour where
rnf = rwhnf
is all you need, but you don't even necessarily need that, for
data Move = Move {colour :: Piece_colour, typ :: Piece_type, start, end ::
Position}
instance NFData Move where
rnf (Move c t s e) = c `seq` t `seq` rnf s `seq` rnf e
is good.
More information about the Beginners
mailing list