Skip to content

Instantly share code, notes, and snippets.

@myuon
myuon / makeClassy.hs
Last active December 21, 2015 18:39
makeClassyを使って複数のオブジェクトで共通する函数をまとめる
{-# LANGUAGE TemplateHaskell, FlexibleContexts, FlexibleInstances, UndecidableInstances, OverlappingInstances #-}
import Control.Lens
import Control.Monad.State
-- 基本となるオブジェクト
data Obj = Obj {
_pos :: Int
} deriving (Show)
-- Obj型のオブジェクトをもつ抽象的なクラスHasObjを作る
@myuon
myuon / End.hs
Created August 2, 2013 13:51
とりあえず書いてみたところまで(結局endまで出来てない)
{-# LANGUAGE GADTs, RankNTypes, MultiParamTypeClasses, FlexibleInstances #-}
module End where
import qualified Prelude
import Control.Category
import Data.Monoid
import Data.Functor.Identity
type Hask = (->)
{-# LANGUAGE GADTs #-}
import Control.Monad
import Control.Monad.Operational.Simple
data Simple a where
End :: Simple a
Put :: String -> Simple ()
Get :: Int -> Simple String
put :: String -> Program Simple ()
@myuon
myuon / ProofSystem.hs
Created April 29, 2013 09:15
Proof System on Haskell (incomplete)
{-# LANGUAGE DeriveFunctor, TypeOperators #-}
import Prelude hiding (True, False, init, id)
import Control.Category
import Control.Arrow
import Control.Monad.Free
newtype Atom a b = Atom { runAtom :: a -> b }
data Formula a b = True
import Control.Monad.Free
-- data Maybe a = Nothing | Just a
data Simple a next = End next | Data a next | Skip a next
deriving (Show)
instance Functor (Simple a) where
fmap f (End next) = End (f next)
fmap f (Data a next) = Data a (f next)
fmap f (Skip a next) = Skip a (f next)
import Data.Char
import Data.List
import Data.Array
import System.Environment (getArgs)
type Board = Array (Int,Int) Int
type BFilter = Array (Int,Int) [Int]
width = 9
toLine :: String -> [Int]
@myuon
myuon / gist:3726663
Created September 15, 2012 06:46 — forked from ikedaisuke/gist:916931
Rotate a square in Gloss (with key event (DOWN-key))
module Main where
-- http://www.f13g.com/%A5%D7%A5%ED%A5%B0%A5%E9%A5%DF%A5%F3%A5%B0/Haskell/GLUT/#content_1_4
import Graphics.Gloss
import Graphics.Gloss.Interface.Pure.Game
data State
= State { angle :: Float
, isPositive :: Bool
@myuon
myuon / gist:3386693
Created August 18, 2012 13:03
SKIコンビネータ2
\abf.fab
= \abf.(I f)(K (ab)f)
= \ab.SI(K(ab))
= \ab.(K(SI)(ab))(K(ab))
= \ab.S(K(SI))K(ab)
= \ab.(K(S(K(SI))K) b)(a b)
= \ab.S(K(S(K(SI))K))ab
= S(K(S(K(SI))K))
@myuon
myuon / gist:3369859
Created August 16, 2012 12:42
SKIコンビネータ
inc := \nfx.f(nfx)
inc
= \xyz.y(xyz)
= \xyz.(Ky z)(xy z)
= \xyz.S(Ky)(xy)z
= \xy.S(Ky)(xy)
= \xy.((KSy)(Ky))(xy)
= \xy.(S(KS)Ky)(xy)
= \xy.S(S(KS)K)xy