Skip to content
Snippets Groups Projects
Commit f2cf01de authored by Herbert Valerio Riedel's avatar Herbert Valerio Riedel :man_dancing: Committed by Mikhail Glushenkov
Browse files

Use -XDeriveFunctor for `data InstallDirs`

(cherry picked from commit 9c3e6091)
parent 6ee0206d
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
......@@ -90,28 +91,10 @@ data InstallDirs dir = InstallDirs {
htmldir :: dir,
haddockdir :: dir,
sysconfdir :: dir
} deriving (Eq, Read, Show, Generic)
} deriving (Eq, Read, Show, Functor, Generic)
instance Binary dir => Binary (InstallDirs dir)
instance Functor InstallDirs where
fmap f dirs = InstallDirs {
prefix = f (prefix dirs),
bindir = f (bindir dirs),
libdir = f (libdir dirs),
libsubdir = f (libsubdir dirs),
dynlibdir = f (dynlibdir dirs),
libexecdir = f (libexecdir dirs),
includedir = f (includedir dirs),
datadir = f (datadir dirs),
datasubdir = f (datasubdir dirs),
docdir = f (docdir dirs),
mandir = f (mandir dirs),
htmldir = f (htmldir dirs),
haddockdir = f (haddockdir dirs),
sysconfdir = f (sysconfdir dirs)
}
instance (Semigroup dir, Monoid dir) => Monoid (InstallDirs dir) where
mempty = gmempty
mappend = (Semi.<>)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment