#2110: Rules to eliminate casted id's ---------------------------------+------------------------------------------ Reporter: igloo | Owner: Type: feature request | Status: new Priority: lowest | Milestone: 7.6.2 Component: Compiler | Version: 6.8.2 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------
Comment(by sweirich): Sorry to jump in late... but I agree with Simon. Exposing the FC cast operation to the user---just for newtypes---seems to be the simplest solution to the problem. If a client of the module doesn't know that Age is a newtype for Int, why would the client expect "map MkAge" to be an identity function? Newtypes *already* have special semantics, so enhancing that seems better than introducing something that unpredictably applies. Furthermore, what Simon is proposing is just convenient syntax for what is already possible with generalized newtype deriving. (And so should be viewed with the same suspicion.) For example, we can cast a list of types thus: {{{ {-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses #-} class Castable a b where cast :: c a -> c b cast' :: c b -> c a instance Castable Int Int where cast = id cast' = id newtype Age = MkAge Int deriving (Castable Int) x :: [Int] x = [1 .. 10] y :: [Age] y = cast x }}} However, when the type to cast is not the last argument to the data structure, the process requires the definition of yet another newtype. {{{ newtype E1 b a = E1 { unE1 :: Either a b } w :: Either Int Int -> Either Age Int w = unE1 . cast . E1 }}} Having this cast around may be convenient for library writers who want to freely coerce between abstract and concrete types (although it is no substitute for a real module system :-). -- Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2110#comment:29> GHC <http://www.haskell.org/ghc/> The Glasgow Haskell Compiler _______________________________________________ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs