Difference between revisions of "Prelude extensions"

From HaskellWiki
Jump to navigation Jump to search
m (Adding table of contents)
(Suggestion for hyperstrict evaluation primitive)
 
(14 intermediate revisions by 9 users not shown)
Line 1: Line 1:
 
__TOC__
 
__TOC__
 
== Sorted lists ==
 
 
The following are versions of standard prelude functions, but intended for sorted lists. The advantage is that they frequently reduce execution time by an O(n). The disadvantage is that the elements have to be members of Ord, and the lists have to be already sorted.
 
 
<haskell>
 
-- Eliminates duplicate entries from the list, where duplication is defined
 
-- by the 'eq' function. The last value is kept.
 
sortedNubBy :: (a -> a -> Bool) -> [a] -> [a]
 
sortedNubBy eq (x1 : xs@(x2 : _)) =
 
if eq x1 x2 then sortedNubBy eq xs else x1 : sortedNubBy eq xs
 
sortedNubBy _ xs = xs
 
 
sortedNub :: (Eq a) => [a] -> [a]
 
sortedNub = sortedNubBy (==)
 
 
-- Merge two sorted lists into a new sorted list. Where elements are equal
 
-- the element from the first list is taken first.
 
mergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
 
mergeBy cmp xs@(x1:xs1) ys@(y1:ys1) =
 
if cmp x1 y1 == GT
 
then y1 : mergeBy cmp xs ys1
 
else x1 : mergeBy cmp xs1 ys
 
mergeBy _ [] ys = ys
 
mergeBy _ xs [] = xs
 
 
merge :: (Ord a) => [a] -> [a] -> [a]
 
merge = mergeBy compare
 
</haskell>
 
 
   
 
== Tuples ==
 
== Tuples ==
Line 41: Line 11:
 
 
 
-- | Apply a function to the second element of a pair
 
-- | Apply a function to the second element of a pair
mapSnd :: (b -> c) -> (a, b) -> (c, b)
+
mapSnd :: (b -> c) -> (a, b) -> (a, c)
 
mapSnd f (a, b) = (a, f b)
 
mapSnd f (a, b) = (a, f b)
 
 
Line 51: Line 21:
 
