Skip to content

Instantly share code, notes, and snippets.

@nobsun
nobsun / F05.hs
Last active May 25, 2017 10:10
「ブロックを回す」問題 ref: http://qiita.com/nobsun/items/a48a372dcb1b95199e84
module F05 where
import Control.Arrow (first, (&&&))
import Data.Bool
import Data.List (sortBy,transpose,intercalate,isPrefixOf)
import Data.List.Split (splitOn)
import Data.Ord (comparing)
import Data.Tuple (swap)
rot :: ([String] -> [String], [String] -> [String]) -> [String] -> [String]
@nobsun
nobsun / lazyIO.hs
Created May 22, 2017 07:27
lazy IO と imperative programming とが相性がわるい例
module Main where
import System.IO.Unsafe
lazy :: IO a -> IO a
lazy = unsafeInterleaveIO
main :: IO ()
main = do
{ input1 <- getLine
@nobsun
nobsun / F04.hs
Created April 23, 2017 12:19
「正八角形の分割」問題 ref: http://qiita.com/nobsun/items/2c227bab1156eddeb3df
module F04 where
import Data.Bool (bool)
import Data.List (sort,unfoldr)
import Text.Printf (printf)
readDiag :: String -> Word
readDiag = read
toBin :: Word -> String
@nobsun
nobsun / E13.hs
Created April 23, 2017 12:11
「六角形のテトロミノ」問題 ref: http://qiita.com/nobsun/items/4099ee005e300b3dbb0c
module E13 where
import Data.List
import Data.Maybe
type CubeCoord = (Int, Int, Int)
cubecoord :: Char -> Maybe CubeCoord
cubecoord 'a' = Just (0,0,0)
cubecoord 'b' = Just (1,-1,0)
@nobsun
nobsun / F03.hs
Created March 23, 2017 01:12
「トリオミノの分類」問題 ref: http://qiita.com/nobsun/items/2b9b15bcaa50b32e4fbb
module F03 where
import Data.Ix (range)
import Data.List (sort)
import Data.Maybe (mapMaybe)
import Data.Tuple (swap)
type Index = (Int,Int)
type Omino = [Index]
type Moves = [Index]
@nobsun
nobsun / O24.hs
Last active March 20, 2017 01:41
関数プログラミングの気分(『多段階選抜』問題を題材にして) ref: http://qiita.com/nobsun/items/4562b728ecd560557bd2
module O24 where
import Data.Char (digitToInt)
import Data.List (intercalate)
type Problem = String
type Answer = String
o24 :: Problem -> Answer
o24 = intercalate "," -- 文字列のリストを "," を挟んで連結する
@nobsun
nobsun / F01.hs
Last active March 8, 2017 21:06
ふたマスの領域の数 ref: http://qiita.com/nobsun/items/c29e0e56de478303259a
module F01 where
import Control.Arrow
import Numeric
import Data.Char
import Data.Function
import Data.List
import Text.Printf
import Debug.Trace
{-# LANGUAGE FlexibleContexts #-}
module E11 where
import Data.List
import Data.Ord
import qualified Data.Set as S
import Data.Tree
import Math.NumberTheory.ArithmeticFunctions
type NodeID = Int
@nobsun
nobsun / F02.hs
Created March 6, 2017 10:30
2つの矩形に含まれるマス目の数 ref: http://qiita.com/nobsun/items/3b436fa0349e8bd5de29
module F02 where
import Control.Arrow
import Data.Ix
import Data.List
type Range = ((Int,Int),(Int,Int))
readRange :: String -> Range
readRange s = case break (','==) s of
import Control.Arrow
import Data.Char
type Field = ([Int],Int)
ifield :: Field
ifield = (repeat 0,0)
data Piece = I | L | O | S | T deriving (Eq,Show,Read)
type Pos = Int