[Haskell-beginners] Associated data type confusion

Alex Hammel ahammel87 at gmail.com
Mon Jan 12 21:35:11 UTC 2015


Awesome, that did the trick! I think I need a bit more practice with 'type
functions' before I'm really comfortable with them.

Thanks a lot!

Cheers,
Alex

On Mon, Jan 12, 2015 at 12:39 PM, Michael Orlitzky <michael at orlitzky.com>
wrote:

> On 01/12/2015 02:25 PM, Alex Hammel wrote:
> > Hello list,
> >
> > I've got a collection of types which come from generated code (it's
> > protocol buffer stuff). I'd like to write a polymorphic function which
> > maps the protocol buffer generated data types to native data types. I've
> > tried something like this:
> >
>
> This should get you started. My ProtoBool and ProtoInt types are just
> dumb wrappers -- your conversions will be more complicated. But this
> will compile and run in ghci:
>
>   ghci> toProto (3::Int)
>   ProtoInt {mkProtoInt = 3}
>
>   ghci> toProto True
>   ProtoBool {mkProtoBool = True}
>
>
> If the toProto and fromProto definitions look goofy in the instances
> it's because they're in point-free style. You could just as well have e.g.,
>
>     toProto b = ProtoBool b
>
> or,
>
>   fromProto i = mkProtoInt i
>
>
> ----
>
> {-# LANGUAGE TypeFamilies #-}
>
> module Proto
> where
>
> -- | Just a wrapper around a 'Bool'.
> newtype ProtoBool = ProtoBool { mkProtoBool :: Bool } deriving (Show)
>
> -- | Just a wrapper around an 'Int'.
> newtype ProtoInt  = ProtoInt { mkProtoInt :: Int } deriving (Show)
>
>
> class ToFromProto a where
>     -- | The type 'a' has another type associated with it, the
>     --   "protocol buffer type" that we can convert to/from. 'Proto'
>     --   below is a type function which when applied to 'a' should
>     --   return this associated type.
>     type Proto a :: *
>
>     toProto :: a -> (Proto a)
>     fromProto :: (Proto a) -> a
>
> instance ToFromProto Bool where
>   -- | The type associated with 'Bool' is 'ProtoBool'
>   type Proto Bool = ProtoBool
>
>   -- | How do we make a 'ProtoBool' from a 'Bool'? Just wrap it.
>   toProto = ProtoBool
>
>   -- | How do we get a 'Bool' From a 'ProtoBool'? Unwrap it.
>   fromProto = mkProtoBool
>
>
> -- | The same for 'Int' and 'ProtoInt'.
> instance ToFromProto Int where
>   type Proto Int = ProtoInt
>   toProto = ProtoInt
>   fromProto = mkProtoInt
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20150112/da8519e6/attachment.html>


More information about the Beginners mailing list