Reputation: 23
I'm not sure if I'm being too ambitious here, but I'm attempting to construct an integer mod 12 data type for use in a music notation system. If possible I'd love to have values of this type be specifiable in practice simply using the numbers 0-11 (as opposed to writing "Note 11", for instance), and have the Note type be inferred by the type signatures of the functions that use it. I've created a clunky makeshift version of this using
type Note = Int
then simply composing any functions that act on Notes with a mod 12 function. This works perfectly well, but it's repetitive. It looks like the perfect spot for a functor, using something roughly along the lines of
instance Functor Note where
fmap f = (`mod` 12).f
I think I could easily make that work if I wrote "Note 0" or something along those lines anytime I use the data type, but that's an exactly equivalent amount of typing to what I'm currently doing (though admittedly it's probably slightly less error prone). Lastly I'm aware that smart constructors are a closely related topic to what I'm working on, but as of yet I couldn't manage to make that work for my pipe dream setup. Is there any way I can have my cake (represent Notes with plain integers 0-11) and eat it too (define fmap for Notes) here, or am I being optimistic?
Thanks in advance!
Upvotes: 2
Views: 332
Reputation: 36622
You can't get a functor instance here, because your type is too specific. But don't despair – you can still pretty much get what you want! We'll just use a free-standing ordinary function that does the same thing, instead of using a type class. Here's the road map:
First, we'll define our Note
type and make it safe: we'll use a smart constructor to ensure that all Note
s hold an Int
between 0
and 11
.
Next, we'll talk about Functor
and why Note
isn't one, as well as how to replace the functionality you want with an ordinary function.
Finally, we'll make Note
support number-literal syntax.
We'll then show some examples of usage.
And we'll close out with the complete code.
So let's define our Note
type. We want it to be a thin wrapper around an integer, so we'll use a newtype
:
newtype Note = MkNote Int deriving Eq
instance Show Note where
show (MkNote 0) = "A"
show (MkNote 1) = "A♯/B♭"
show (MkNote 2) = "B"
show (MkNote 3) = "C"
show (MkNote 4) = "C♯/D♭"
show (MkNote 5) = "D"
show (MkNote 6) = "D♯/E♭"
show (MkNote 7) = "E"
show (MkNote 8) = "F"
show (MkNote 9) = "F♯/G♭"
show (MkNote 10) = "G"
show (MkNote 11) = "G♯/A♭"
show (MkNote _) = error "internal error: invalid `Note'"
Now, to ensure that Note
s are always 0–11, we use a smart constructor:
note :: Int -> Note
note = MkNote . (`mod` 12)
And we also provide a destructor:
getNote :: Note -> Int
getNote (MkNote i) = i
These functions will allow us to convert between Note
s and Int
s safely, so we can export the Note
type but not the MkNote
constructor to ensure that all Note
s are between 0 and 11.
If we turn on the GHC extension PatternSynonyms
, we can fake having an ordinary data type:
pattern Note :: Int -> Note
pattern Note i <- MkNote i where
Note i = note i
This defines a new pattern Note i
that, when pattern matching, corresponds to the MkNote
constructor (the <-
part), and when used in an expression corresponds to the note
smart constructor (the where …
part).
Now, you want to move between Int
functions and Note
functions, and you ask about creating a Functor
instance. Well, Functor
isn't really what you're looking for here. Let's look at the type class:
class Functor f where
fmap :: (a -> b) -> (f a -> f b)
Hmm… we see that f
is being applied to another type there. But we can't do that with Note
! We say that Note
has kind (the type of a type) *
, which is the kind of all types; but f
has kind * -> *
, which is to say it's a type-level function that takes types to types. This is why we can say
instance Functor Maybe where …
-- fmap :: (a -> b) -> (Maybe a -> Maybe b)
but not
-- instance Functor Note where …
-- fmap :: (a -> b) -> (Note a -> Note b)
So what can we do instead? Well, just because the type class doesn't work doesn't mean we can't define our own mapping function:
nmap :: (Int -> Int) -> Note -> Note
nmap f = note . f . getNote
Since note
does the (`mod` 12)
thing you wanted, this is essentially the same as your definition, and this is the type that it must have: we can only nmap
functions of type Int -> Int
. This is another reason fmap
doesn't work – it must support all functions.
We can use this technique to define functions for working with multi-argument functions as well:
nmap2 :: (Int -> Int -> Int) -> Note -> Note -> Note
nmap2 f n1 n2 = note $ f (getNote n1) (getNote n2)
And if we want to work with functions that don't return Note
s, we can do that:
nuse :: (Int -> a) -> Note -> a
nuse f = f . getNote
nuse2 :: (Int -> Int -> a) -> Note -> Note -> a
nuse2 f = f `on` getNote
-- `on` is from "Data.Function"
(Note that nmap = note . nuse
, and similarly for nmap2
.)
Finally, we can use this to support number literals. In Haskell, numeric literals like 42
are equivalent to the expression fromInteger (42 :: Integer)
, where fromInteger
is from the Num
type class. So you can make Note
s an instance of Num
:
instance Num Note where
(+) = nmap2 (+)
(-) = nmap2 (-)
(*) = error "Can't multiply `Note`s" -- Or @nmap2 (*)@
negate = nmap negate
abs = id -- No-op; equivalent to @nmap abs@
signum = nmap signum
fromInteger = note . fromInteger -- 'Integer' → 'Int' → 'Note'
Putting all that together, here are some examples of what we can write.
A list of A♯s:
aSharps :: [Note]
aSharps = [ note 1, note (-11), note 13
, 1, -11, 13
, Note 1, Note (-11), Note 13 ]
-- All elements are equal
A function that turns Cs into As but leave other notes unchanged:
noCs :: Note -> Note
noCs 3 = 0
noCs n = n
and a different way of writing that function:
noCs' :: Note -> Note
noCs' 15 = 0
noCs' n = n
And so on and so forth
Finally, here's what all that code looks like put together; note that the module header doesn't export MkNote
for safety.
{-# LANGUAGE PatternSynonyms #-}
module Note (
Note(), pattern Note, note, getNote,
nmap, nmap2, nuse, nuse2
) where
import Data.Function
newtype Note = MkNote Int deriving Eq
instance Show Note where
show (MkNote 0) = "A"
show (MkNote 1) = "A♯/B♭"
show (MkNote 2) = "B"
show (MkNote 3) = "C"
show (MkNote 4) = "C♯/D♭"
show (MkNote 5) = "D"
show (MkNote 6) = "D♯/E♭"
show (MkNote 7) = "E"
show (MkNote 8) = "F"
show (MkNote 9) = "F♯/G♭"
show (MkNote 10) = "G"
show (MkNote 11) = "G♯/A♭"
show (MkNote _) = error "internal error: invalid `Note'"
note :: Int -> Note
note = MkNote . (`mod` 12)
getNote :: Note -> Int
getNote (MkNote i) = i
pattern Note :: Int -> Note
pattern Note i <- MkNote i where
Note i = note i
nmap :: (Int -> Int) -> Note -> Note
nmap f = note . f . getNote
nmap2 :: (Int -> Int -> Int) -> Note -> Note -> Note
nmap2 f n1 n2 = note $ f (getNote n1) (getNote n2)
nuse :: (Int -> a) -> Note -> a
nuse f = f . getNote
nuse2 :: (Int -> Int -> a) -> Note -> Note -> a
nuse2 f = f `on` getNote
instance Num Note where
(+) = nmap2 (+)
(-) = nmap2 (-)
(*) = error "Can't multiply `Note`s" -- Or @nmap2 (*)@
negate = nmap negate
abs = id -- No-op; equivalent to @nmap abs@
signum = nmap signum
fromInteger = note . fromInteger -- 'Integer' → 'Int' → 'Note'
Upvotes: 4
Reputation: 152707
The class you're looking for is Num
: the literal syntax 0
in Haskell implicitly calls fromInteger
. So you might write something like
newtype Note = Note Int
instance Num Note where
fromInteger n = Note (fromInteger (n `mod` 12))
Note a + Note b = Note ((a + b) `mod` 12)
and so on for the other Num
operations. You might also like to use the Hackage package modular-arithmetic, which provides the Mod Int 12
type and already has these operations available.
Upvotes: 7