Skip to content

Instantly share code, notes, and snippets.

@daig
Created April 8, 2020 07:30
Show Gist options
  • Save daig/bd96c562aaa7e30630ef839607493d93 to your computer and use it in GitHub Desktop.
Save daig/bd96c562aaa7e30630ef839607493d93 to your computer and use it in GitHub Desktop.
Fun.hs
{-# language UndecidableInstances #-}
{-# language PostfixOperators #-}
module Fun where
import Prelude hiding ((.),($),(/))
import qualified Prelude as P
import Data.List
import Data.Bool
import Control.Exception
import qualified Data.Map as M
import qualified Data.Set as S
import Data.Functor.Identity
import GHC.Types
import Data.Monoid
import Data.Maybe
import Control.Applicative
type (?) = Maybe
type Map = Functor
type B = Bool
type (⊕) = Either
type Î = Identity
pattern Î a = Identity a
type T = Type
type C = Constraint
class U x; instance U x
type (c :: k -> C) ==> c' = forall x. (c x => c' x)
î :: a -> a; î = id
--[1,2,3].foo & 1 + 1 & 3*12
-- .bar 10
-- .baz⊲quoz
--(?) = bool
infixl 1 .
infixl 2 &
infixl 7 ÷
infixr 9 ⊲
infix ⌿, ⍀
(÷) = (P./)
(×) = (P.*)
zz = (⍉[1,2,3])\ i -> i+i .print⊲show
a.f = f a
f&a = f a
(↯) = error
infixr 6 ∙ -- TODO: this is default
(∙) :: Semigroup a => a -> a -> a
(∙) = (<>)
(!) :: Exception e => IO a -> (e -> IO a) -> IO a
(!) = catch
(⁉) :: Exception e => IO a -> IO (e⊕a)
(⁉) = try
xxx = [1,2,3]∀even
(∀),(∃) :: Foldable t => t a -> (a -> B) -> B
(∃) = flip any
(∀) = flip all
(⊔),(⊓) :: Ord a => a -> a -> a
(⊔) = max
(⊓) = min
add = (+)
cons = (:)
vv = [1..10].add⌿0
ww = add⌿0&[1..10]
($),(¨) :: Map f => (a -> b) -> f a -> f b
($) = fmap
(¨) = fmap
(⍨),(⍉) :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)
(⍨) = traverse -- U+2368
(⍉) = traverse
--a⋄b
--a∘b
(⍣), (//) :: (Foldable t, Monoid a) => (x -> a) -> t x -> a
(//) = foldMap
(⍣) = foldMap
ff = Sum⍣[1,2,3]
fld :: (Foldable t, Monoid a) => t a -> a
fld = (î⍣)
(⌿) :: Foldable t => (b -> a -> b) -> b -> t a -> b
(⌿) = foldl'
(⍀) :: Foldable t => (a -> b -> b) -> b -> t a -> b
(⍀) = foldr
(⊲) :: (x -> b) -> (a -> x) -> a -> b
f⊲g = \a -> f (g a)
(⊳) :: (a -> x) -> (x -> b) -> a -> b
f⊳g = \a -> g (f a)
mul = (*)
--(/) = (⊳)
(↑),(↓) :: [a] -> Int -> [a]
(↑) = flip take
(↓) = flip drop
(↟),(↡) :: [a] -> (a -> B) -> [a]
(↟) = flip takeWhile
(↡) = flip dropWhile
--testDrop = (↡ \ x -> odd x) [1..10]
--testDrop = [1..10].(↡odd)
testDrop = [1..10]↡odd
(/) = flip mapMaybe
tt = (/î)
(?) p = if p then (⊣) else (⊢)
-- From Protolude
guarded, (¿):: Alternative f => (a -> B) -> a -> f a
guarded p a = p a?empty&pure a
(¿) = guarded
-- From Protolude
guardedA,(¿¿) :: (Functor f, Alternative t) => (a -> f B) -> a -> f (t a)
guardedA p a = (¨p a)\b->b?empty&pure a
(¿¿) = guardedA
train,(%) :: (a -> x -> c) -> (b -> x) -> a -> b -> c
train axc bx a = axc a ⊲ bx
(%) = train
foo = filter
--bar = zip / zipWith
(⊣) :: a -> b -> a
a⊣b = a
(⊢) :: a -> b -> b
a⊢b = b
(⍳) :: (a -> B) -> [a] -> (?)Int
(⍳) = findIndex
(⍸) = findIndices
infix 4 ∋ -- TODO: this is default
(∋) :: (Foldable t, Eq a) => t a -> a -> B
(∋) = flip elem
(⍷) :: Foldable t => (a -> B) -> t a -> (?)a
(⍷) = find -- TODO: it sucks that its backwards
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment