[Haskell-cafe] Are newtypes optimised and how much?
Simon Peyton-Jones
simonpj at microsoft.com
Wed Oct 20 07:09:39 EDT 2010
| At the end of the day what motivated me to ask these questions it that
| I like very much defining newtypes for most of the types I use, I have
| completely forgotten about `type' aliasing. I'm completely happy to
| write Foo and unFoo all over the place to aid my type correctness, but
| I want a nice generic way to convert to/from newtypes but keeping it a
| compile-time concept. Sometimes I have unThisThat, unTheOther,
| unThoseWhoShantBeNamed, etc. and it I could just use fromIntegral and
| fromString then that would be super.
Yes, you can freely use Foo/unFoo. There's no runtime penalty. (In the jargon of GHC's intermediate language, Foo and unFoo translate to *type-safe casts*, which generate no executable code.
That includes the 'newtype deriving' stuff too, and hence your uses of fromInteger etc.
However, sadly:
| Also, is 'map unFoo' optimised away at compile-time, too? I think that
| it would be compiled to map id. So it would still wrap a thunk around
| each cons. How far does it go?
No, this isn't optimised. The trouble is that you write (map Foo xs), but GHC doesn't know about 'map'. We could add a special case for map, but then you'd soon want (mapTree Foo my_tree).
What you really want is to say is something like this. Suppose my_tree :: Tree String. Then you'd like to say
my_tree ::: Tree Foo
meaning "please find a way to convert m_tree to type (Tree Foo), using newtype coercions.
The exact syntax is a problem (as usual). We have the technology now. The question is how important it is.
Simon
| -----Original Message-----
| From: haskell-cafe-bounces at haskell.org [mailto:haskell-cafe-bounces at haskell.org]
| On Behalf Of Christopher Done
| Sent: 19 October 2010 19:12
| To: Haskell Cafe
| Subject: [Haskell-cafe] Are newtypes optimised and how much?
|
| So I have the following nice things:
|
| {-# LANGUAGE GeneralizedNewtypeDeriving, OverloadedStrings #-}
|
| import Data.String
|
| newtype Foo = Foo { unFoo :: String } deriving (IsString)
|
| x :: Foo
| x = "Hello, World!"
|
| newtype Bar = Bar { unBar :: Integer } deriving
| (Eq,Show,Num,Integral,Real,Enum,Ord)
|
| y :: Bar
| y = 2
|
| I can write literals and they will be converted to the type I wanted
| with no extra verbiage needed.
|
| Questions (I'm talking about GHC when I refer to compilation):
|
| (1) Are fromString and fromIntegral ran at compile time? I don't think
| that this is the case. I think they are just translated to fromString
| "Hello, World!" and fromIntegral 2 verbatim.
| (2) Regardless of this, the implementation of fromString and
| fromIntegral is essentially a no-op, it's just fromString = Foo,
| fromIntegral = Bar, which is in turn essentially fromString = id,
| fromIntegral = id, as far as I understand it. It's purely compile
| time. But supposing I write:
|
| fromIntegral (fromIntegral (2::Integer) :: Bar) :: Integer
|
| Is this at the end of the day equal to just (2::Integer)? Thinking
| simple-mindedly, I would say, yes. The compiler knows that
| fromIntegral :: Integer -> Bar == id, and that fromIntegral :: Bar ->
| Integer == id (right?). But is that the case? Perhaps the type class
| methods have some dictionary and thus cannot be inlined, or maybe that
| doesn't matter?
|
| At the end of the day what motivated me to ask these questions it that
| I like very much defining newtypes for most of the types I use, I have
| completely forgotten about `type' aliasing. I'm completely happy to
| write Foo and unFoo all over the place to aid my type correctness, but
| I want a nice generic way to convert to/from newtypes but keeping it a
| compile-time concept. Sometimes I have unThisThat, unTheOther,
| unThoseWhoShantBeNamed, etc. and it I could just use fromIntegral and
| fromString then that would be super.
|
| Also, is 'map unFoo' optimised away at compile-time, too? I think that
| it would be compiled to map id. So it would still wrap a thunk around
| each cons. How far does it go?
|
| So, if I go around using fromIntegral/fromString (etc. for other
| newtype types), is it still kept compile time? After having newtypes
| catch dozens of type mismatches that otherwise wouldn't unified
| happily but were completely wrong (e.g. wrong argument order), I've
| found newtype to be an indispensable part of Haskell and of writing a
| large piece of software.
|
| Cheers
| _______________________________________________
| Haskell-Cafe mailing list
| Haskell-Cafe at haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list