Do I need to bother with INLINE/INLINABLE pragmas for small, exported, functions, or will GHC do it for me? - haskell

I have a module which collects and exports a bunch of small functions such as:
fromEither :: (MonadError e m) => Either e a -> m a
fromEither = either throwError return
or
withError :: MonadError e m => (e -> e) -> m a -> m a
withError = flip catchError (throwError . f)
It's a good idea to have them inlined, as after specializing to a particular instance of MonadError it's likely a lot of code will be optimized away.
The GHC's documentation says:
GHC (with -O, as always) tries to inline (or “unfold”) functions/values that are “small enough,” thus avoiding the call overhead and possibly exposing other more-wonderful optimisations. Normally, if GHC decides a function is “too expensive” to inline, it will not do so, nor will it export that unfolding for other modules to use.
Does it mean that such functions are most likely to be treated as if they had an INLINE pragma (i.e. their non-optimised RHS recorded in the interface file)? Or do I have to add INLINE myself? Does adding it change anything (assuming GHC decides they're "small enough")?
I don't mind if GHC decides not to inline some of my functions, if it feels they're too expensive, but in general I'd like to have them inlined without polluting my source code with adding INLINE everywhere.

From my experience, such small functions will be inlined automatically and across module borders, if it makes sense.
You can check whether GHC decided to make that possible, by running ghc --show-iface on the resulting .hi-File. If it says something about an Unfolding as in the follwing example, when using this module the function will likely be inlined:
$ ghc --show-iface /usr/lib/ghc/base-4.6.0.1/Data/Either.hi
Magic: Wanted 33214052,
got 33214052
...
38da29044ff77a85b08cebca1fed11ad
either :: forall a c b.
(a -> c) -> (b -> c) -> Data.Either.Either a b -> c
{- Arity: 3, HasNoCafRefs, Strictness: LLS,
Unfolding: (\ # a
# c
# b
f :: a -> c
ds :: b -> c
ds1 :: Data.Either.Either a b ->
case ds1 of wild {
Data.Either.Left x -> f x Data.Either.Right y -> ds y }) -}

I want to add to Joachim's answer that the number of functions in the module also influences whether or not ghc will export them. For example, Pipes.Prelude from pipes would show slow-downs on several functions when I started to add several unrelated functions to the same module. Adding INLINABLE pragmas to these functions restored their original speed.

Related

How do I write a function with the signature `(Proxy a -> s) -> Proxy (Maybe a) -> Maybe s`

As per the title, I'm looking to write a function with the following signature.
g :: (Proxy a -> s) -> Proxy (Maybe a) -> Maybe s
g f x = ...
For my use case, f is symbolVal. I can run symbolVal on a plain KnownSymbol a => a, but I can't get this to work on KnownSymbol a => Maybe a.
Up to isomorphism, a type Proxy T is equal to () -- indeed both types only have one possible values.
Also, up to isomorphism, a function () -> T is equal to T -- after all the function can only be called with one value.
One can then simplify (up to isomorphism) your type as follows:
(Proxy a -> s) -> Proxy (Maybe a) -> Maybe s
~=
(() -> s) -> () -> Maybe s
~=
s -> Maybe s
Hence, your question is equivalent to "how can we implement s -> Maybe s and we only have two ways t do that:
f x = Just x
f x = Nothing
Translating back to your g we obtain the two solutions
g h _ = Just (h Proxy)
g h _ = Nothing
I don't think either of these is interesting, but there are no other (terminating) choices.
I think this is an XY question: you're asking about a different problem from what you really should be solving.
See, proxies were always just a hack to make up for the fact that Haskell isn't really designed to pass around type information like you can pass around values. (By contrast, dependently typed languages are designed up-front for doing this.) But actually, for quite a while now Haskell has included a feature that allows explicitly passing types: -XTypeApplications. So at this point proxies are basically just a legacy alternative, but in your own code I would suggest not worrying about how you can manipulate proxies or proxy-functions. Instead you should just pass around the type information explicitly, and if you need to fulfill the Proxy whvr -> argument of some library function then simply give it Proxy #whvr right there and then.
If you don't understand how to do that, give a bit more example code of the use-case in which you really have this need.

Using a lens twice

I'm struggling with using the lens library for a particular problem. I'm trying to pass
an updated data structure
a lens focussed on part of that updated structure
to another function, g. I pass both the lens and the data structure because g needs some shared information from the data structure as well as a piece of information. (If it helps, the data structure contains information on a joint probability distribution, but g only works on either marginal and needs to know which marginal I'm looking at. The only difference between the two marginals is their mean with the rest of their definition being shared in the data structure).
My first attempt looked like this
f :: Functor f => Params -> ((Double -> f Double) -> Params -> f Params) -> a
f p l = g (l %~ upd $ p) l
where upd = ...
g p x = go p p^.x
but that fails during compilation because f gets inferred as being Identity for the update and Const Double for the getter.
What's the best way to accomplish what I want to do? I can imagine being able to do one of the following:
make a copy of the lens so that the type inference can be different in each case
rather than passing the updated structure and the lens, I pass the original structure and a lens which returns a modified value (if I only want to update the part of the structure that the lens looks at).
making a better design choice for my functions/data structure
something completely different
Thanks for any help!
András Kovács answer shows how to achieve this with RankNTypes. If you wish to avoid RankNTypes, then you can use ALens and cloneLens:
f :: a -> ALens' a Int -> (Int, a)
f a l = (newvalue, a & cloneLens l .~ newvalue)
where oldvalue = a^.cloneLens l
newvalue = if oldvalue == 0 then 0 else oldvalue - 1
Control.Lens.Loupe provides operators and functions that work on ALens instead of Lens.
Note that in many cases, you should also be able to use <<%~, which is like %~ but also returns the old value, or <%~, which returns the new value:
f :: a -> LensLike' ((,) Int) a Int -> (Int, a)
f a l = a & l <%~ g
where g oldvalue = if oldvalue == 0 then 0 else oldvalue - 1
This has the advantage that it can also work with Isos or sometimes also with Traversals (when the target type is a Monoid).
You want your type signature to look like this:
f :: Params -> Lens Params Params Double Double -> ...
-- alternatively, instead of the long Lens form you can write
-- Lens' Params Double
This is not equivalent to what you wrote out in the signature, because the functor parameter is quantified inside Lens:
type Lens s t a b = forall f. Functor f => (a -> f b) -> (s -> f t)
The correct signature translates to :
f :: Params -> (forall f. Functor f => (Double -> f Double) -> Params -> f Params) -> ...
This prevents the compiler from unifying the different f parameters of different lens usages, i. e. you can use the lens polymorphically. Note that you need the RankNTypes or Rank2Types GHC extension in order to be able to write out the signature.
Benno gave the best general purpose answer.
There is two other options, however, which I offer here for completeness.
1.)
There are several Loupe combinators in Lens.
http://hackage.haskell.org/package/lens-4.1.2/docs/Control-Lens-Loupe.html
They all have names that involve #.
^# and #%= both take ALens which is a lens instantiated at a particular concrete choice of functor.
This can be useful if you need to pass around lists of lenses, or if you really really need multiple passes.
2.)
Another option, and my preferred tactic, is to figure out how to do both operations a the same time.
Here you are modifying, but want the value you just set. Well, yes can give you that by using <%~ instead of %~.
Now you only instantiate the lens at one choice of functor and your code gets faster.

