Skip to content

Instantly share code, notes, and snippets.

View yasuabe's full-sized avatar

Yasuyuki Abe yasuabe

View GitHub Profile
@yasuabe
yasuabe / Simpath.Edge.hs
Last active May 12, 2017 12:27
haskell implementation of Simpath: Edge
module Simpath.Edge where
import Prelude hiding (either)
import Data.Function
import Data.Set (Set)
import Control.Applicative
import qualified Data.Set as Set
import qualified Data.Foldable as Foldable
type Node = Int
@yasuabe
yasuabe / Simpath.Frontier.hs
Created May 12, 2017 12:37
haskell implementation of simpath: Frontier
{-# LANGUAGE FlexibleContexts #-}
module Simpath.Frontier where
import Control.Applicative
import Control.Monad
import Control.Monad.State (State, state, get, put, runState)
import Data.Set (Set)
import qualified Data.Set as Set
import qualified Data.Foldable as Foldable
import Simpath.Common
@yasuabe
yasuabe / Simpath.CounterMap.hs
Created May 12, 2017 12:43
haskell implementation of simpath: CounterMap
module Simpath.CounterMap where
import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.Foldable as Foldable
import Data.Function
import qualified Simpath.Frontier as F
import Simpath.Frontier (Frontier)
import Simpath.Border (Border)
@yasuabe
yasuabe / Simpath.Border.hs
Last active May 12, 2017 13:00
haskell implementation of simpath: Border
module Simpath.Border where
import Control.Monad.State (State, get, put, evalState)
import Simpath.Common
import Simpath.Edge
import Data.Set (Set)
import qualified Data.Set as Set
data Border = Border { edge :: Edge, done :: Maybe Int } deriving (Show)
@yasuabe
yasuabe / Simpath.Common.hs
Created May 12, 2017 13:00
haskell implementation of simpath: Common
module Simpath.Common where
justIf :: Bool -> a -> Maybe a
justIf b a = if b then Just a else Nothing
mapOrElse :: (a -> b) -> b -> Maybe a -> b
mapOrElse f b ma = case ma of { Just a -> f a; _ -> b }
@yasuabe
yasuabe / Simpath.Main.hs
Created May 12, 2017 13:02
haskell implementation of simpath: Main
import System.Environment
import Simpath.Border (borders)
import Simpath.Edge (Edge, edge, modify)
import Simpath.CounterMap
gridEdges :: Int -> [Edge]
gridEdges size = upper ++ lower
where
upper = snd $ foldl (\(c, ts) n -> (c + n, ts ++ edgesAt n c)) (0, []) [1 .. size-1]
where edgesAt n acc = map (+ acc) [1 .. n] >>= addPair
@yasuabe
yasuabe / scenario_test_for_free_service.sc
Last active December 7, 2017 11:10
Free Monadを用いた Serviceコードのシナリオテストの試案
import scala.language.higherKinds
import cats.data.StateT
import cats.free.Free
import cats.~>
import cats.instances.all._
import iota.TListK.:::
import iota.{CopK, TNilK}
import Free.inject
@yasuabe
yasuabe / hylomorphism.sc
Last active March 8, 2019 21:05
階乗とフィボナッチの両方で使えるhylomorphismを書いてみる
import cats.Functor
import cats.syntax.functor._
// hylomorphism -----------------
type Algebra[F[_], B] = F[B] => B
type Coalgebra[F[_], A] = A => F[A]
def hylomorphism[F[_]: Functor, A, B](
alg: Algebra[F, B],
coalg: Coalgebra[F, A])(seed: A): B =
@yasuabe
yasuabe / Chapter01.scala
Last active December 15, 2017 21:58
ch01 multi-currency money
package fp_tdd
import org.scalacheck.Prop.forAll
import org.scalacheck.Properties
object Chapter01 extends Properties("Ch01") {
// ======== TODO ========
// $5 + 10 CHF = $10 if rate is 2:1
// Make "amount" private
// Dollar side effect
@yasuabe
yasuabe / Chapter02.scala
Created December 15, 2017 15:03
ch02 degenerate objects
package fp_tdd
import org.scalacheck.Prop.forAll
import org.scalacheck.Properties
object Chapter02 extends Properties("Ch02") {
// ======== TODO ========
// $5 + 10 CHF = $10 if rate is 2:1
// Make "amount" private
// Money rounding?