Copyright | (c) 2014-2016, Peter Trško |
---|---|
License | BSD3 |
Maintainer | peter.trsko@gmail.com |
Stability | experimental |
Portability | CPP, DeriveDataTypeable, DeriveGeneric, FlexibleInstances, NoImplicitPrelude, RankNTypes, TypeOperators, TypeFamilies |
Safe Haskell | None |
Language | Haskell2010 |
Generic folding for various endomorphism representations.
- foldEndo :: FoldEndoArgs args => args
- dualFoldEndo :: FoldEndoArgs args => args
- class FoldEndoArgs a where
- type ResultOperatesOn a
- type Result a
- foldEndoArgs :: Endo (ResultOperatesOn a) -> a
- dualFoldEndoArgs :: Dual (Endo (ResultOperatesOn a)) -> a
- class AnEndo a where
- type EndoOperatesOn a
- anEndo :: a -> Endo (EndoOperatesOn a)
- aDualEndo :: a -> Dual (Endo (EndoOperatesOn a))
- newtype WrappedFoldable f a = WrapFoldable {
- getFoldable :: f a
- type (:->) args r = (Result args ~ r) => args
- (&$) :: (a -> b) -> a -> b
- (<&$>) :: Functor f => (a -> b) -> f a -> f b
- embedEndoWith :: (AnEndo e, EndoOperatesOn e ~ a) => (Endo a -> b) -> e -> b
- embedDualEndoWith :: (AnEndo e, EndoOperatesOn e ~ a) => (Dual (Endo a) -> b) -> e -> b
Usage Examples
Examples in this section were taken from real live production code, but they were tamed down a little.
Basic Idea
Lets define simple application Config
data type as:
data Verbosity = Silent | Normal | Verbose | Annoying deriving (Show) data Config = Config { _verbosity :: Verbosity , _outputFile :: FilePath } deriving (Show)
Now lets define setters for _verbosity
and _outputFile
:
setVerbosity :: Verbosity ->E
Config setVerbosity b cfg = cfg{_verbosity = b} setOutputFile :: FilePath ->E
Config setOutputFile b cfg = cfg{_outputFile = b}
Note that E
is defined in Data.Monoid.Endo module and
it looks like:
type E
a = a -> a
Its purpose is to simplify type signatures.
Now lets get to our first example:
example1 ::E
Config example1 =appEndo
$
foldEndo
&$
setVerbosity Annoying&$
setOutputFile "an.out.put"
Above example shows us that it is possible to modify Config
as if it was a
monoid, but without actually having to state it as such. In practice it is
not always possible to define it as Monoid
, or at least as a Semigroup
.
Endomorphism are monoids under composition, therefore they are what usually
works in situations when the modified data type can not be instantiated as a
monoid.
Working With Corner Cases
In real applications corner cases arise quite easily, e.g.
FilePath
has one pathological case, and that is "". There
is a lot of ways to handle it. Here we will concentrate only few basic
techniques to illustrate versatility of our approach.
-- | Trying to set output file to "" will result in keeping original -- value. setOutputFile2 :: FilePath ->E
Config setOutputFile2 "" = id setOutputFile2 fp = setOutputFile fp example2 ::E
Config example2 =appEndo
$foldEndo
&$
setVerbosity Annoying&$
setOutputFile2 "an.out.put"
Same as above, but exploits instance
:AnEndo
a => AnEndo
Maybe
a
setOutputFile3 :: FilePath -> Maybe (E
Config) setOutputFile3 "" = Nothing setOutputFile3 fp = Just $ setOutputFile fp example3 ::E
Config example3 =appEndo
$foldEndo
&$
setVerbosity Annoying&$
setOutputFile3 "an.out.put"
Great thing about Maybe
is the fact that it has
Alternative
and MonadPlus
instances.
Using guard
may simplify setOutputFile3
in to definition
like following:
setOutputFile3':: FilePath -> Maybe (E
Config) setOutputFile3' fp = setOutputFile fp<$
guard
(not (null fp))
Following example uses common pattern of using Either
as error reporting
monad. This approach can be easily modified for arbitrary error reporting
monad.
setOutputFile4 :: FilePath -> Either String (E
Config) setOutputFile4 "" = Left "Output file: Empty file path." setOutputFile4 fp = Right $ setOutputFile fp example4 :: Either String (E
Config) example4 =appEndo
<&$>
foldEndo
<*>
pure
(setVerbosity Annoying)<*>
setOutputFile4 "an.out.put"
Notice, that above example uses applicative style. Normally, when using this
style for setting record values, one needs to keep in sync the order of
constructor arguments, and order of operations. Using foldEndo
(and its
dual dualFoldEndo
) doesn't have this restriction.
Using With Lenses
Instead of setter functions one may want to use lenses. In this example we use types from lens package, but definitions use function from between package:
verbosity :: Lens' Config Verbosity verbosity = _verbosity~@@^>
\s b -> s{_verbosity = b} outputFile :: Lens' Config FilePath outputFile = _outputFile~@@^>
\s b -> s{_outputFile = b}
Now setting values of Config
would look like:
example5 ::E
Config example5 =appEndo
$foldEndo
&$
verbosity .~ Annoying&$
outputFile .~ "an.out.put"
Other Usage
Probably one of the most interesting things that can be done with this module is following:
instanceAnEndo
Verbosity where typeEndoOperatesOn
Verbosity = ConfiganEndo
= Endo . set verbosity newtype OutputFile = OutputFile FilePath instanceAnEndo
OutputFile where typeEndoOperatesOn
OutputFile = ConfiganEndo
(OutputFile fp) =Endo
$ outputFile .~ fp example6 ::E
Config example6 =appEndo
$foldEndo
&$
Annoying&$
OutputFile "an.out.put"
Using With optparse-applicative
This is a more complex example that defines parser for optparse-applicative built on top of some of the above definitions:
options :: Parser Config options =runIdentityT
$runEndo
defaultConfig <$> options' where -- All this IdentityT clutter is here to avoid orphan instances. options' ::IdentityT
Parser (Endo
Config) options' =foldEndo
<*> outputOption -- :: IdentityT Parser (Maybe (E Config)) <*> verbosityOption -- :: IdentityT Parser (Maybe (E Config)) <*> annoyingFlag -- :: IdentityT Parser (E Config) <*> silentFlag -- :: IdentityT Parser (E Config) <*> verboseFlag -- :: IdentityT Parser (E Config) defaultConfig :: Config defaultConfig = Config Normal "" main :: IO () main = execParser (info options fullDesc) >>= print
Example of running above main
function:
>>>
:main -o an.out.put --annoying
Config {_verbosity = Annoying, _outputFile = "an.out.put"}
Parsers for individual options and flags are wrapped in IdentityT
, because
there is no following instance:
instanceFoldEndoArgs
r =>FoldEndoArgs
(Parser r)
But there is:
instance (Applicative
f,FoldEndoArgs
r) =>FoldEndoArgs
(IdentityT
f r)
Functions used by the above code example:
outputOption ::IdentityT
Parser (Maybe (E
Config)) outputOption = IdentityT . optional . option (set outputFile <$> parseFilePath) $ short 'o' <> long "output" <> metavar "FILE" <> help "Store output in to a FILE." where parseFilePath = eitherReader $ \s -> if null s then Left "Option argument can not be empty file path." else Right s verbosityOption ::IdentityT
Parser (Maybe (E
Config)) verbosityOption =IdentityT
. optional . option (set verbosity <$> parseVerbosity) $ long "verbosity" <> metavar "LEVEL" <> help "Set verbosity to LEVEL." where verbosityToStr = map toLower . Data.showConstr . Data.toConstr verbosityIntValues = [(show $ fromEnum v, v) | v <- [Silent .. Annoying]] verbosityStrValues = ("default", Normal) : [(verbosityToStr v, v) | v <- [Silent .. Annoying]] parseVerbosityError = unwords [ "Verbosity can be only number from interval" , show $ map fromEnum [minBound, maxBound :: Verbosity] , "or one of the following:" , concat . intersperse ", " $ map fst verbosityStrValues ] parseVerbosity = eitherReader $ s -> case lookup s $ verbosityIntValues ++ verbosityStrValues of Just v -> Right v Nothing -> Left parseVerbosityError annoyingFlag ::IdentityT
Parser (E
Config) annoyingFlag =IdentityT
. flag id (verbosity .~ Annoying) $ long "annoying" <> help "Set verbosity to maximum." silentFlag ::IdentityT
Parser (E
Config) silentFlag =IdentityT
. flag id (verbosity .~ Silent) $ shorts
<> long "silent" <> help "Set verbosity to minimum." verboseFlag ::IdentityT
Parser (E
Config) verboseFlag =IdentityT
. flag id (verbosity .~ Verbose) $ shortv
<> long "verbose" <> help "Be verbose."
Generic Endomorphism Folding
foldEndo :: FoldEndoArgs args => args Source
Fold all variously represented endomorphisms in to one endomorphism.
Order in which endomorphisms are folded is preserved:
>>>
foldEndo (Endo (1:)) [(2:), (3:)] `appEndo` []
[1,2,3]
For numbers it would look like:
>>>
foldEndo (Endo (+1)) [(+2), (*3)] `appEndo` 1
6
Above can be seen as:
>>>
(+1) . (+2) . (*3) $ 1
6
dualFoldEndo :: FoldEndoArgs args => args Source
Same as foldEndo
, but folds endomorphisms in reverse order.
Following are the same examples as for foldEndo
function. Please, note the
differences in results.
Order in which endomorphisms are folded is reversed:
>>>
dualFoldEndo (Endo (1:)) [(2:), (3:)] `appEndo` []
[3,2,1]
For numbers it would look like:
>>>
dualFoldEndo (Endo (+1)) [(+2), (*3)] `appEndo` 1
12
Above can be seen as:
>>>
(*3) . (+2) . (+1) $ 1
12
Type Classes
class FoldEndoArgs a where Source
Class of arguments for foldEndo
and its dual dualFoldEndo
functions.
Note that results are instances of this (FoldEndoArgs
) class and
endomorphism representations are instances of AnEndo
type class.
type ResultOperatesOn a Source
Extracts type of a value that is modified by the result.
Result type of the whole endomorphism folding. It can be used to
restrict the result of foldEndo
and dualFoldEndoArgs
. Example:
-- Type restricted version offoldEndo
that forces the result of the -- whole folding machinery to be "Endo
Int". myFoldEndo :: (Result
args ~Endo
Int,FoldEndoArgs
args) => args -> args myFoldEndo =foldEndo
foldEndoArgs :: Endo (ResultOperatesOn a) -> a Source
dualFoldEndoArgs :: Dual (Endo (ResultOperatesOn a)) -> a Source
FoldEndoArgs r => FoldEndoArgs (IO r) Source | Allows endomorphism folding for endomorphisms wrapped inside
In the next example, prefix ghci> :{ ghci| |
FoldEndoArgs r => FoldEndoArgs (Identity r) Source | |
FoldEndoArgs (Endo a) Source | |
FoldEndoArgs r => FoldEndoArgs (Maybe r) Source | |
(AnEndo a, FoldEndoArgs r, (~) * (EndoOperatesOn a) (ResultOperatesOn r)) => FoldEndoArgs (a -> r) Source | Recurse along |
FoldEndoArgs r => FoldEndoArgs (Either e r) Source | |
(Monoid c, FoldEndoArgs r) => FoldEndoArgs (Const c r) Source | This basically discards result of folding, in example:
|
(Applicative f, FoldEndoArgs r) => FoldEndoArgs (ListT f r) Source | |
(Monad m, FoldEndoArgs r) => FoldEndoArgs (MaybeT m r) Source | |
(Applicative f, FoldEndoArgs r) => FoldEndoArgs (IdentityT f r) Source | This instance can be used in cases when there is no
|
(Applicative f, FoldEndoArgs r) => FoldEndoArgs (ReaderT r' f r) Source | |
(Monad m, FoldEndoArgs r) => FoldEndoArgs (StateT s m r) Source | |
(Monad m, FoldEndoArgs r) => FoldEndoArgs (StateT s m r) Source | |
(Monad m, FoldEndoArgs r) => FoldEndoArgs (ExceptT e m r) Source | |
(Applicative f, FoldEndoArgs r, Monoid w) => FoldEndoArgs (WriterT w f r) Source | |
(Applicative f, FoldEndoArgs r, Monoid w) => FoldEndoArgs (WriterT w f r) Source | |
(Applicative f, Applicative g, FoldEndoArgs r) => FoldEndoArgs (Product f g r) Source | |
(Applicative f, Applicative g, FoldEndoArgs r) => FoldEndoArgs (Compose f g r) Source | |
(Monad m, Monoid w, FoldEndoArgs r) => FoldEndoArgs (RWST r' w s m r) Source | |
(Monad m, Monoid w, FoldEndoArgs r) => FoldEndoArgs (RWST r' w s m r) Source |
Class that represents various endomorphism representation. In other words
anything that encodes (a -> a)
can be instance of this class.
Here are some important instances with not so obvious definitions.
instanceAnEndo
(Proxy
a) where typeEndoOperatesOn
(Proxy
a) = aanEndo
_ =mempty
-- = Endoid
aDualEndo
_ =mempty
It got quite common to use Proxy
data type as an explicit way to pass
types around. Above instance allows you to restrict type of result of
endomorphism folding, to some extent.
instanceAnEndo
a =>AnEndo
(Maybe
a) where typeEndoOperatesOn
(Maybe
a) =EndoOperatesOn
aanEndo
Nothing
=mempty
-- = Endoid
anEndo
(Just
e) =anEndo
e -- Definition ofaDualEndo
is analogous.
Instance for Maybe
lets us conditionally inject endomorphism in to a
folding chain.
instanceAnEndo
a =>AnEndo
(Identity
a) where typeEndoOperatesOn
(Identity
a) =EndoOperatesOn
aanEndo
(Identity
e) =anEndo
eaDualEndo
(Identity
e) =aDualEndo
e
Above instance allows us to discard Identity
wrapper, which is commonly
used in data types that are parametrized by functor or monad.
type EndoOperatesOn a Source
Extract type on which endomorphism operates, e.g. for
(
it would be Endo
a)a
.
anEndo :: a -> Endo (EndoOperatesOn a) Source
aDualEndo :: a -> Dual (Endo (EndoOperatesOn a)) Source
Type Wrappers
newtype WrappedFoldable f a Source
Wrapper for Foldable
types. Used to provide instances that work for all
Foldable
types without the need for OverlappingInstances
language
extension.
WrapFoldable | |
|
Monad f => Monad (WrappedFoldable f) Source | |
Functor f => Functor (WrappedFoldable f) Source | |
Applicative f => Applicative (WrappedFoldable f) Source | |
Foldable f => Foldable (WrappedFoldable f) Source | |
Traversable f => Traversable (WrappedFoldable f) Source | |
Generic1 (WrappedFoldable f) Source | |
(Data (f a), Typeable (* -> *) f, Typeable * a) => Data (WrappedFoldable f a) Source | |
Read (f a) => Read (WrappedFoldable f a) Source | |
Show (f a) => Show (WrappedFoldable f a) Source | |
Generic (WrappedFoldable f a) Source | |
(Foldable f, AnEndo a) => AnEndo (WrappedFoldable f a) Source | |
type Rep1 (WrappedFoldable f) Source | |
type Rep (WrappedFoldable f a) Source | |
type EndoOperatesOn (WrappedFoldable f a) = EndoOperatesOn a Source |
Utility Functions and Types
type (:->) args r = (Result args ~ r) => args Source
Type alias that restricts type of endomorphism folding result, and it
looks similar to ->
. Example of creating version of foldEndo
with
specific result:
foldToEndoString ::FoldEndoArgs
args => args:->
Endo
String foldToEndoString =foldEndo
>>>
foldToEndoString ("foo" <>) ("bar" <>) `appEndo` "baz"
"foobarbaz"
Following type signatures for foldEndoArgs
are equivalent:
FoldEndoArgs
args => args:->
Endo
String (FoldEndoArgs
args,Result
args ~Endo
String) => args
(&$) :: (a -> b) -> a -> b infixl 1 Source
Variant of function (
, from
Data.Function module, but with fixity as
$
) :: (a -> b) -> a -> b(
function from Data.Function
module (available in base since version 4.8.0.0).&
) :: a -> (a -> b) -> b
(<&$>) :: Functor f => (a -> b) -> f a -> f b infixl 1 Source
Variant of function
(
from Data.Functor module, but with fixity as <$>
) :: Functor
f => (a -> b) -> a -> b&$
function.
:: (AnEndo e, EndoOperatesOn e ~ a) | |
=> (Endo a -> b) | Embedding function. |
-> e | |
-> b |
Use Endo
(possibly result of foldEndo
) and use it to
create value of different type.
Examples:
embedEndoWith
tell
:: (Monad m,AnEndo
e, w ~EndoOperatesOn
e) => e ->WriterT
(Endo
w) m ()embedEndoWith
(modify
.appEndo
) :: (Monad m,AnEndo
e, s ~EndoOperatesOn
e) => e ->StateT
s m ()
See also embedDualEndoWith
.
:: (AnEndo e, EndoOperatesOn e ~ a) | |
=> (Dual (Endo a) -> b) | Embedding function. |
-> e | |
-> b |
Dual to embedEndoWith
, which uses aDualEndo
instead of anEndo
.