[http://haskell.org/ghc/docs/latest/html/libraries/fgl/Data-Graph-Inductive-Query-Monad.html#1 Data.Graph.Inductive.Query.Monad module (section ''Additional Graph Utilities'')] contains <hask>mapFst</hask>, <hask>mapSnd</hask>, and also a function <hask>><</hask> corresponding to <hask>mapPair</hask>. Another implementation of these functions in the standard libraries: using <hask>first</hask>, <hask>second</hask>, <hask>***</hask> arrow operations overloaded for functions (as special arrows), see [http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Arrow.html Control.Arrow] module, or [[Arrow]] HaskellWiki page.
 
[http://haskell.org/ghc/docs/latest/html/libraries/fgl/Data-Graph-Inductive-Query-Monad.html#1 Data.Graph.Inductive.Query.Monad module (section ''Additional Graph Utilities'')] contains <hask>mapFst</hask>, <hask>mapSnd</hask>, and also a function <hask>><</hask> corresponding to <hask>mapPair</hask>. Another implementation of these functions in the standard libraries: using <hask>first</hask>, <hask>second</hask>, <hask>***</hask> arrow operations overloaded for functions (as special arrows), see [http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Arrow.html Control.Arrow] module, or [[Arrow]] HaskellWiki page.
   
  +
See also [[pointfree|point-free]] programming.
== Matrix ==
 
   
  +
=== Treating pairs and lists in the same way ===
Sometimes you just want to multiply 2 matrices, like
 
   
  +
We can define a Pair class which allows us to process both pairs and non-empty lists using the same operator:
[[1,2],[3,4]]*[[1,2],[3,4]]
 
   
  +
<haskell>
The following makes it possible, but requires -fglasgow-exts :
 
  +
import Control.Arrow ((***))
   
  +
infixl 4 <**>
  +
  +
class Pair p x y | p -> x, p -> y where
  +
toPair :: p -> (x, y)
  +
(<**>) :: (x -> a -> b) -> (y -> a) -> p -> b
  +
(<**>) f g = uncurry id . (f *** g) . toPair
  +
  +
instance Pair (a, b) a b where
  +
toPair = id
  +
  +
instance Pair [a] a [a] where
  +
toPair l = (head l, tail l)
  +
</haskell>
  +
  +
== Matrices ==
  +
  +
A simple representation of matrices is as lists of lists of numbers:
 
<haskell>
 
<haskell>
instance Num a => Num [[a]] where
+
newtype Matrix a = Matrix [[a]] deriving (Eq, Show)
abs x = map (map abs) x
 
(+) x y = zipWith (zipWith (+)) x y
 
(*) x y = map (matrixXvector x) y
 
where
 
matrixXvector :: [[a]] -> [a] -> [a]
 
matrixXvector m v = foldl vectorsum [] $ zipWith vectorXnumber m v
 
vectorXnumber :: [a] -> a -> [a]
 
vectorXnumber v n = map (n*) v
 
vectorsum :: [a] -> [a] -> [a]
 
vectorsum [] y = y
 
vectorsum x [] = x
 
vectorsum x y = zipWith (+) x y
 
 
</haskell>
 
</haskell>
  +
These matrices may be made an instance of <hask>Num</hask>
  +
(though the definitions of <hask>abs</hask> and <hask>signum</hask> are just fillers):
  +
<haskell>
  +
instance Num a => Num (Matrix a) where
  +
Matrix as + Matrix bs = Matrix (zipWith (zipWith (+)) as bs)
  +
Matrix as - Matrix bs = Matrix (zipWith (zipWith (-)) as bs)
  +
Matrix as * Matrix bs =
  +
Matrix [[sum $ zipWith (*) a b | b <- transpose bs] | a <- as]
  +
negate (Matrix as) = Matrix (map (map negate) as)
  +
fromInteger x = Matrix (iterate (0:) (fromInteger x : repeat 0))
  +
abs m = m
  +
signum _ = 1
  +
</haskell>
  +
The <hask>fromInteger</hask> method builds an infinite matrix, but addition and subtraction work even with infinite matrices, and multiplication works as long as either the first matrix is of finite width or the second is of finite height.
  +
Applying the linear transformation defined by a matrix to a vector is
  +
<haskell>
  +
apply :: Num a => Matrix a -> [a] -> [a]
  +
apply (Matrix as) b = [sum (zipWith (*) a b) | a <- as]
  +
</haskell>
  +
  +
== Data.Either extensions ==
  +
  +
  +
<haskell>
  +
import Data.Either
  +
  +
either', trigger, trigger_, switch :: (a -> b) -> (a -> b) -> Either a a -> Either b b
  +
  +
either' f g (Left x) = Left (f x)
  +
either' f g (Right x) = Right (g x)
  +
  +
trigger f g (Left x) = Left (f x)
  +
trigger f g (Right x) = Left (g x)
  +
  +
trigger_ f g (Left x) = Right (f x)
  +
trigger_ f g (Right x) = Right (g x)
  +
  +
switch f g (Left x) = Right (f x)
  +
switch f g (Right x) = Left (g x)
  +
  +
sure :: (a->b) -> Either a a -> b
  +
sure f = either f f
  +
  +
sure' :: (a->b) -> Either a a -> Either b b
  +
sure' f = either' f f
  +
</haskell>
  +
  +
== Schönfinkel & Curry's amalgamation combinator, for Haskell ==
  +
  +
  +
<haskell>
  +
sperse :: (a -> b -> c) -> (a -> b) -> a -> c
  +
sperse f g x = f x (g x)
  +
</haskell>
  +
  +
== Curry and Feys's paradoxical combinator, for Haskell ==
  +
  +
  +
<haskell>
  +
yet :: (a -> a) -> a
  +
yet f = f (yet f)
  +
</haskell>
  +
  +
== Hyperstrict evaluation[http://foldoc.org/hyperstrict <span></span>] ==
  +
  +
  +
<haskell>
  +
compel :: a -> a -- primitive
  +
</haskell>
  +
  +
== See also ==
  +
[[List function suggestions]]
  +
  +
  +
[[Category:Code]]

Latest revision as of 02:22, 18 May 2020

Tuples

It is often necessary to apply functions to either the first or the second part of a pair. This is often considered a form of mapping (like map from Data.List).

 -- | Apply a function to the first element of a pair
 mapFst :: (a -> c) -> (a, b) -> (c, b)
 mapFst f (a, b) = (f a, b)
 
 -- | Apply a function to the second element of a pair
 mapSnd :: (b -> c) -> (a, b) -> (a, c)
 mapSnd f (a, b) = (a, f b)
 
 -- | Apply a function to both elements of a pair
 mapPair :: (a -> c, b -> d) -> (a, b) -> (c, d)
 mapPair (f, g) (a, b) = (f a, g b)

Data.Graph.Inductive.Query.Monad module (section Additional Graph Utilities) contains mapFst, mapSnd, and also a function >< corresponding to mapPair. Another implementation of these functions in the standard libraries: using first, second, *** arrow operations overloaded for functions (as special arrows), see Control.Arrow module, or Arrow HaskellWiki page.

See also point-free programming.

Treating pairs and lists in the same way

We can define a Pair class which allows us to process both pairs and non-empty lists using the same operator:

import Control.Arrow ((***))

infixl 4 <**>

class Pair p x y | p -> x, p -> y where
    toPair :: p -> (x, y)
    (<**>) :: (x -> a -> b) -> (y -> a) -> p -> b
    (<**>) f g = uncurry id . (f *** g) . toPair

instance Pair (a, b) a b where
    toPair = id

instance Pair [a] a [a] where
    toPair l = (head l, tail l)

Matrices

A simple representation of matrices is as lists of lists of numbers:

 newtype Matrix a = Matrix [[a]] deriving (Eq, Show)

These matrices may be made an instance of Num (though the definitions of abs and signum are just fillers):

 instance Num a => Num (Matrix a) where
    Matrix as + Matrix bs = Matrix (zipWith (zipWith (+)) as bs)
    Matrix as - Matrix bs = Matrix (zipWith (zipWith (-)) as bs)
    Matrix as * Matrix bs =
       Matrix [[sum $ zipWith (*) a b | b <- transpose bs] | a <- as]
    negate (Matrix as) = Matrix (map (map negate) as)
    fromInteger x = Matrix (iterate (0:) (fromInteger x : repeat 0))
    abs m = m
    signum _ = 1

The fromInteger method builds an infinite matrix, but addition and subtraction work even with infinite matrices, and multiplication works as long as either the first matrix is of finite width or the second is of finite height. Applying the linear transformation defined by a matrix to a vector is

 apply :: Num a => Matrix a -> [a] -> [a]
 apply (Matrix as) b = [sum (zipWith (*) a b) | a <- as]

Data.Either extensions

import Data.Either

either', trigger, trigger_, switch ::  (a -> b) -> (a -> b) -> Either a a -> Either b b

either' f g (Left x) = Left (f x)
either' f g (Right x) = Right (g x)

trigger f g (Left x) = Left (f x)
trigger f g (Right x) = Left (g x)

trigger_ f g (Left x) = Right (f x)
trigger_ f g (Right x) = Right (g x)

switch f g (Left x) = Right (f x)
switch f g (Right x) = Left (g x)

sure :: (a->b) -> Either a a -> b
sure f = either f f

sure' :: (a->b) -> Either a a -> Either b b
sure' f = either' f f

Schönfinkel & Curry's amalgamation combinator, for Haskell

sperse :: (a -> b -> c) -> (a -> b) -> a -> c
sperse f g x = f x (g x)

Curry and Feys's paradoxical combinator, for Haskell

yet :: (a -> a) -> a
yet f = f (yet f)

Hyperstrict evaluation

compel :: a -> a  -- primitive

See also

List function suggestions