Use of 'unsafeCoerce'

In Haskell, there is a function called unsafeCoerce, that turns anything into any other type of thing. What exactly is this used for? Like, why we would you want to transform things into each other in such an "unsafe" way?
Provide an example of a way that unsafeCoerce is actually used. A link to Hackage would help. Example code in someones question would not.
unsafeCoerce lets you convince the type system of whatever property you like. It's thus only "safe" exactly when you can be completely certain that the property you're declaring is true. So, for instance:
unsafeCoerce True :: Int
is a violation and can lead to wonky, bad runtime behavior.
unsafeCoerce (3 :: Int) :: Int
is (obviously) fine and will not lead to runtime misbehavior.
So what's a non-trivial use of unsafeCoerce? Let's say we've got an typeclass-bound existential type
module MyClass ( SomethingMyClass (..), intSomething ) where
class MyClass x where {}
instance MyClass Int where {}
data SomethingMyClass = forall a. MyClass a => SomethingMyClass a
Let's also say, as noted here, that the typeclass MyClass is not exported and thus nobody else can ever create instances of it. Indeed, Int is the only thing that instantiates it and the only thing that ever will.
Now when we pattern match to destruct a value of SomethingMyClass we'll be able to pull a "something" out from inside
foo :: SomethingMyClass -> ...
foo (SomethingMyClass a) =
-- here we have a value `a` with type `exists a . MyClass a => a`
--
-- this is totally useless since `MyClass` doesn't even have any
-- methods for us to use!
...
Now, at this point, as the comment suggests, the value we've pulled out has no type information—it's been "forgotten" by the existential context. It could be absolutely anything which instantiates MyClass.
Of course, in this very particular situation we know that the only thing implementing MyClass is Int. So our value a must actually have type Int. We could never convince the typechecker that this is true, but due to an outside proof we know that it is.
Therefore, we can (very carefully)
intSomething :: SomethingMyClass -> Int
intSomething (SomethingMyClass a) = unsafeCoerce a -- shudder!
Now, hopefully I've suggested that this is a terrible, dangerous idea, but it also may give a taste of what kind of information we can take advantage of in order to know things that the typechecker cannot.
In non-pathological situations, this is rare. Even rarer is a situation where using something we know and the typechecker doesn't isn't itself pathological. In the above example, we must be completely certain that nobody ever extends our MyClass module to instantiate more types to MyClass otherwise our use of unsafeCoerce becomes instantly unsafe.
> instance MyClass Bool where {}
> intSomething (SomethingMyClass True)
6917529027658597398
Looks like our compiler internals are leaking!
A more common example where this sort of behavior might be valuable is when using newtype wrappers. It's a fairly common idea that we might wrap a type in a newtype wrapper in order to specialize its instance definitions.
For example, Int does not have a Monoid definition because there are two natural monoids over Ints: sums and products. Instead, we use newtype wrappers to be more explicit.
newtype Sum a = Sum { getSum :: a }
instance Num a => Monoid (Sum a) where
mempty = Sum 0
mappend (Sum a) (Sum b) = Sum (a+b)
Now, normally the compiler is pretty smart and recognizes that it can eliminate all of those Sum constructors in order to produce more efficient code. Sadly, there are times when it cannot, especially in highly polymorphic situations.
If you (a) know that some type a is actually just a newtype-wrapped b and (b) know that the compiler is incapable of deducing this itself, then you might want to do
unsafeCoerce (x :: a) :: b
for a slight efficiency gain. This, for instance, occurs frequently in lens and is expressed in the Data.Profunctor.Unsafe module of profunctors, a dependency of lens.
But let me again suggest that you really need to know what's going on before using unsafeCoerce like this is anything but highly unsafe.
One final thing to compare is the "typesafe cast" available in Data.Typeable. This function looks a bit like unsafeCoerce, but with much more ceremony.
unsafeCoerce :: a -> b
cast :: (Typeable a, Typeable b) => a -> Maybe b
Which, you might think of as being implemented using unsafeCoerce and a function typeOf :: Typeable a => a -> TypeRep where TypeRep are unforgeable, runtime tokens which reflect the type of a value. Then we have
cast :: (Typeable a, Typeable b) => a -> Maybe b
cast a = if (typeOf a == typeOf b) then Just b else Nothing
where b = unsafeCoerce a
Thus, cast is able to ensure that the types of a and b really are the same at runtime, and it can decide to return Nothing if they are not. As an example:
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ExistentialQuantification #-}
data A = A deriving (Show, Typeable)
data B = B deriving (Show, Typeable)
data Forget = forall a . Typeable a => Forget a
getAnA :: Forget -> Maybe A
getAnA (Forget something) = cast something
which we can run as follows
> getAnA (Forget A)
Just A
> getAnA (Forget B)
Nothing
So if we compare this usage of cast with unsafeCoerce we see that it can achieve some of the same functionality. In particular, it allows us to rediscover information that may have been forgotten by ExistentialQuantification. However, cast manually checks the types at runtime to ensure that they are truly the same and thus cannot be used unsafely. To do this, it demands that both the source and target types allow for runtime reflection of their types via the Typeable class.
The only time I ever felt compelled to use unsafeCoerce was on finite natural numbers.
{-# LANGUAGE DataKinds, GADTs, TypeFamilies, StandaloneDeriving #-}
data Nat = Z | S Nat deriving (Eq, Show)
data Fin (n :: Nat) :: * where
FZ :: Fin (S n)
FS :: Fin n -> Fin (S n)
deriving instance Show (Fin n)
Fin n is a singly linked data structure that is statically ensured to be smaller than the n type level natural number by which it is parametrized.
-- OK, 1 < 2
validFin :: Fin (S (S Z))
validFin = FS FZ
-- type error, 2 < 2 is false
invalidFin :: Fin (S (S Z))
invalidFin = FS (FS FZ)
Fin can be used to safely index into various data structures. It's pretty standard in dependently typed languages, though not in Haskell.
Sometimes we want to convert a value of Fin n to Fin m where m is greater than n.
relaxFin :: Fin n -> Fin (S n)
relaxFin FZ = FZ
relaxFin (FS n) = FS (relaxFin n)
relaxFin is a no-op by definition, but traversing the value is still required for the types to check out. So we might just use unsafeCoerce instead of relaxFin. More pronounced gains in speed can result from coercing larger data structures that contain Fin-s (for example, you could have lambda terms with Fin-s as bound variables).
This is an admittedly exotic example, but I find it interesting in the sense that it's pretty safe: I can't really think of ways for external libraries or safe user code to mess this up. I might be wrong though and I'd be eager to hear about potential safety issues.
There is no use of unsafeCoerce I can really recommend, but I can see that in some cases such a thing might be useful.
The first use that springs to mind is the implementation of the Typeable-related routines. In particular cast :: (Typeable a, Typeable b) => a -> Maybe b achieves a type-safe behaviour, so it is safe to use, yet it has to play dirty tricks in its implementation.
Maybe unsafeCoerce can find some use when importing FFI subroutines to force types to match. After all, FFI already allows to import impure C functions as pure ones, so it is intrinsecally usafe. Note that "unsafe" does not mean impossible to use, but just "putting the burden of proof on the programmer".
Finally, pretend that sortBy did not exist. Consider then this example:
-- Like Int, but using the opposite ordering
newtype Rev = Rev { unRev :: Int }
instance Ord Rev where compare (Rev x) (Rev y) = compare y x
sortDescending :: [Int] -> [Int]
sortDescending = map unRev . sort . map Rev
The code above works, but feels silly IMHO. We perform two maps using functions such as Rev,unRev which we know to be no-ops at runtime. So we just scan the list twice for no reason, but that of convincing the compiler to use the right Ord instance.
The performance impact of these maps should be small since we also sort the list. Yet it is tempting to rewrite map Rev as unsafeCoerce :: [Int]->[Rev] and save some time.
Note that having a coercing function
castNewtype :: IsNewtype t1 t2 => f t2 -> f t1
where the constraint means that t1 is a newtype for t2 would help, but it would be quite dangerous. Consider
castNewtype :: Data.Set Int -> Data.Set Rev
The above would cause the data structure invariant to break, since we are changing the ordering underneath! Since Data.Set is implemented as a binary search tree, it would cause quite a large damage.

Why were Haskell 98's standard classes made inferior to Haskell 1.3's?

Before Haskell 98, there were Haskell 1.0 through 1.4. It's pretty interesting to see the development throughout the years, as features were added to the earliest versions of standardized Haskell.
For instance, the do-notation was first standardized by Haskell 1.3 (published 1996-05-01). In the Prelude, we find the following definitions (page 87):
-- Monadic classes
class Functor f where
map :: (a -> b) -> f a -> f b
class Monad m where
(>>=) :: m a -> (a -> m b) -> m b
(>>) :: m a -> m b -> m b
return :: a -> m a
m >> k = m >>= \_ -> k
class (Monad m) => MonadZero m where
zero :: m a
class (MonadZero m) => MonadPlus m where
(++) :: m a -> m a -> m a
The same definitions are found in Haskell 1.4. I do have a few problems with this (e.g. the MonadPlus reform hasn't happened here yet), but overall, it is a very nice definition.
This is very different from Haskell 98, where the following definition is found:
-- Monadic classes
class Functor f where
fmap :: (a -> b) -> f a -> f b
class Monad m where
(>>=) :: m a -> (a -> m b) -> m b
(>>) :: m a -> m b -> m b
return :: a -> m a
fail :: String -> m a
-- Minimal complete definition:
-- (>>=), return
m >> k = m >>= \_ -> k
fail s = error s
This is also the definition in Haskell 2010. I have the following problems with this definition:
MonadZero and MonadPlus are gone. They were useful classes.
In case of a pattern match failure in a do-notation...
Haskell 1.3 uses zero. The Left Zero law applies (zero >>= k = zero), so you know what's supposed to happen.
Haskell 98 uses fail msg, where msg is compiler-generated in case of GHC. Anything can happen, no guarantees about its semantics. Therefore, it's not much of a function for users. As a consequence, the behaviour of pattern match failures in Haskell 98's do-notation is unpredictable!
Names are less general (e.g. map vs. fmap). Not a big problem, but it's a thorn in my eye.
All in all, I think these changes weren't for the best. In fact, I think they were a step backwards from Haskell 1.4. Why were these things changed for Haskell 98, and why in this way?
As an aside, I can imagine the following defenses:
"fail allows for locating errors." Only for programmers, and only at runtime. The (unportable!) error message is not exactly something you want to parse. If you really care about it, you should track it explicitly. We now have Control.Failure from the failure package, which does a much better job at this (failure x behaves mostly like zero).
"Having too many classes makes development and use too hard." Having too few classes breaks their laws, and those laws are just as important as types.
"Instance-restricted functions are easier to learn." Then why isn't there a SimplePrelude instead, with most of the classes removed? It's only one magical declaration away for students, they can manage that much. (Perhaps {-# LANGUAGE RebindableSyntax #-} is needed too, but again, students are very good at copy-pasting stuff.)
"Instance-restricted functions make errors more readable." I use fmap much more often than map, so why not map and listMap instead?
Why were these things changed for Haskell 98, and why in this way?
Haskell 98 involves a lot of simplification to the language (much of which has since been reversed). The goal was to improve Haskell as a teaching language, and to make relatively conservative choices.
See e.g.
We regarded Haskell 98 as a reasonably conservative design. For
example, by that time multi-parameter type classes were being widely
used, but Haskell 98 only has single-parameter type classes (Peyton
Jones et al., 1997).
In: History of Haskell
And:
Haskell 98 will by no means be the last revision of Haskell. On the
contrary, we design it knowing that new language extensions
(multi-parameter type classes, universal and existential
quantification, pattern guards, etc, etc) are well on the way.
However, Haskell 98 will have a special status: the intention is that
Haskell compilers will continue to support Haskell 98 (given an
appropriate flag) even after later versions of the language have been
defined, and so the name `Haskell 98' will refer to a fixed, stable
language.
In: Haskell98 report
So, things were simplified, with the goal of producing a simpler standard.

Are newtypes faster than enumerations?

According to this article,
Enumerations don't count as single-constructor types as far as GHC is concerned, so they don't benefit from unpacking when used as strict constructor fields, or strict function arguments. This is a deficiency in GHC, but it can be worked around.
And instead the use of newtypes is recommended. However, I cannot verify this with the following code:
{-# LANGUAGE MagicHash,BangPatterns #-}
{-# OPTIONS_GHC -O2 -funbox-strict-fields -rtsopts -fllvm -optlc --x86-asm-syntax=intel #-}
module Main(main,f,g)
where
import GHC.Base
import Criterion.Main
data D = A | B | C
newtype E = E Int deriving(Eq)
f :: D -> Int#
f z | z `seq` False = 3422#
f z = case z of
A -> 1234#
B -> 5678#
C -> 9012#
g :: E -> Int#
g z | z `seq` False = 7432#
g z = case z of
(E 0) -> 2345#
(E 1) -> 6789#
(E 2) -> 3535#
f' x = I# (f x)
g' x = I# (g x)
main :: IO ()
main = defaultMain [ bench "f" (whnf f' A)
, bench "g" (whnf g' (E 0))
]
Looking at the assembly, the tags for each constructor of the enumeration D is actually unpacked and directly hard-coded in the instruction. Furthermore, the function f lacks error-handling code, and more than 10% faster than g. In a more realistic case I have also experienced a slowdown after converting a enumeration to a newtype. Can anyone give me some insight about this? Thanks.
It depends on the use case. For the functions you have, it's expected that the enumeration performs better. Basically, the three constructors of D become Ints resp. Int#s when the strictness analysis allows that, and GHC knows it's statically checked that the argument can only have one of the three values 0#, 1#, 2#, so it needs not insert error handling code for f. For E, the static guarantee of only one of three values being possible isn't given, so it needs to add error handling code for g, that slows things down significantly. If you change the definition of g so that the last case becomes
E _ -> 3535#
the difference vanishes completely or almost completely (I get a 1% - 2% better benchmark for f still, but I haven't done enough testing to be sure whether that's a real difference or an artifact of benchmarking).
But this is not the use case the wiki page is talking about. What it's talking about is unpacking the constructors into other constructors when the type is a component of other data, e.g.
data FooD = FD !D !D !D
data FooE = FE !E !E !E
Then, if compiled with -funbox-strict-fields, the three Int#s can be unpacked into the constructor of FooE, so you'd basically get the equivalent of
struct FooE {
long x, y, z;
};
while the fields of FooD have the multi-constructor type D and cannot be unpacked into the constructor FD(1), so that would basically give you
struct FooD {
long *px, *py, *pz;
}
That can obviously have significant impact.
I'm not sure about the case of single-constructor function arguments. That has obvious advantages for types with contained data, like tuples, but I don't see how that would apply to plain enumerations, where you just have a case and splitting off a worker and a wrapper makes no sense (to me).
Anyway, the worker/wrapper transformation isn't so much a single-constructor thing, constructor specialisation can give the same benefit to types with few constructors. (For how many constructors specialisations would be created depends on the value of -fspec-constr-count.)
(1) That might have changed, but I doubt it. I haven't checked it though, so it's possible the page is out of date.
I would guess that GHC has changed quite a bit since that page was last updated in 2008. Also, you're using the LLVM backend, so that's likely to have some effect on performance as well. GHC can (and will, since you've used -O2) strip any error handling code from f, because it knows statically that f is total. The same cannot be said for g. I would guess that it's the LLVM backend that then unpacks the constructor tags in f, because it can easily see that there is nothing else used by the branching condition. I'm not sure of that, though.

Resources