[Haskell-beginners] hiding members of a data, separate accessors instead
Gabriel Gonzalez
gabriel439 at gmail.com
Sun Mar 24 21:00:26 CET 2013
On 03/24/2013 12:24 PM, Emmanuel Touzery wrote:
> But then since the library is using (..) that would mean everything is
> exported?
>
It only means that those fields are exported from that specific module.
Downstream modules that use Network.Http.Types internally may or may not
re-export everything.
Your example below doesn't import Network.Http.Types; it imports
Network.Http.Client. If you look at the source for Network.Http.Client
you will see that it does not re-export everything it imported from
Network.Http.Types:
http://hackage.haskell.org/packages/archive/http-streams/0.4.0.0/doc/html/src/Network-Http-Client.html
When you import Network.Http.Client, `ghc` only uses whatever is in the
export list of Network.Http.Client.
> For instance testing on the Request data:
>
> http://hackage.haskell.org/packages/archive/http-streams/0.4.0.0/doc/html/src/Network-Http-Types.html#Request
> module Network.Http.Types (
> Request(..),
> data Request
> = Request {
> qMethod :: !Method,
> qHost :: Maybe ByteString,
> qPath :: !ByteString,
> qBody :: !EntityBody,
> qExpect :: !ExpectMode,
> qHeaders :: !Headers
> }
>
> ----
> {-# LANGUAGE OverloadedStrings #-}
>
> import Network.Http.Client
>
> main = do
> q <- buildRequest $ do
> http GET "/"
> setAccept "text/html"
>
> print q
> print $ qMethod q
>
> ---
>
> test-hs.hs:11:17: Not in scope: `qMethod'
>
> With regards to what Daniel wrote, I realize my email was confusing.
> When I was talking about warnings I was talking of another problem
> entirely, that i probably should not have mentioned in this context.
> In that other context I had data declarations for types that I would
> instanciate only from Data.Aeson parsing from JSON. I would then only
> use pattern matching on the instances, never call the "accessor
> functions" by themselves, then I get a warning that they're unused
> which annoys me. But it's quite unrelated to this mail...
>
> Emmanuel
>
>
>
> On Sun, Mar 24, 2013 at 6:34 PM, Gabriel Gonzalez
> <gabriel439 at gmail.com <mailto:gabriel439 at gmail.com>> wrote:
>
> Assume you have the following type:
>
> data Type = T { field1 :: String, field2 :: Double }
>
> ... and you want to export the type `Type` and the acessors
> `field1` and `field2`, but not the constructor `T`, then you would
> write:
>
> module MyModule (
> Type(field1, field2)
> ) where
>
> Another way to do this is like so:
>
> module MyModule (
> Type,
> field1,
> field2
> ) where
>
> That's perfectly legal, too.
>
> Normally, when you write something like:
>
> module MyModule (
> Type(..)
> ) where
>
> the ".." expands out to:
>
> module MyModule (
> Type(T, field1, field2)
> ) where
>
> All the first solution does is just leave out the T constructor
> from those exports.
>
>
> On 03/24/2013 09:14 AM, Emmanuel Touzery wrote:
>> hi,
>>
>> i was looking at the response type in http-streams:
>> http://hackage.haskell.org/packages/archive/http-streams/0.4.0.0/doc/html/Network-Http-Client.html#t:Response
>>
>> I'm used that simply the data type and all its "members" are
>> visible --
>> the functions to access its contents. But in this case on the HTML
>> documentation the response type looks like it has no members. And the
>> author has defined like "public accessors" later in the code:
>>
>> getStatusCode :: Response -> StatusCode
>> getStatusCode = pStatusCode
>>
>> So I'm not even sure how he achieved that the members are not
>> visible,
>> the data are exported with (..) as is usually done... And the
>> other thing is why
>> would you do that.. You could name the member getStatusCode in
>> the first
>> place, but then it might increase encapsulation to hide it
>> (depending on how he
>> managed to hide the members).. But did you then make
>> it impossible to deconstruct a Response through pattern matching?
>> That
>> sounds like a minus... Although pattern matching on a data with 6
>> fields
>> is always going to be a pain and decreasing the chances for modifying
>> the data type without breaking compatibility.
>>
>> These "members" are also causing me problems in other situations,
>> for instance I have some cases when I use a data type only a few
>> times and with -Wall the compiler tells me I don't use the
>> accessor; in fact I read that value from the data, but through
>> pattern matching/deconstruction only, not through that particular
>> function. I'm thinking to try to hide the warning as I think my
>> code is correct.
>>
>> Anyway I'm curious on the mechanism used by that library... I've
>> already noticed a few nice tricks in this library, like a small
>> state monad to take optional parameters, much more elegant than
>> any other mechanism i've seen so far to achieve the same effect.
>>
>> Thank you!
>>
>> Emmanuel
>>
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners at haskell.org <mailto:Beginners at haskell.org>
>> http://www.haskell.org/mailman/listinfo/beginners
>
>
>
> _______________________________________________
> 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/20130324/7810bb0a/attachment-0001.htm>
More information about the Beginners
mailing list