6

I want to convert a function A -> IO B to IO (A -> B), knowing that there is only a finite number of possible values of A. At the moment I just do

 convert :: (A -> IO B) -> IO (A -> B)
 convert f = do
     b1 <- f a1
     b2 <- f a2
     ...
     let f' a1 = b1
         f' a2 = b2
         ...
     return f'

However I'm not satisfied with the amount of code this requires.

Karolis Juodelė
  • 3,708
  • 1
  • 19
  • 32

5 Answers5

9

A slightly souped-up version of Joachim's answer, that uses Data.Map to perform the lookup faster. I'll be using the TupleSections pragma as well.

{-# LANGUAGE TupleSections #-}

import Data.Map
import Control.Monad

For added neatness, assume that your Piece type can be given Ord, Bounded and Enum instances.

data Piece = Knight | Bishop | Rook deriving (Ord,Bounded,Enum,Show)

and define the useful enumerate function

enumerate :: (Bounded a, Enum a) => [a]
enumerate = [minBound..maxBound]

Now you can do

convert :: (Monad m, Bounded a, Enum a, Ord a) => (a -> m b) -> m (a -> b)
convert f = do
    memo <- sequence [liftM (a,) (f a)  | a <- enumerate]
    return (fromList memo!)
Chris Taylor
  • 46,912
  • 15
  • 110
  • 154
6

If you have a list values :: [A], and A has an Eq-Instance, this would work:

convert :: (A -> IO B) -> IO (A -> B)
convert f = do
  lookupTable <- sequence [ (\b -> (a,b)) `fmap` f a | a <- values]
  return $ (\a -> fromJust (lookup a lookupTable))

As other have noted, if you don’t mind the additional type class requirements for A, you can use maps or hashmaps to speed up the lookup.

Also, from your use-case description, it seems that you are loading static data from a file that comes with your program. Depending on the environment where your final program runs (e.g. guaranteed that the files exist and are not changing), this might be a valid use for unsafePerformIO to simply define A -> B as a top-level function. Alternatively there are ways to include binary blobs in the compile source.

Joachim Breitner
  • 25,395
  • 6
  • 78
  • 139
  • I really dislike this, for it's use of `Maybe`, but then I suspect this is the best I'll get.. – Karolis Juodelė Sep 19 '13 at 09:30
  • @KarolisJuodelė I'd like to add that I'd call `convert` only once and then use the function it produces to make lookups in pure code. This will ensure that you read `B`s only once. A slight improvement would be to use `Data.Map` instead of a list to get a bit faster lookups. And if you want to avoid `fromJust`, you could have/load some default `B` value and use `fromMaybe theDefault` instead of `fromJust`. – Petr Sep 19 '13 at 11:27
  • Unless you have a language that allows you to express that `values` really contains all values (maybe in Agda you can do that), you will have partialness of one form of the other (possibly using a default value as a backup). – Joachim Breitner Sep 19 '13 at 12:55
  • There's the [`universe`](http://hackage.haskell.org/package/universe-0.4.0.3) package which indicates finite domains by fiat. I also remember a blog post somewhere (perhaps Russel O'Connor's blog) which had a typeclass that was likely impossible to instantiate for infinite types. Either of these would justify using something unsafe like `fromJust`. – J. Abrahamson Sep 19 '13 at 17:14
  • Actually it was probably Martin Escardo's work, but I can't find it. – J. Abrahamson Sep 19 '13 at 17:16
  • And it would probably not be impossible in Haskell, if definitions were allowed to be partial. – Joachim Breitner Sep 19 '13 at 18:27
  • @KarolisJuodelė you cannot get this conversion for arbitrary functions, and there is a theoretical reason for that. But you can do that for arbitrary monads in Haskell using pairs. Everyone here suggested only sugar to expose function-like interface to a list of pairs built for known inputs. – Sassa NF Sep 19 '13 at 18:34
4

For the sake of completeness, I'll mention that the countable package on Hackage makes this possible by providing the Finite type class. You define something like

instance Finite Piece where
  allValues = [Pawn, Knight, Bishop, Rook, Queen, King]

then you have

assemble :: (Finite a, Applicative f) => (a -> f b) -> f (a -> b)

which will specialise to precisely what you need.

Looking at the source, it seems that it uses an association list, so it would be slow if your type was large. Plus, it defines some orphan instances of Foldable and Traversable and Eq (!) for functions, which some may regard as distasteful.

Ben Millwood
  • 6,754
  • 24
  • 45
0

You have function f :: A -> IO B and you have g :: IO A, you use your convert function with Applicative <*> :: f (a -> b) -> f a -> f b as

fg :: IO a -> (a ->IO B) -> IO B
fg g f = (convert f) <*>  g

But you can just use monad (>>=) :: m a -> (a -> m b) -> m b,

fg :: IO a -> (a ->IO B) -> IO B
fg g f = g >>= f
viorior
  • 1,783
  • 11
  • 16
  • I most definitely do not use my convert like that. Instead I do `pureF <- convert ioF` in my `main` and then pass `pureF` around in my pure functions. – Karolis Juodelė Sep 19 '13 at 09:57
  • Thanks, I understand your position. But in case `pureF <- convert ioF` you have unsafe functions instead of having unsafe data. – viorior Sep 19 '13 at 10:06
  • There is nothing unsafe about this. I merely perform the side effects before using their results. – Karolis Juodelė Sep 19 '13 at 10:21
0

Your function signature permits any function a->m b on input, yet inside you assume a specific range of values. convert is not as polymorphic as the signature seems to declare.

What you have done is created a Map from a to b, then made a pure function that looks up a pure value in that map. Here's why:

What you are asking for is similar to implementing tensorial strength strength :: (Monad m) => (a, m b) -> m (a, b) for a monoidal category (C, ⊗, I) - given a binary relation ⊗ in category C and a monad m, convert a ⊗ m b to m (a ⊗ b). When this is possible for a binary relationship that meets certain requirements, the monad is strong. In Haskell all monads are strong, if tensorial product a ⊗ b is chosen to be a pair (a, b): strength (a, mb) = mb >>= return . (a,). Yet, here you are attempting to do the same for a binary relationship ->. Unfortunately, a -> b cannot be chosen to be a tensor product, because it is not a bi-functor - it is contravariant in a. So what you want cannot be accomplished for arbitrary functions.

What is different in your case, is that essentially you built all pairs (a,b). The amount of code, therefore, can be reduced if you explicitly enumerate all possible pairs of a and b, for example by building a m (Map a b). The others here offered nice sugars exposing "function-like" interfaces, but they are merely lookups in the map.

Sassa NF
  • 5,306
  • 15
  • 22
  • It seems to me that since `->` is, as you point out, not even the right sort of thing to be a tensor product, the discussion of `strength` is not really relevant. – Ben Millwood Sep 19 '13 at 18:09
  • @BenMillwood It seems to me that it should be clear from the discussion of `strength` why what the topic starter wants is not even achievable for arbitrary functions, and in what form it is achievable. – Sassa NF Sep 19 '13 at 18:15
  • @BenMillwood also, what the others suggested is a sugar around a plain lookup, or map from known keys to precomputed values. – Sassa NF Sep 19 '13 at 18:29