Skip to content

Instantly share code, notes, and snippets.

View schar's full-sized avatar
💭
🦧

Simon Charlow schar

💭
🦧
View GitHub Profile
@schar
schar / avoidf.hs
Last active September 6, 2016 00:22
{-# LANGUAGE FlexibleInstances #-}
module Main (main) where
main :: IO ()
main = return ()
type E = String
type T = String
data F a = F a [a] deriving (Show, Eq)
@schar
schar / AvoidF.hs
Last active January 17, 2021 12:26
AvoidF, without transderivationality, using Functors
-- details here http://tiny.cc/avoidf
{-# LANGUAGE FlexibleInstances #-}
module Main (main) where
type E = String
type T = String
data F a = F a [a] deriving (Show, Eq)
@schar
schar / modnum.hs
Last active May 1, 2016 13:51
but this works whyyyyyy 🤔
module Main (main) where
import Data.List
type EBase = String
type E = [EBase]
data Var = W | X | Y | Z deriving (Show, Eq)
vars :: [Var]
vars = [W, X, Y, Z]
{-- to add: monads, semantics, binding[?] --}
import Data.List
data Type = DP | S | NP | V | Stop -- atomic cats
| FS Type Type | BS Type Type -- {/, \}
| US Type Type -- | (for events/modification)
| FF Type Type | BB Type Type -- {//, \\}
deriving (Show, Eq)
data Tree = Atom String | Bin String TTree TTree
{-- to add: semantics, binding[?] --}
import Data.Char
import Data.List
data Type =
E | T | N | V | -- atomic cats
M Type | -- monads
FS Type Type | BS Type Type | -- {/ , \}
FF Type Type | BB Type Type | -- {//,\\}
X -- islands punctuation
import Control.Arrow ((>>>))
import Data.List
type EBase = String -- atoms
type E = [EBase] -- atoms and non-atoms
data Var = W | X | Y | Z deriving (Show, Eq)
vars :: [Var]
vars = [W, X, Y, Z]
@schar
schar / update.hs
Last active September 4, 2016 22:40
generalized monadic update semantics
import Control.Applicative
import Control.Monad
newtype Upd m s a = Upd { runUpd :: m s -> m (a,s) }
instance Monad m => Monad (Upd m s) where
return x = Upd $ \ss -> do s <- ss
return (x,s)
Upd m >>= k = Upd $ \ss -> do (a,s) <- m ss
runUpd (k a) (return s)
@schar
schar / curryD.hs
Last active September 11, 2016 17:41
dynamic assignments on the fly
type E = Int
type D s a = s -> Maybe (a, s)
unit :: a -> D s a
unit x i = Just (x, i)
bind :: D s a -> (a -> D s b) -> D s b
bind m k i = m i >>= uncurry k
heD :: D E E
type E = Int
type D r a = r -> (a, r)
unit :: a -> D r a
unit x i = (x, i)
bind :: D r a -> (a -> D r b) -> D r b
bind m k i = uncurry k $ m i
he :: E -> E
@schar
schar / isosRS.hs
Created September 12, 2016 20:37
uncurrying reader and state
type R r a = r -> a
uncurryR :: R r (R s a) -> R (r, s) a -- an isomorphism
uncurryR m (r, s) = m r s
curryR :: R (r, s) a -> R r (R s a) -- another isomorphism
curryR m r s = m (r, s)
type S r a = r -> (a, r)