Skip to content

Instantly share code, notes, and snippets.

View yasuabe's full-sized avatar

Yasuyuki Abe yasuabe

View GitHub Profile
@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.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.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.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.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