Get data of type without pattern match on all data contructors - haskell

Is there a way to make abstraction of the data type and just use the values?
data Color a = Blue a | Green a | Red a | Yellow a | Magenta a deriving (Show)
Something like :
calcColor :: Color a -> Color a -> Maybe a
calcColor (_ x) (_ y) = Just $ x + y
It doesn't have to be necessarily in the function declaration.
One option I was thinking was to have something like fromJust but even that feels a little redundant.
fromColor :: Color a -> a
fromColor (Blue t) = t
fromColor (Red t) = t
fromColor (Green t) = t
fromColor (Yellow t) = t
Edit - added context and more clarifications
From the way I managed to question it, the title might look like a duplicate question.
I'm not that sure, but that is for the community to decide.
I pretty new to Haskell so maybe my question looks stupid but still I think it's a valid case because I actually have this situation.
#FyodorSoikin, #leftaroundabout Your answers helps me, but partially. I'll try make explain better what exactly I would like to achive.
I want to think at the Color type like a category (let's say G), the colors beeing elements of the G,
and I also have phones that come in different colors. The phones category (let's say H).
Now I have I try to come with a way to make use of the morphisms (functions) of the G category using a functor in the H category or the other way around.
For example : determine the future stocks of a color type based on the sales of phones.
I want to understand to what extend I can create a types like Color to have the advantages of a type ustead of using a string value.

You could do a hack like
{-# LANGUAGE DeriveFoldable #-}
import Data.Foldable (Foldable, toList)
data Color a = Blue a | Green a | Red a | Yellow a | Magenta a
deriving (Show, Foldable)
fromColor :: Color a -> a
fromColor c = case toList c of
[ca] -> ca
_ -> error "Impossible, `Color` has only one field."
But I agree with Fyodor Soikin's comment: why have the a field in each constructor in the first place? Just factor it out
data Hue = Blue | Green | Red | Yellow | Magenta
data Color a = Color { hue :: Hue, value :: a }

Based on your edit, it looks like you are looking for a basic vocabulary for dealing with Color. That can be provided both by class instances and by special-purpose functions.
A Functor instance, for example, allows you to change the a value in a Color a independently of the color itself:
data Hue = Blue | Green | Red | Yellow | Magenta
deriving (Eq, Show)
data Color a = Color { hue :: Hue, value :: a }
deriving (Eq, Show)
instance Functor Color where
fmap f (Color h a) = Color h (f a)
GHCi> test1 = Color Red 27
GHCi> fmap (2*) test1
Color {hue = Red, value = 54}
Two brief notes:
The things I'm suggesting here can be done equally as well with your four-constructor Color type or with leftaroundabout's single-constructor one. The latter, though, should be easier to work with in most situations, so I'll stick with it.
The DeriveFunctor extension means you almost never have to write a Functor instance explicitly: turn it on by adding {-# LANGUAGE DeriveFunctor #-} to the top of your file and then just write:
data Color a = Color { hue :: Hue, value :: a }
deriving (Eq, Show, Functor)
Another thing you might want to do is having a Hue -> Colour a -> Maybe a function, which would give you a way to use operations on Maybe to filter the a values by their attached hue:
colorToMaybe :: Hue -> Color a -> Maybe a
colorToMaybe chosenHue col
| hue col == chosenHue = Just (value col)
| otherwise = Nothing
GHCi> test1 = Color Red 27
GHCi> test2 = Color Red 14
GHCi> test3 = Color Blue 33
GHCi> import Data.Maybe
GHCi> mapMaybe (colorToMaybe Red) [test1, test2, test3]
[27,14]
GHCi> import Control.Applicative
GHCi> liftA2 (+) (colorToMaybe Red test1) (colorToMaybe Red test2)
Just 41
GHCi> liftA2 (+) (colorToMaybe Red test1) (colorToMaybe Red test3)
Nothing
These are just rather arbitrary suggestions. The specifics of what you'll want to define will depend on your use cases.

Related

Implement Enum Instance behavior on custom data type in Haskell

I've got a custom data type in Haskell to represent a traffic light
data TrafficLight = Red | Yellow | Green
I'm attempting to implement the features of the Enum typeclass using an instance block like so:
instance Enum TrafficLight where
succ Green = Yellow
succ Yellow = Red
succ Red = Green
pred Green = Red
pred Yellow = Green
pred Red = Yellow
pred and succ work as expected, however I'd also like to implement the range function, such that I'd be able to call
ghci> [Green .. Red]
and have it return
[Green,Yellow,Red]
I understand that this functionality seems to come from the enumFrom function in the Enum typeclass, but I'm not completely sure how to implement it the say way I implemented pred and succ.
The description for enumFrom at haskell.org gives the following possible definition enumFrom n = n : enumFrom (succ n). It should work in your case.

Storing an Enum type in an unboxed Vector

Suppose I have something like this:
data Colour = Red | Blue | Green
deriving (Eq, Ord, Enum, Bounded, Read, Show)
And I want to have an unboxed Vector of Colours. I obviously cannot do this directly (because Colour isn't an instance of Unbox), but I also can't tell how I would write the Unbox instance for Colour. The the documentation for Unbox doesn't seem to say how you make something an instance of it (or at least, not in a way I understand).
One approach is to use Data.Vector.Unboxed.Deriving, which uses template Haskell to define the correct instances for the new types in terms of existing types with Unbox instances.
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies, TemplateHaskell #-}
module Enum where
import qualified Data.Vector.Unboxed as U
import Data.Vector.Generic.Base
import Data.Vector.Generic.Mutable
import Data.Vector.Unboxed.Deriving
import Data.Word
data Colour = Red | Blue | Green
deriving (Eq, Ord, Enum, Bounded, Read, Show)
colourToWord8 :: Colour -> Word8
colourToWord8 c =
case c of
Red -> 0
Blue -> 1
Green -> 2
word8ToColour :: Word8 -> Colour
word8ToColour w =
case w of
0 -> Red
1 -> Blue
_ -> Green
derivingUnbox "Colour"
[t| Colour -> Word8 |]
[| colourToWord8 |]
[| word8ToColour |]
test n = U.generate n (word8ToColour . fromIntegral . (`mod` 3))
Of course this wastes space in this case because we only use 2 of the 8 bits in Word8.

(Re)-defining (==) for class Eq

In the following example:
data ColourName
= White
| Grey
| Gray
| Black
| Blue
-- ...
-- hundreds more of colours
-- ...
| LastColor
deriving (Read, Show, Eq)
I'd like to redefine (==) so that Grey and Gray evaluate as equal.
Obviously, one way would be to not include Eq in deriving, however, then I'd have to define
(==) :: ColourName
(==) White White = True
(==) Gray Gray = True
(==) Grey Grey = True
(==) Gray Grey = True
(==) Grey Gray = True
(==) Black Black = True
-- frickin' log of other colors, hundreds of lines of typing
(==) LastColor LastColor = True
(==) a b = False
which is nothing I plan to do.
I also can't do
instance Eq ColourName where
(==) :: ColourName -> ColourName -> Bool
(==) Gray Grey = True
(==) Grey Gray = True
(==) a b = (a == b)
because this leads to an infinite recursion, is basically underdefined.
Is there a way out?
(No, I don't want to use data Colour = Colour String or similar. I want the valid colours to be represented as an enumeration, such providing automatic validation, but want to allow spelling variation for the end users of the module!)
You can use the derived Enum instance :
data ColourName = Gray | Grey | ...
deriving (Read, Show, Enum)
instance Eq ColourName where
Gray == Grey = True
Grey == Gray = True
a == b = fromEnum a == fromEnum b
Edit: You can also use PatternSynonyms with GHC 7.8+. It works like a smart constructor, but can also be used in pattern matches.
pattern Gray = Grey
Do not do this. It won't work well with pattern matching. It will break something like
f Gray = g
f x = h
because pattern matching does not care about your Eq instance.
By break, I mean it won't have the behavior you want, since f Grey would end up calling h rather than g, even though you would expect for f x == f y for all x == y. This means the programmer has to explicitly remember to make cases for both f Gray and f Grey which is just dumb.
If you are determined to have an ugly hack to allow for alternate spellings, I suppose you can do
#define Gray Grey
with CPP enabled.
By definition the values Grey and Gray are not equal. There is nothing that suggests that they should be equal, except the extra semantics you've attached to them. I'd say this is an abuse of the Eq typeclass.
Define a function to handle these additional semantics:
sameColour :: Color -> Color -> Bool
sameColour Grey Gray = True
sameColour Gray Grey = True
sameColor a b = a == b
this can easily be extended to handle multiple colour "synonyms"
Similarly to Piezoid's answer, you could make it a bit less efficient by using the Show instance to compare them:
data ColourName = Gray | Grey | ...
deriving (Show, Read)
instance Eq ColourName where
Gray == Grey = True
Grey == Gray = True
a == b = show a == show b
Then you don't have to rely on using Enum, but you will have a bit of a performance hit from having to compare strings.
I would use a newtype here:
newtype ColourNameEquatingGrayAndGrey = CNEGAG ColourName
instance Eq ColourNameEquatingGrayAndGrey where
CNEGAG Gray == CNEGAG Grey = True
CNEGAG Grey == CNEGAG Gray = True
CNEGAG a == CNEGAG b = a == b
(Sorry about the silly type and constructor names...)
This allows you to keep deriving Eq, it makes you be very explicit about where in your code you are lumping the different spellings together, and you can still use library functions such as nub (as compared to having to switch over to nubBy sameColour (as in #cdk's answer) or something like that). You can also make your own Show instance, should you need one, and the runtime cost should be minimal.
The only downside I can think of right now is that pattern matching becomes more cumbersome, but I'm guessing that with 100s of alternatives that's not something you do at the drop of a hat!

How do I create an unbox instance of an ADT?

I'm having trouble finding good resources that work for how to make my data types unboxed, for use in an unboxed vector. How would I make the data type
data Color = Yellow | Red | Green | Blue | Empty deriving (Show, Eq)
be an instance of Unbox?
Edit: after poking around a bit more, it seems that by forcing paramaters in some functions to be strict, I can convince GHC to unbox them automatically. If this applicable in my case? How do I know which paramaters to make strict?
You can use the vector-th-unbox package to derive the instance for you. You just need to provide conversion functions to and from some existing Unbox type:
colorToWord8 :: Color -> Word8
colorToWord8 = ...
word8ToColor :: Word8 -> Color
word8ToColor = ...
derivingUnbox "Color"
[t| Color -> Word8 |]
colorToWord8
word8ToColor
GeneralizedNewtypeDeriving won't help you here because you're dealing with a 'full-blown' ADT, rather than a newtype wrapping something that's already an instance of Unbox.
Your data type is more suited to boxed vectors. Use Data.Vector.Unboxed if you need to hold more primitive numeric types like Doubles, Ints, etc. Perhaps you can make Color an instance of Unbox, but it almost certainly isn't worth the hassle. Import Data.Vector and you'll be set:
import qualified Data.Vector as V
Color = Red | Blue deriving Show
someColors :: V.Vector Color
someColors = V.fromList [Red, Blue, Blue, Red]

Haskell deriving additional instances for imported datatypes

I'm relatively new to Haskell. I write a clone of the card game uno and i want pretty coloured output of a card. I do
import System.Console.ANSI
which provides
data Color = Black
| Red
| Green
| Yellow
| Blue
| Magenta
| Cyan
| White
deriving (Bounded, Enum, Show)
now i want to add deriving (Ord, Eq) as well, i could write this in the source file of the imported package, but there should be an easier way to do this.
i don't have a clue what keywords to google for or look for in a book.
No need to edit the library. In your source file, state:
instance Eq Color where
x == y = fromEnum x == fromEnum y
instance Ord Color where
compare x y = compare (fromEnum x) (fromEnum y)
Explanation: fromEnum is a function on Enum that returns an int (Black -> 0, Red -> 1, etc.). Integers are obviously equality-comparable and ordered.
Edit: #rampion's version, in the comments, is obviously prettier:
instance Eq Color where
(==) = (==) `on` fromEnum
instance Ord Color where
compare = compare `on` fromEnum

Resources