Skip to content

Instantly share code, notes, and snippets.

@dbaynard
Created November 25, 2018 14:36
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save dbaynard/9fabf089ca35c9f590b7a4e041faf51c to your computer and use it in GitHub Desktop.
Save dbaynard/9fabf089ca35c9f590b7a4e041faf51c to your computer and use it in GitHub Desktop.
Haskell snippets
---
title: Forestay
author: David Baynard
date: 05 Jun 2017
fontfamily: libertine
csl: chemical-engineering-science.csl
link-citations: true
abstract: |
...
There are many common functions I often need. Until I PR them upstream into libraries, here they go.
They only require
# Preamble
```haskell
{-# LANGUAGE
PackageImports
, TypeInType
, TypeFamilies
, TypeOperators
, TypeApplications
#-}
module Forestay
( type ($)
, IdK(Id)
, onJust
, funzip
, azip
, lfZip
, rfZip
, reverseBits
, reverseByte
) where
import "base" Control.Arrow ((&&&))
import "base" Data.Bits
import "base" Data.Word
```
# Types
## `$` (and `'Id`) — (_defunctionalization_)
It would be useful to have an equivalent of `$` for types, to reduce parentheses.
This is implemented as a type family.
In addition it is occasoinally useful to have a type constructor which does nothing.
`'Id`, when applied with `$`, is such a constructor.
```haskell
data IdK = Id
type family ($) (x :: k) (y :: j) :: j where
'Id $ y = y
(x :: j -> j) $ y = x y
infixr 0 $
```
For example,
``` { .haskell .ignore }
type Something p =
( p $ Bool
, p $ Int
)
test1 :: Something Id
test1 = (True :: Bool, 0 :: Int)
test2 :: Something Maybe
test2 = (Just True, Just 0)
```
# Combinators
## Folds over data types
This is like `maybe`, but the last parameter is the continuation for Just
```haskell
onJust :: Maybe a -> b -> (a -> b) -> b
onJust ma b = maybe b `flip` ma
{-# INLINE onJust #-}
infix 1 `onJust`
```
## Zipping with functors
It is more than occasionally useful to be able to wrap and unwrap pairs around functors, and vice versa.
```haskell
funzip :: Functor f => f (a, b) -> (f a, f b)
funzip = fmap fst &&& fmap snd
{-# INLINE funzip #-}
```
```haskell
azip :: Applicative f => (f a, f b) -> f (a, b)
azip = uncurry $ (<*>) . fmap (,)
{-# INLINE azip #-}
rfZip :: Functor f => (a, f b) -> f (a, b)
rfZip = uncurry (fmap . (,))
{-# INLINE rfZip #-}
lfZip :: Functor f => (f a, b) -> f (a, b)
lfZip = uncurry $ (. flip (,)) . flip fmap
{-# INLINE lfZip #-}
```
# Bit twiddling
```haskell
reverseBits :: FiniteBits a => a -> a
reverseBits n = let z = [0..finiteBitSize n] in
foldr (uncurry f) n . zip z . reverse $ testBit n <$> z
where
f r True = flip setBit r
f r False = flip clearBit r
-- | <http://graphics.stanford.edu/~seander/bithacks.html>
reverseByte :: Word8 -> Word8
reverseByte = fromIntegral @Word64 @Word8 .
(`shiftR` 32) .
(* 0x0101010101) .
(.&. 0x0884422110) .
(* 0x80200802) .
fromIntegral @Word8 @Word64
```
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment