Accessing the "default show" in Haskell? - haskell

Say you have a data-structure (borrowed from this question):
data Greek = Alpha | Beta | Gamma | Delta | Eta | Number Int
Now one can make it an instance of Show by appending deriving Show on that instruction.
Say however we wish to show Number Int as:
instance Show Greek where
show (Number x) = show x
-- ...
The problem is that one must specify all other parts of the Greek data as well like:
show Alpha = "Alpha"
show Beta = "Beta"
For this small example that's of course doable. But if the number of options is long, it requires a large amount of work.
I'm wondering whether it is possible to access the "default show" implementation and call it with a wildcard. For instance:
instance Show Greek where
show (Number x) = show x
show x = defaultShow x
You thus "implement" the specific patterns that differ from the default approach and the remaining patterns are resolved by the "fallback mechanism".
Something a bit similar to method overriding with a reference to super.method in object oriented programming.

As #phg pointed above in the comment this can be also done with the help of generic-deriving:
{-# LANGUAGE DeriveGeneric #-}
module Main where
import Generics.Deriving.Base (Generic)
import Generics.Deriving.Show (GShow, gshow)
data Greek = Alpha | Beta | Gamma | Delta | Eta | Number Int
deriving (Generic)
instance GShow Greek
instance Show Greek where
show (Number n) = "n:" ++ show n
show l = gshow l
main :: IO ()
main = do
print (Number 8)
print Alpha

You can sorta accomplish this using Data and Typeable. It is a hack of course, and this example only works for "enumerated" types as in your example.
I'm sure we could get more elaborate with how we do this, but to cover your given example:
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Data
import Data.Typeable
data Greek = Alpha | Beta | Gamma | Delta | Eta | Number Int
deriving (Data,Typeable)
instance Show Greek where
show Number n = show n
show x = show $ toConstr x
This approach as I've implemented it cannot handle nested data structures or anything else remotely fancy, but again, this is an ugly hack. If you really must use this approach you can dig around in the Data.Data package I'm sure you could piece something together...
Here is a blog post giving a quick introduction to the packages: http://chrisdone.com/posts/data-typeable
The proper way to go about this would be to use a newtype wrapper. I realize that this isn't the most convenient solution though, especially when using GHCi, but it incurs no additional overhead, and is less likely to break in unexpected ways as your program grows.
data Greek = Alpha | Beta | Gamma | Delta | Eta | Number Int
deriving (Show)
newtype SpecialPrint = SpecialPrint Greek
instance Show SpecialPrint where
show (SpecialPrint (Number x)) = "Number: " ++ show x
show (SpecialPrint x) = show x
main = do
print (SpecialPrint Alpha)
print (SpecialPrint $ Number 1)

No, that's not possible AFAIK.
Further, custom instances of Show deserve a second thought, because Show and Read instances should be mutually compatible.
For just converting to human (or whoever) readable strings, use your own function or own typeclass. This will also achieve what you want:
Assuming you have a Presentable typeclass with a method present, and also the default Show instance, you can write:
instance Presentable Greek where
present (Number x) = show x
present x = show x

Related

How to write the instance for Show of a given datatype shorter?

I´m quite new to Haskell but I wonder how I can write following Code shorter:
data Suite = Club | Heart | Spade | Diamond
data Value = Two | Three | Four | Five | Six | Seven | Eight | Nine | Ten | Jack | Queen |
King | Ace
data Card = Card Suite Value
instance Show Suite where
show Club = "Club"
show Heart = "Heart"
show Spade = "Spade"
show Diamond = "Diamond"
instance Enum Suite where
enumFromTo Club Diamond = [Club, Heart, Spade, Diamond]
enumFromTo Heart Diamond = [Heart, Spade, Diamond]
enumFromTo Club Spade = [Club, Heart, Spade]
instance Show Value where
show Two = "Two"
show Three = "Three"
show Four = "Four"
show Five = "Five"
show Six = "Six"
show Seven = "Seven"
show Eight = "Eight"
show Nine = "Nine"
show Ten = "Ten"
show Jack = "Jack"
show Queen = "Queen"
show King = "King"
show Ace = "Ace"
I want to write the instance for Show Value way shorter. Is there a good way to do this or do I need to write all of it?
I also wonder how i could go from here if I want to define the same instances for Eq Card, Ord Card?
So far
instance Eq Card where
Card _ _ == _ = False
instance Ord Card where
Card Heart Three > Card Heart Two = True
worked, but to write every single possibility would be quite a lot of work.
Thanks for any answers!
Edit: I´m aware of the possiblity to append deriving (Show, etc..) but I don´t want to use it
You've rejected deriving these instances, which is the main way we avoid that much boilerplate. The most obvious remaining elementary way to shorten the Show Value is to use a case expression. This uses an extra line but shortens each case slightly:
instance Show Value where
show x = case x of
Two -> "Two"
Three -> "Three"
-- etc.
Expanding to non-elementary ways, you could
Use generics, either the somewhat more modern version in GHC.Generics or (probably easier in this case) the one in Data.Data. For these, you'll need deriving Generic or deriving Data, respectively, and then you can write (or dig up on Hackage) generic versions of the class methods you need. Neither of these approaches seems very appropriate for a Haskell beginner, but you can work up to them over a number of months.
Use Template Haskell. This is a very advanced language feature, and despite working with Haskell for many years, I have not really begun to grasp how to program with it. Good luck!
If you just want your show method call to print the name of the constructor (as it appears here), there's no need to manually instance them at all. You can automatically derive the Show instance thusly:
data Suit = Club | Heart | Spade | Diamond
deriving Show
data Value = Two | Three | Four | Five | Six | Seven
| Eight | Nine | Ten | Jack | Queen | King | Ace
deriving Show
In some cases, such as Instance Show Value, there is no good way to shorten it without deriving (not counting the ones in dfeuer's answer).
But in others there is! E.g.
for the Enum instances it's enough to define fromEnum and toEnum, all the rest have default definitions. You certainly don't need to list all possibilities in enumFromTo as your example code does.
After you define instance Enum Value, you can write comparison functions by converting to Int and comparing the results:
instance Eq Value where
x == y = fromEnum x == fromEnum y
instance Ord Value where
compare x y = compare (fromEnum x) (fromEnum y)
You can use instances for Value and Suit when writing definitions for Card, e.g.
instance Eq Card where
Card s1 v1 == Card s2 v2 = s1 == s2 && v1 == v2

haskell type,new type or data for only an upper case char

If i want to make a String but holds only an uppercase character. I know that String is a [Char]. I have tried something like type a = ['A'..'Z'] but it did not work any help?
What you're wanting is dependent types, which Haskell doesn't have. Dependent types are those that depend on values, so using dependent types you could encode at the type level a vector with length 5 as
only5 :: Vector 5 a -> Vector 10 a
only5 vec = concatenate vec vec
Again, Haskell does not have dependent types, but languages like Agda, Coq and Idris do support them. Instead, you could just use a "smart constructor"
module MyModule
( Upper -- export type only, not constructor
, mkUpper -- export the smart constructor
) where
import Data.Char (isUpper)
newtype Upper = Upper String deriving (Eq, Show, Read, Ord)
mkUpper :: String -> Maybe Upper
mkUpper s = if all isUpper s then Just (Upper s) else Nothing
Here the constructor Upper is not exported, just the type, and then users of this module have to use the mkUpper function that safely rejects non-uppercase strings.
For clarification, and to show how awesome dependent types can be, consider the mysterious concatenate function from above. If I were to define this with dependent types, it would actually look something like
concatenate :: Vector n a -> Vector m a -> Vector (n + m) a
concatenate v1 v2 = undefined
Wait, what's arithmetic doing in a type signature? It's actually performing type-system level computations on the values that this type is dependent on. This removes a lot of potential boilerplate in Haskell, and it makes guarantees at compilation time that, e.g., arrays can't have negative length.
Most desires for dependent types can be filled either using smart constructors (see bheklilr's answer), generating Haskell from an external tool (Coq, Isabelle, Inch, etc), or using an exact representation. You probably want the first solution.
To exactly represent just the capitals then you could write a data type that includes a constructor for each letter and conversion to/from strings:
data Capital = CA | CB | CC | CD | CE | CF | CG | CH | CI | CJ | CK | CL | CM | CN | CO | CP | CQ | CR | CS | CT | CU | CV | CW | CX | CY | CZ deriving (Eq, Ord, Enum)
toString :: [Capital] -> String
toString = map (toEnum . (+ (fromEnum 'A')) . fromEnum)
You can even go a step further and allow conversion from string literals, "Anything in quotes", to a type [Capitals] by using the OverloadedStrings extension. Just add to the top of your file {-# LANGUAGE OverloadedStrings, FlexibleInstances #-}, be sure to import Data.String and write the instance:
type Capitals = [Capital]
instance IsString Capitals where
fromString = map (toEnum . (subtract (fromEnum 'A')) . fromEnum) . filter (\x -> 'A' <= x && x <= 'Z')
After that, you can type capitals all you want!
*Main> toString ("jfoeaFJOEW" :: Capitals)
"FJOEW"
*Main>
bheklilr is correct but perhaps for your purposes the following could be OK:
import Data.Char(toUpper)
newtype UpperChar = UpperChar Char
deriving (Show)
upperchar :: Char -> UpperChar
upperchar = UpperChar. toUpper
You can alternatively make UpperChar an alias of Char (use type instead of newtype) which would allow you to forms lists of both Char and UpperChar. The problem with an alias, however, is that you could feed a Char into a function expecting an UpperChar...
One way to do something similar which will work well for the Latin script of your choice but not so well as a fully general solution is to use a custom type to represent upper case letters. Something like this should do the trick:
data UpperChar = A|B|C|D| (fill in the rest) | Y | Z deriving (Enum, Eq, Ord, Show)
newtype UpperString = UpperString [UpperChar]
instance Show UpperString
show (UpperString s) = map show s
The members of this type are not Haskell Strings, but you can convert between them as needed.

How to override Show instance of some basic types in Haskell?

I'm writting some programs in Haskell, dealing with a lot of basic types like Word32/Word64 etc..
I use ghci to test the functions frequently, see the results in terminal.
To be convenient and fast, I always show data in hexadecimal e.g.
data Human = M Int | F Int
instance Show Human where
show M x = printf "man, age %d" x
show F x = printf "woman, age %d" x
but I want basic types to be showed in hexadecimal (espacially in ghci).
I found instance declaration cannot be overridden.
and I don't want to warp all of them up like:
newtype MyInt = MyInt Int
instance Show MyInt where
...
It looks a little bit stupid.
Can I modify some code in the package base for ghc?
I just want everything becoming "hex". I just want ghci showing "hex". how could I achieve it?
EDIT
Since all of us agree that override Show is not proper and impractical,
Any answer of "better ways to show Numeric in hexadecimal in ghci" is welcomed.
No, there is no way to achieve this without newtypes; instances cannot be overriden.
If you really want this, I would suggest defining your own typeclass, ShowHex, like Show but with all the instances printing in hex. However, I would consider your Show instance incorrect; Show instances are designed for debugging and serialisation, and should output syntactically valid code.1 Yours doesn't, so I would suggest either defining your own typeclass for displaying these values, or simply using a function.
Modifying the code to base for this is impractical; not only would this change in semantics for the instances break a lot of packages, but it'd be a huge pain to get GHC to actually use your modified version.
1 Ideally, the code they produce should be semantically valid Haskell that produces a value comparing equal to show's input, but this is not strictly necessary.
That would be abusing the Show instance. It's not really meant for formatting. If you want to show something in hexadecimal, just use a function to do the conversion. For example, you can use showHex from Numeric to make a small helper like this:
> import Numeric
Numeric> let hex x = showHex x ""
Numeric> hex 123456
"1e240"
One extreme solution would be to use {-# LANGUAGE NoImplicitPrelude #-}, and import your own "Prelude" instead. That would probably be a lot more work than it's worth for your case, though.
Agreeing with #ehird and #hammar that this could be abused. In the case of wanting some numbers to always show as hex, I think it's reasonable because "0xff" is a legitimate representation of a number. So this:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module HexNumber where
import Numeric
import Text.Read
import qualified Text.Read.Lex as L
newtype HexInt a = HexInt { int :: a }
deriving (Eq, Ord, Num, Enum)
instance (Show a, Integral a) => Show (HexInt a) where
show hi = "0x" ++ showHex (int hi) ""
instance (Num a) => Read (HexInt a) where
-- Couldn't figure out how to write this instance so just copy/paste from Text.Read
readPrec = readNumber convertInt
readListPrec = readListPrecDefault
readList = readListDefault
readNumber :: Num a => (L.Lexeme -> ReadPrec a) -> ReadPrec a
readNumber convert =
parens
( do x <- lexP
case x of
L.Symbol "-" -> do y <- lexP
n <- convert y
return (negate n)
_ -> convert x
)
convertInt :: Num a => L.Lexeme -> ReadPrec a
convertInt (L.Number n)
| Just i <- L.numberToInteger n = return (fromInteger i)
convertInt _ = pfail
Now I can:
> let x = 10 :: HexInt Int
> x
0xa
> x * 2
0x14
> let x = 10 :: HexInt Integer
> x
0xa
> x * 2
0x14
> read "0xa" :: HexInt Int
0xa
> read "10" :: HexInt Int
0xa
This seems very useful to me working with low-level stuff a lot. Maybe I'll put it on Hackage.

Implementing Read typeclass where parsing strings includes "$"

I've been playing with Haskell for about a month. For my first "real" Haskell project I'm writing a parts-of-speech tagger. As part of this project I have a type called Tag that represents a parts-of-speech tag, implemented as follows:
data Tag = CC | CD | DT | EX | FW | IN | JJ | JJR | JJS ...
The above is a long list of standardized parts-of-speech tags which I've intentionally truncated. However, in this standard set of tags there are two that end in a dollar sign ($): PRP$ and NNP$. Because I can't have type constructors with $ in their name, I've elected to rename them PRPS and NNPS.
This is all well and good, but I'd like to read tags from strings in a lexicon and convert them to my Tag type. Trying this fails:
instance Read Tag where
readsPrec _ input =
(\inp -> [((NNPS), rest) | ("NNP$", rest) <- lex inp]) input
The Haskell lexer chokes on the $. Any ideas how to pull this off?
Implementing Show was fairly straightforward. It would be great if there were some similar strategy for Read.
instance Show Tag where
showsPrec _ NNPS = showString "NNP$"
showsPrec _ PRPS = showString "PRP$"
showsPrec _ tag = shows tag
You're abusing Read here.
Show and Read are meant to print and parse valid Haskell values, to enable debugging, etc. This doesn't always perfectly (e.g. if you import Data.Map qualified and then call show on a Map value, the call to fromList isn't qualified) but it's a valid starting point.
If you want to print or parse your values to match some specific format, then use a pretty-printing library for the former and an actual parsing library (e.g. uu-parsinglib, polyparse, parsec, etc.) for the latter. They typically have much nicer support for parsing than ReadS (though ReadP in GHC isn't too bad).
Whilst you may argue that this isn't necessary, this is just a quick'n'dirty hack you're doing, quick'n'dirty hacks have a tendency to linger around... do yourself a favour and do it right the first time: it means there's less to re-write when you want to do it "properly" later on.
Don't use the Haskell lexer then. The read functions use ParSec, which you can find an excellent introduction to in the Real World Haskell book.
Here's some code that seems to work,
import Text.Read
import Text.ParserCombinators.ReadP hiding (choice)
import Text.ParserCombinators.ReadPrec hiding (choice)
data Tag = CC | CD | DT | EX | FW | IN | JJ | JJR | JJS deriving (Show)
strValMap = map (\(x, y) -> lift $ string x >> return y)
instance Read Tag where
readPrec = choice $ strValMap [
("CC", CC),
("CD", CD),
("JJ$", JJS)
]
just run it with
(read "JJ$") :: Tag
The code is pretty self explanatory. The string x parser monad matches x, and if it succeeds (doesn't throw an exception), then y is returned. We use choice to select among all of these. It will backtrack appropriately, so if you add a CCC constructor, then CC partially matching "CCC" will fail later, and it will backtrack to CCC. Of course, if you don't need this, then use the <|> combinator.

General conversion type class

I'd like to see if it is feasible to have a type class for converting one thing into another and back again from a mapping of [(a,b)].
This example should illustrate what I'd like to do:
data XX = One | Two | Three deriving (Show, Eq)
data YY = Eno | Owt | Eerht deriving (Show, Eq)
instance Convert XX YY where
mapping = [(One, Eno), (Two, Owt), (Three, Eerht)]
-- // How can I make this work?:
main = do print $ (convert One :: YY) -- Want to output: Eno
print $ (convert Owt :: XX) -- Want to output: Two
Here's my stab at making this work:
{-# LANGUAGE MultiParamTypeClasses #-}
import Data.Maybe(fromJust)
lk = flip lookup
flipPair = uncurry $ flip (,)
class (Eq a, Eq b) => Convert a b where
mapping :: [(a, b)]
mapping = error "No mapping defined"
convert :: a -> b
convert = fromJust . lk mapping
-- // This won't work:
instance (Convert a b) => Convert b a where
convert = fromJust . lk (map flipPair mapping)
It is easy to do this with defining two instances for the conversion going either way but I'd like to only have to declare one as in the first example. Any idea how I might do this?
Edit: By feasible I mean, can this be done without overlapping instances any other nasty extensions?
I, er... I almost hate to suggest this, because doing this is kinda horrible, but... doesn't your code work as is?
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE OverlappingInstances #-}
import Data.Maybe(fromJust)
lk x = flip lookup x
flipPair = uncurry $ flip (,)
class (Eq a, Eq b) => Convert a b where
mapping :: [(a, b)]
mapping = error "No mapping defined"
convert :: a -> b
convert = fromJust . lk mapping
instance (Convert a b) => Convert b a where
convert = fromJust . lk (map flipPair mapping)
data XX = One | Two | Three deriving (Show, Eq)
data YY = Eno | Owt | Eerht deriving (Show, Eq)
instance Convert XX YY where
mapping = [(One, Eno), (Two, Owt), (Three, Eerht)]
main = do print $ (convert One :: YY)
print $ (convert Owt :: XX)
And:
[1 of 1] Compiling Main ( GeneralConversion.hs, interpreted )
Ok, modules loaded: Main.
*Main> main
Eno
Two
*Main>
I'm not sure how useful such a type class is, and all the standard disclaimers about dubious extensions apply, but that much seems to work. Now, if you want to do anything fancier... like Convert a a or (Convert a b, Convert b c) => Convert a c... things might get awkward.
I suppose I might as well leave a few thoughts about why I doubt the utility of this:
In order to use the conversion, both types must be unambiguously known; likewise, the existence of a conversion depends on both types. This limits how useful the class can be for writing very generic code, compared to things such as fromIntegral.
The use of error to handle missing conversions, combined with the above, means that any allegedly generic function using convert will be a seething pit of runtime errors just waiting to happen.
To top it all off, the generic instance being used for the reversed mapping is in fact a universal instance, only being hidden by overlapped, more specific instances. That (Convert a b) in the context? That lets the reversed mapping work, but doesn't restrict it to only reversing instances that are specifically defined.

Resources