I created an instance of Functor
for the following definition of a DoubeList
(doubly linked list) data type recently. (Motivated by this post) My goal was to define an instance of Functor so that the function f
in fmap f db
is applied to the first field in each node in the doubly linked list - regardless of which value constructor is passed to fmap
. Afterward, I was having trouble explaining to myself how my fmap
definition would actually evaluate.
For example, passing in some value constructed with LeftEnd
will result in fmap
on a Middle
or RightEnd
. Likewise, a fmap
on some value with a Middle
or RightEnd
constructor will result in an fmap
on a previous or next node - and so on and so forth.
However, after exploring the result of fmapping on LeftEnd
, MiddleEnd
or RightEnd
using returnFirst
and returnNext
, it seems that for some function f
in fmap f db
, f
is applied to the first field in each node only once - like I set out to do. But I can't seem to grasp how this is possible.
My intuition is telling me that the lazy nature of Haskell is coming into play here. Any insight or explanation would be greatly appreciated!
module DoubleList where
data DoubleList a
= LeftEnd a (DoubleList a)
| Middle a (DoubleList a) (DoubleList a)
| RightEnd a (DoubleList a)
-- perserve identity
-- fmap id create = id create
-- perserve function composition
-- fmap (f . g) create = fmap f . fmap g $ create
instance Functor DoubleList where
fmap f (LeftEnd a nxt) = LeftEnd (f a) (fmap f nxt)
fmap f (Middle a prev nxt) = Middle (f a) (fmap f prev) (fmap f nxt)
fmap f (RightEnd a prev) = RightEnd (f a) (fmap f prev)
instance Show a => Show (DoubleList a) where
show (LeftEnd x next) = "Left End " ++ show x ++ "<->" ++ show next
show (Middle x prev next) = show x ++ "<->" ++ show next
show (RightEnd x next) = show x ++ " Right End"
create :: DoubleList Integer
create = let n1 = LeftEnd 1 n2
n2 = Middle 2 n1 n3
n3 = Middle 3 n2 n4
n4 = Middle 4 n3 n5
n5 = RightEnd 5 n4
in n1
returnFirst :: DoubleList a -> DoubleList a
returnFirst (Middle _ prev _) = returnFirst prev
returnFirst (RightEnd _ prev) = returnFirst prev
returnFirst firstNode = firstNode
returnPrev :: DoubleList a -> DoubleList a
returnPrev (Middle x fst@(LeftEnd _ _) _ ) = fst
returnPrev (Middle x mid@(Middle _ _ _) _ ) = mid
returnPrev (RightEnd x prev) = prev
returnPrev leftEnd = leftEnd
returnNext :: DoubleList a -> DoubleList a
returnNext (LeftEnd x nxt) = nxt
returnNext (Middle x prev nxt) = nxt
returnNext (RightEnd _ prev) = prev