Useful IDE features - What abaut automatically adding import statements?

Eclipse does have this which saves you a lot of time: Fix imports. Did I miss anyone mentioning such a feature request? Or is there already a solution around ? Marc Weber

On Sun, Jun 17, 2007 at 10:58:04AM +0100, David House wrote:
Marc Weber writes:
Eclipse does have this which saves you a lot of time: Fix imports.
Could you describe the semantics of that more precisely?
You get the error: Not in scope 'c' and the IDE should figure out automatically which used packages have modules exporting c. Then it should ask wether you want import one of those modules and add the module to the import list. Marc

Hi
It's one of the features I want to add to GuiHaskell
(http://www-users.cs.york.ac.uk/~ndm/guihaskell/). Once the main code
base is finished, things like this should be relatively easy.
Thanks
Neil
On 6/17/07, Marc Weber
On Sun, Jun 17, 2007 at 10:58:04AM +0100, David House wrote:
Marc Weber writes:
Eclipse does have this which saves you a lot of time: Fix imports.
Could you describe the semantics of that more precisely?
You get the error: Not in scope 'c'
and the IDE should figure out automatically which used packages have modules exporting c. Then it should ask wether you want import one of those modules and add the module to the import list.
Marc _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Eclipse does have this which saves you a lot of time: Fix imports.
Could you describe the semantics of that more precisely?
You get the error: Not in scope 'c'
and the IDE should figure out automatically which used packages have modules exporting c. Then it should ask wether you want import one of those modules and add the module to the import list.
in my vim setup, i can hit '_i' (import) or '_im' (import module) on an identifier to get a menu of modules from which it could be imported; selecting an entry adds an import to the current module, either for the identifier only, or for the whole module it comes from (this feature gets its information from haddock's indices of the standard hierarchical libs, so it is currently limited to identifiers found there) . combined with quickfix mode, which will jump to the identifier not in scope, this seems to be quite close to what you ask for? http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/Vim/ [while useful, it doesn't check for existing imports, and it relies on ghc --make/--interactive to find the packages holding the modules] there's also '_.' which will use the same data to suggest possible fully qualified identifiers for the id under cursor. claus ps HaRe also had some transformations for manipulating imports/exports. http://www.cs.kent.ac.uk/projects/refactor-fp/hare.html

in my vim setup, i can hit '_i' (import) or '_im' (import module) on an Great. To late ;( I've now implemented this as well. My setup is getting the information
On Sun, Jun 17, 2007 at 03:39:25PM +0100, Claus Reinke wrote: directly from the installed packages (thus ghc-pkg describe package and then ghc -show-iface eachmodule.hi) Because I use caching it should be reasonable fast ? (I hope so, I still have to do some testing) The used packages are taken from the cabal file (and / or buffer setting)
identifier to get a menu of modules from which it could be imported; selecting an entry adds an import to the current module, either for the identifier only,
import Foo (a) add identifier b results in import Foo (a,b) ? or for the whole module it comes from (this feature
gets its information from haddock's indices I'm using tags and the plain source file most of the time. So I don't have trouble generating haddock documentation. I think its easy but I haven't spent much time on this. It contains all, the documentation and the implementation.
combined with quickfix mode, which will jump to the identifier not in scope, this seems to be quite close to what you ask for? I'll let you know when having finished the quickfix integration. Perhaps this can be done all automatically? http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/Vim/ there's also '_.' which will use the same data to suggest possible fully qualified identifiers for the id under cursor. This might be useful, too
HaRe also had some transformations for manipulating imports/exports. http://www.cs.kent.ac.uk/projects/refactor-fp/hare.html I don't know HaRe at all. Would this even work when working with #ifdef etc?
I'd like to have some features, such as _T .. But this only works if the file can be parsed by ghc, right? Thanks for your suggestion. Marc Weber

I've now implemented this as well. My setup is getting the information directly from the installed packages (thus ghc-pkg describe package and then ghc -show-iface eachmodule.hi) Because I use caching it should be reasonable fast ? (I hope so, I still have to do some testing) The used packages are taken from the cabal file (and / or buffer setting)
the more, the merrier!-) yes, caching is essential (reading in a huge dictionary is fast, creating it is not). getting the info from ghc-pkg would be preferable, and i do actually keep two dictionaries, one from haddock, one from ghci's :browse. but there seems to be a lot of internal info in the output of --show-iface, is that useable? extracting the information from haddock indices was the most-likely-to-work approach at the time.. linking editing sessions to .cabal files is still on my todo list;-)
import Foo (a)
add identifier b results in import Foo (a,b)
?
currently, i get: import Foo (a) import Foo (b) which is one reason why i'd like to take existing imports into account in some future version.
or for the whole module it comes from (this feature
gets its information from haddock's indices I'm using tags and the plain source file most of the time.
yes, tags and sources are used for some features, but the standard libs simply have no sources in the default installations.
So I don't have trouble generating haddock documentation. I think its easy but I haven't spent much time on this. It contains all, the documentation and the implementation.
i'm not generating haddocks, just extracting information from them.
combined with quickfix mode, which will jump to the identifier not in scope, this seems to be quite close to what you ask for? I'll let you know when having finished the quickfix integration.
basic quickfix settings for ghc seem fairly straightforward, see http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/Vim/vimfiles/compi...
HaRe also had some transformations for manipulating imports/exports. http://www.cs.kent.ac.uk/projects/refactor-fp/hare.html I don't know HaRe at all. Would this even work when working with #ifdef etc?
i don't recall whether we tried to do anything about preprocessors, probably not. also, preprocessor directives are mostly used to work around language differences, and none but the haskell 98 branch would be useable with HaRe.
I'd like to have some features, such as _T .. But this only works if the file can be parsed by ghc, right?
yes. both '_t' and '_T' simply use ghci's :t (:s is also available via '_si'). claus

I'd like to have some features, such as _T .. But this only works if the file can be parsed by ghc, right?
yes. both '_t' and '_T' simply use ghci's :t (:s is also available via '_si').
actually, that was only in early versions. these days, GHC.vim lists the imports, uses 'ghc -e :browse ..' on each import, and caches the results in a dictionary, which is used both for one of the completions, and for '_t'/'_T'. claus

Another feature which would be cool for an IDE is: "implement instance". So you automatically get to see all the functions of a type class you need to implement. Using C#/Java, this is used all over the place. No virus found in this outgoing message. Checked by AVG Free Edition. Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007 08:23

Another feature which would be cool for an IDE is: "implement instance". So you automatically get to see all the functions of a type class you need to implement. Using C#/Java, this is used all over the place.
sounds potentially useful, but perhaps not quite as useful as one might expect: if you only want to see all the class methods, hugs/ghci provide the ':info' command (and haskell modes tend to provide access to that). $ ghc -e ':i Monad' class Monad m where (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b return :: a -> m a fail :: String -> m a -- Defined in GHC.Base instance Monad Maybe -- Defined in Data.Maybe instance Monad IO -- Defined in GHC.IOBase instance Monad [] -- Defined in GHC.Base with a little bit of filtering and replacing, we get $ ghc -e ':i Monad' | sed -n '/^class/,/-- Defined in/{s/class/instance/;p}' instance Monad m where (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b return :: a -> m a fail :: String -> m a -- Defined in GHC.Base i've used sed here, to keep it editor-independent, one can do the equivalent within emacs/vim, without sed. now, if one wanted to save typing, one might want to translate the type declarations into definition templates, but the type has more information than such template, and there are many forms of definition that fit a type, so having to replace the type declarations with definitions is perhaps as good as it gets? a similarly useful code template generation transformation would be to introduce complete case distinctions over sum types, so that f x = undefined would, if we knew (x::Maybe a), become f (Just a) = undefined f Nothing = undefined or 'doSomething >>= \(x::Either l r)->body' would become doSomething >>= \x->case x of {Left l->body; Right r->body} which, of course, should rather be doSomething >>= either (\l->body) (\r->body) yes, there are many opportunities for making haskell editing easier, and not all of them require detailed editor hacking or haskell analysis and transformation skills (though some do). keep the suggestions coming. perhaps summarize them on a haskell.org wiki page, though, so they don't get lost. someone might get round to implementing them, some of them might already be available!-) if someone were to put up a simple table/list of desired ide features (with brief descriptions) on the wiki, everyone could add links to each feature showing how their favourite ide handles said feature. then new users could go through that list and choose to learn one of those ides that provides most of the features they need. and fans of a particular ide could use the list to pick any missing feature that they feel able to implement.. claus

Hi not sure if this is a real project to build a Haskell IDE ... adherence to the MS accessibility guidelines. Ironically the VS environement seems to deviate from the corporation's own advice to the rest of the world. Paul

Well, yes and no. Such an IDE does not have to follow the guidelines, because as you said, these are “flexible”. Take Microsoft Office 2007, completely new GUI, shocked the world. But take Eclipse. This is a fairly standard GUI, mostly the same on unix, mac, and Windows. IMHO, for a Windows user coming from Visual Basic, Visual Studio, Borland Delphi, etc, switching to Eclipse is much easier than switching to emacs. Or take the Concurrent Clean IDE. Totally not a windows GUI. But easy to get started with. Just install, open an example, select run and off you go. From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of PR Stanley Sent: Monday, June 18, 2007 15:06 To: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Useful IDE features - Accessibility considerations Hi not sure if this is a real project to build a Haskell IDE ... adherence to the MS accessibility guidelines. Ironically the VS environement seems to deviate from the corporation's own advice to the rest of the world. Paul No virus found in this incoming message. Checked by AVG Free Edition. Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007 08:23 No virus found in this outgoing message. Checked by AVG Free Edition. Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007 08:23

That looks cool. Just another wild idea which I might find useful, but is more like refactoring, is to convert the fields of a record to get/set type-classes, and refactor all usages of those fields. So ------------------- data Person = Person { name :: String, age :: Float } main = print $ name p ++ " is " ++ show (age p) ++ " years old" where p = Person { name = "Homer", age = 41 } ------------------- Would refactor into (just wild Haskell code from a newbie here) ------------------- data Person = Person String Float class HasName a where nameOf :: a -> String withName :: a -> String -> a class HasAge a where ageOf :: a -> Float withAge :: a -> Float -> a instance HasName Person where nameOf (Person name age) = name withName (Person name age) newName = Person newName age instance HasAge Person where ageOf (Person name age) = age withAge (Person name age) newAge = Person name newAge defaultPerson = Person "" 0 ------------------- main = print $ nameOf p ++ " is " ++ show(ageOf p) ++ " years old" where p = defaultPerson `withName` "Homer" `withAge` 41 -- or just where p = Person "Homer" 41 ------------------- Visual Studio, Eclipse, IntelliJ etc already have these kind of wizards to encapsulate fields with setters getters for C#/Java, and also introduce boiler plate code, although less of it. However, Haskell turns each field into a separate type class, so this is much more reusable code than their OO counterparts. Peter -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Claus Reinke Sent: Monday, June 18, 2007 14:24 To: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Useful IDE features - "implement instance"
Another feature which would be cool for an IDE is: "implement instance". So you automatically get to see all the functions of a type class you need to implement. Using C#/Java, this is used all over the place.
sounds potentially useful, but perhaps not quite as useful as one might expect: if you only want to see all the class methods, hugs/ghci provide the ':info' command (and haskell modes tend to provide access to that). $ ghc -e ':i Monad' class Monad m where (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b return :: a -> m a fail :: String -> m a -- Defined in GHC.Base instance Monad Maybe -- Defined in Data.Maybe instance Monad IO -- Defined in GHC.IOBase instance Monad [] -- Defined in GHC.Base with a little bit of filtering and replacing, we get $ ghc -e ':i Monad' | sed -n '/^class/,/-- Defined in/{s/class/instance/;p}' instance Monad m where (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b return :: a -> m a fail :: String -> m a -- Defined in GHC.Base i've used sed here, to keep it editor-independent, one can do the equivalent within emacs/vim, without sed. now, if one wanted to save typing, one might want to translate the type declarations into definition templates, but the type has more information than such template, and there are many forms of definition that fit a type, so having to replace the type declarations with definitions is perhaps as good as it gets? a similarly useful code template generation transformation would be to introduce complete case distinctions over sum types, so that f x = undefined would, if we knew (x::Maybe a), become f (Just a) = undefined f Nothing = undefined or 'doSomething >>= \(x::Either l r)->body' would become doSomething >>= \x->case x of {Left l->body; Right r->body} which, of course, should rather be doSomething >>= either (\l->body) (\r->body) yes, there are many opportunities for making haskell editing easier, and not all of them require detailed editor hacking or haskell analysis and transformation skills (though some do). keep the suggestions coming. perhaps summarize them on a haskell.org wiki page, though, so they don't get lost. someone might get round to implementing them, some of them might already be available!-) if someone were to put up a simple table/list of desired ide features (with brief descriptions) on the wiki, everyone could add links to each feature showing how their favourite ide handles said feature. then new users could go through that list and choose to learn one of those ides that provides most of the features they need. and fans of a particular ide could use the list to pick any missing feature that they feel able to implement.. claus _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe No virus found in this incoming message. Checked by AVG Free Edition. Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007 08:23 No virus found in this outgoing message. Checked by AVG Free Edition. Version: 7.5.472 / Virus Database: 269.9.0/852 - Release Date: 17/06/2007 08:23

Hello peterv, Monday, June 18, 2007, 6:44:06 PM, you wrote:
Just another wild idea which I might find useful, but is more like refactoring, is to convert the fields of a record to get/set type-classes, and refactor all usages of those fields.
i never done such refactoring. just use different names for fields. a rule of thumb is including of record name in field names: data PackedFilePath = PackedFilePath { fpPackedDirectory :: !MyPackedString , fpPackedBasename :: !MyPackedString , fpLCExtension :: !String , fpHash :: {-# UNPACK #-} !Int32 , fpParent :: !PackedFilePath } | RootDir data FileInfo = FileInfo { fiFilteredName :: !PackedFilePath , fiDiskName :: !PackedFilePath , fiStoredName :: !PackedFilePath , fiSize :: {-# UNPACK #-} !FileSize , fiTime :: {-# UNPACK #-} !FileTime , fiIsDir :: {-# UNPACK #-} !Bool } -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat, Yes, that's what I had to do when using assembler in the 19080s, but it was nice to get rid of that when using C/C++ or any other imperative/OO language that I'm aware of. You see, for someone with an imperative/OO background, the Haskell record restriction on field names looks incredibly dumb. But when using type classes to encapsulate the fields makes each function polymorphic on any record that implements these field wrappers, thus enhancing abstraction. Type inference helps a lot here, otherwise one would have to type each constraint in the signature of the function, which is a pain (forgive me if I'm using incorrect terms here, I come from the OO world...) Personally I like that, but that's a question of taste I guess. Peter -----Original Message----- From: Bulat Ziganshin [mailto:bulat.ziganshin@gmail.com] Sent: Tuesday, June 19, 2007 8:39 AM To: peterv Cc: 'Claus Reinke'; haskell-cafe@haskell.org Subject: Re[2]: [Haskell-cafe] Useful IDE features - "implement instance" Hello peterv, Monday, June 18, 2007, 6:44:06 PM, you wrote:
Just another wild idea which I might find useful, but is more like refactoring, is to convert the fields of a record to get/set type-classes, and refactor all usages of those fields.
i never done such refactoring. just use different names for fields. a rule of thumb is including of record name in field names: data PackedFilePath = PackedFilePath { fpPackedDirectory :: !MyPackedString , fpPackedBasename :: !MyPackedString , fpLCExtension :: !String , fpHash :: {-# UNPACK #-} !Int32 , fpParent :: !PackedFilePath } | RootDir data FileInfo = FileInfo { fiFilteredName :: !PackedFilePath , fiDiskName :: !PackedFilePath , fiStoredName :: !PackedFilePath , fiSize :: {-# UNPACK #-} !FileSize , fiTime :: {-# UNPACK #-} !FileTime , fiIsDir :: {-# UNPACK #-} !Bool } -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Just another wild idea which I might find useful, but is more like refactoring, is to convert the fields of a record to get/set type-classes, and refactor all usages of those fields.
you could use a preprocessor (DrIFT, Data.Derive) to derive the instances, but you need to share the class declarations between all client modules.
------------------- data Person = Person { name :: String, age :: Float }
main = print $ name p ++ " is " ++ show (age p) ++ " years old" where p = Person { name = "Homer", age = 41 } ------------------- ..
alternatively, you could generalise this a bit, so that there is only one class for all combinations of records, fields, and field value types, and then generalise it further so that you only need one pair of instances to define selection and update for all records. that kind of operates at the borders of the language, so you lose portability (the nicest version is ghc-only; nearly all language extensions used are also supported by hugs, but with a slightly different interpretation). you'd still need to share the label types between all client modules. claus ---------------------------------------------------------- {-# OPTIONS_GHC -fallow-undecidable-instances #-} {-# OPTIONS_GHC -fallow-overlapping-instances #-} {-# OPTIONS_GHC -fglasgow-exts #-} infixl ? infixr <:,:< ------------------- poor man's records -- record extension -- (ghc only: infix constructor; for hugs, use (,) instead) data fieldValue :< record = fieldValue :< record -- field selection (?) and update (<:) -- needs overlapping instances to recurse down record extensions -- for hugs: drop the functional dependency, use more type annotations class Has field value record | field record -> value where (?) :: record -> field -> value (<:) :: (field,value) -> record -> record -- if the first field matches, we're done instance Has field value ((field,value) :< record) where ((_f,v) :< _) ? f = v (f,v) <: ((_f,_) :< r) = ((f,v) :< r) -- otherwise, try again, with the remaining record instance Has field value record => Has field value ((f,v) :< record) where ((f',v') :< r) ? f = r ? f (f,v) <: ((f',v') :< r) = ((f',v') :< ( (f,v)<:r ) ) -- some field labels data Name = Name data Age = Age ------------------- a generic version, no separate Person type or instances type Person1 = (Name,String) :< (Age,Float) :< () homer :: Person1 homer = (Name,"Homer") :< (Age,41) :< () test1 = print $ homer?Name ++ " is " ++ show(homer?Age) ++ " years old" ------------------- a more down-to-earth version, closer to the original data Person = Person String Float instance Has Name String Person where (Person name age) ? Name = name (Name,newName) <: (Person name age) = Person newName age instance Has Age Float Person where (Person name age) ? Age = age (Age,newAge) <: (Person name age) = Person name newAge defaultPerson = Person "" 0 homer2 = (Name,"Homer2") <: (Age,42::Float) <: defaultPerson test2 = print $ homer2?Name ++ " is " ++ show(homer2?Age::Float) ++ " years old" ------------------- main = test1 >> test2

peterv wrote:
Another feature which would be cool for an IDE is: "implement instance". So you automatically get to see all the functions of a type class you need to implement. Using C#/Java, this is used all over the place.
...isn't that because the Java programming language *requires* miles of boilerplate code to do anything? ;-)
participants (8)
-
Andrew Coppin
-
Bulat Ziganshin
-
Claus Reinke
-
David House
-
Marc Weber
-
Neil Mitchell
-
peterv
-
PR Stanley