[Haskell-cafe] Use of abbreviations in Haskell

Thomas DuBuisson thomas.dubuisson at gmail.com
Sat Jan 3 23:11:37 EST 2009


Cafe,
I was going to write about this earlier, but I'm so ill read on the
record selector papers that I deleted the draft.

My proposal would be for each selector name to be a special type of
"phantom" type class (existing in the intermediate language only).
This type class would not be accessible by the programmer and thus
s/he couldn't make a polymorphic function for which specialization
would be needed.  In other words -  in normal circumstances there is
no need for dictionaries and thus no run-time difference between this
method and using different record names.

Example:

> data IPv4Hdr = Hdr4 { src, dst :: IPv4 }
> data IPv6Hdr = Hdr6 { src, dst :: IPv6 }
>
> func4 :: IPv4Hdr -> IO ()
> func4 hdr = do
>     let s = src hdr
>     ...
>
> func6 :: IPv6Hdr -> IO ()
> func6 hdr = do
>     let s = src hdr
>     ...

At some intermediate stage you'd see:

> class Src h s where
>     src :: h -> s
> class Dst h d where
>     dst :: h -> d
>
> instance Src IPv4Hdr IPv4 where
>     src (IPv4 s _) = s
> instance Dst IPv4Hdr IPv4 where
>     dst (IPv4 _ d) = d
> -- repeat for IPv6

The only point of frustration I see is if the programmer manually
makes both data types an instance of a programmer-visible type class,
thus making a polymorphic function.

> class IPHdr a
> instance IPHdr IPv4Hdr
> instance IPHdr IPv6Hdr
>
> sendPing :: (IPHdr a) => a -> IO ()
> sendPing p = networkSend (dst p) pingPayload

In this case I'd vote for specializing the function so there still
aren't any extra dictionaries, but I know that is not always optimal.

Tom

On Sat, Jan 3, 2009 at 10:08 PM, Isaac Dupree
<ml at isaac.cedarswampstudios.org> wrote:
> Ketil Malde wrote:
>> A module may be defined in a file with a name corresponding to the
>> module name, or any dot-separated prefix of it?  I.e. the file
>> Foo/Bar.hs will define module Foo.Bar and optionally Foo.Bar.Baz as
>> well?
>>
>> GHC should then be able to find it, and I believe it already has a
>> prioritized search mechanism (presumably, the file could be named
>> Foo.Bar.hs, too).
>
> I don't think GHC actually allows that (Foo.Bar.hs, ever). But your suggestion
> could work.
>
> 1. Try Foo/Bar/Baz.hs ; if it exists, end search (and error if it does not
> contain Foo.Bar.Baz, obviously as the file's top-level module).
> 2. Try Foo.Bar.hs ; if it exists, end search (and error if it does not contain
> Foo.Bar.Baz, obviously as a sub-module).
> 3. Try Foo.hs ; if it exists, end search (and error if it does not contain
> Foo.Bar.Baz, obviously as a sub-module... or possibly as a sub-sub-module?).
> 4. give up :-)
>
> Note though, that local modules tempt us to a couple other things too, even
> though they're not necessary to the proposal and would complicate it:
> - access-controlled modules (e.g. if other code can't import Foo.Bar.Baz)
> - relative-path imports / module names (e.g. if in Foo/Bar.hs we make Baz and
> try to import it some way with "import Baz")
>
> and as we already mentioned, it would likely involve some implicit importing
> of the sub-module.
>
> translating into ordinary haskell:
> I think my module-search mechanism makes a well-defined, deterministic way to
> find the right module, no complex translation necessary (except layout rule
> madness maybe?).
> Implicit importing: submodule syntax implies adding an "import
> The.Module.Name" line at that point in the containing file.  This would suggest
> that submodules must be at the top, among the imports, because all imports
> must syntactically be at the beginning of the file -- and there's a reason for
> this.  Bother!  Even if the reason is dependency chasing, one would think
> same-file dependencies aren't important, but the submodules themselves can
> import things from other files, so those lines should need to be near the
> beginning anyway.
>
> so an example could be
>
> module MyData
> (
> module MyData.Sub,  -- or equivalently, D(..)
> transform
> )
> where
>
> module MyData.Sub  --or "module Sub" ?? that seems a bit too ad-hoc though
> where
>  data D = E | F
>
> transform :: D -> D
> transform F = E
> transform E = F
>
>
> ~Isaac
>
> _______________________________________________
> 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