module Element where
import QName
import ...
data Element = Element {name :: QName, attribs :: [Attr], content ::
[Content], line :: Maybe Line}
module Attr where
import QName
import ...
data Attr = Attr {key :: QName, val :: String}
module QName where
import ...
data QName = QName {name :: String, uri :: Maybe String, prefix ::
Maybe String}
module Main where
import qualified QName as Q
import qualified Element as E
... Q.name ... E.name ...
On 2 Jan 2009, at 17:20, Felix Martini wrote:
Hi all,
There is currently a discussion on reddit/programming about Haskell.
One complaint is that Haskell functions often use abbreviated names. I
tend to agree with that. In my personal experience it generally takes
more time to learn a third party Haskell library than libraries
written in other languages. I am not sure why but it could be because
of function names. It seems to me that Haskell's current record syntax
enhances this. Take for example the new xml library,
data Element = Element {
elName :: QName
elAttribs :: [Attr]
elContent :: [Content]
elLine :: Maybe Line
}
data Attr = Attr {
attrKey :: QName
attrVal :: String
}
data QName = QName {
qName :: String
qURI :: Maybe String
qPrefix :: Maybe String
}
Personally i would prefer it to be something like
data Element = Element {
name :: QualifiedName
attributes :: [Attribute]
content :: [Content]
line :: Maybe Line
}
data Attribute = Attribute {
key :: QualifiedName
value :: String
}
data QualifiedName = QualifiedName {
name :: String
uri :: Maybe String
prefix :: Maybe String
}
but the global scope of the record field names doesn't allow that and
therefore all kinds of abbreviations are inserted in front of the
record field names which are hard to remember. So a better record
syntax would be welcome. Perhaps the constructor could be used to
limit the scope of the record field name e.g. QualifiedName.prefix?
Regards,
Felix
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe