Skip to content
Snippets Groups Projects
Commit ca41b96c authored by Conor McBride's avatar Conor McBride
Browse files

a bit of Stuff

parent 247f9da3
No related branches found
No related tags found
No related merge requests found
:set -pgmL markdown-unlit
../.ghci
\ No newline at end of file
BwdFwd.md
\ No newline at end of file
Backwards and Forwards Lists
============================
I like to have types of backwards and forwards lists that are not the built in
list types.
``` haskell
{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
module BwdFwd where
data Bwd x = B0 | Bwd x :< x
deriving (Functor, Foldable, Traversable, Show, Eq)
infixl 5 :<
data Fwd x = F0 | x :> Fwd x
deriving (Functor, Foldable, Traversable, Show, Eq)
infixr 5 :>
```
I tend to call forwards lists things like `xs`, while the backwards lists
get called things like `xz`. The `z` is like an `s` backwards, and perhaps
also suggestive of zipper constructions.
They are intended to capture spatially organised data, so they are
not `Monad` instances, and they are applicative in the manner of zip.
``` haskell
instance Applicative Bwd where
pure x = pure x :< x
(fz :< f) <*> (sz :< s) = (fz <*> sz) :< f s
_ <*> _ = B0
instance Applicative Fwd where
pure x = x :> pure x
(f :> fs) <*> (s :> ss) = f s :> (fs <*> ss)
_ <*> _ = F0
```
Of course, they are `Monoid`s.
``` haskell
instance Monoid (Bwd x) where
mempty = B0
mappend xz B0 = xz
mappend xz (yz :< y) = mappend xz yz :< y
instance Monoid (Fwd x) where
mempty = F0
mappend F0 ys = ys
mappend (x :> xs) ys = x :> mappend xs ys
```
You can shuffle between them.
``` haskell
(<><) :: Bwd x -> Fwd x -> Bwd x
xz <>< F0 = xz
xz <>< (x :> xs) = (xz :< x) <>< xs
infixl 5 <><
(<>>) :: Bwd x -> Fwd x -> Fwd x
B0 <>> xs = xs
(xz :< x) <>> xs = xz <>> (x :> xs)
infixr 5 <>>
```
Colloquially, `<><` is known as &lsquo;fish&rsquo; because it looks like one.
That means `<>>` gets called &lsquo;chips&rsquo;.
### Boring superclass instances
``` haskell
instance Semigroup (Bwd x) where (<>) = mappend
instance Semigroup (Fwd x) where (<>) = mappend
```
\ No newline at end of file
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment