ghci: catching up with hugs?-)
Claus Reinke
claus.reinke at talk21.com
Thu Jul 29 12:48:26 EDT 2004
Having mostly been converted from hugs to ghci (due to working
with too large programs or libraries more readily supported there),
I've come to find it quite indispensible for Haskell development.
However, there are a few corners where I still miss Hugs functionality
that doesn't seem to be available in ghci, and I wonder whether there
are any plans to remedy this (or whether there are any fundamental
obstacles):
- especially when working with gui libs, I often find myself wanting to
know which instances some type belongs to (as that determines the
attributes/properties/etc one may use with that type).
in hugs, a simple ":info <type>" gives me the answer:
Prelude> :info Bool
-- type constructor
data Bool
-- constructors:
False :: Bool
True :: Bool
-- instances:
instance Eq Bool
instance Ord Bool
instance Ix Bool
instance Enum Bool
instance Read Bool
instance Show Bool
instance Bounded Bool
in fact, I can even ask by class, using ":info <class>":
Prelude> :i Enum
-- type class
class Enum a where
succ :: a -> a
pred :: a -> a
toEnum :: Int -> a
fromEnum :: a -> Int
enumFrom :: a -> [a]
enumFromThen :: a -> a -> [a]
enumFromTo :: a -> a -> [a]
enumFromThenTo :: a -> a -> a -> [a]
-- instances:
instance Enum ()
instance Enum Char
instance Enum Int
instance Enum Integer
instance Enum Float
instance Enum Double
instance Integral a => Enum (Ratio a)
instance Enum Bool
instance Enum Ordering
in ghci, such useful info seems absent, and I find myself hunting
the haddocs. shouldn't ghci be able to provide this info as well?
- since ghc now keeps better source location info, how about ":find <name>"?
in hugs, that calls a configurable external command (usually an editor)
with the filename and linenumber of <name>'s definition. this is very
useful, even more so for Haskell IDEs that communicate with hugs to
implement "jump to definition" instead of relying on outdated or non-
existent tag files.
in ghci, that could simply pass filename and linenumber to a configurable
Haskell function (:: String -> Int -> IO ()) - well, if we have the source code..
so we need an indication of whether ghci knows where to find the source,
and if not, we need the package and full hierarchical module and item name,
so that the user-supplied "find" function could eg. try to open the
corresponding haddoc entry if the source is not available, before giving
up. simplified example:
myfind :: Maybe (FilePath,Int) -> (String,String) -> IO ExitCode
myfind (Just (filepath,line)) _ =
system $ editor++" +"++show line++" "++filepath
myfind Nothing (package,mp) =
system $ browser++" "++haddocBase++sep++package++sep++mp++".html"
:set find myfind
:find MVar
-- goes off to open "<somewhere>\base\Control.Concurrent.MVar.html"
[ghci already offers source location information as part of ":info", *if* it
has seen the source code; I'm just asking for a more convenient interface,
as well as infomation in the common case of no source code]
- the ":set <something>" command in ghci "feeds" the ghc command line, but how
can I figure out the current settings (especially paths and packages)?
in hugs ":set" would list all settings; in ghci that doesn't seem to happen.
Especially the first two (instance info and configurable source/doc link
would help me with frequently recurring work patterns during Haskell
code development.
Cheers,
Claus
More information about the Glasgow-haskell-users
mailing list