Skip to content

Instantly share code, notes, and snippets.

View lotz84's full-sized avatar

Tatsuya Hirose lotz84

View GitHub Profile
@lotz84
lotz84 / mcm.hs
Created December 21, 2021 10:51
Matrix chain multiplication implementation with dependent type
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Main where
@lotz84
lotz84 / mini_interpreter.hs
Last active February 20, 2021 17:07
Haskell Type-level Mini Interpreter
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NoStarIsType #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
import Data.Type.Bool (If)
import Data.Type.Equality (type (==))
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Firebase.Auth where
import Data.Text.Lazy (Text)
import Data.Extensible
import Prelude hiding (null)
import Control.Monad (guard)
import Numeric.AD
import Numeric.Interval
allsol :: (RealFloat a, Ord a)
=> (forall b. Floating b => b -> b) -- 根を求める非線形関数
-> [Interval a] -- 探索する区間
@lotz84
lotz84 / Main.hs
Last active December 26, 2019 07:35
"Fast and Accurate Least-Mean-Squares Solvers" in Haskell https://arxiv.org/abs/1906.04705
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NoStarIsType #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.Normalise #-}
@lotz84
lotz84 / Main.hs
Created September 24, 2019 17:18
Tensor implementation using Representable Functor
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE IncoherentInstances #-}
{-# LANGUAGE LiberalTypeSynonyms #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
@lotz84
lotz84 / Main.hs
Created December 19, 2018 17:24
ピタゴラス3体問題
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ViewPatterns #-}
module Main where
import Data.Maybe
import Graphics.Gloss
import Numeric.Hamilton
import Numeric.LinearAlgebra.Static hiding ((<>))
import qualified Data.Vector.Sized as V
@lotz84
lotz84 / Main.hs
Created December 16, 2018 15:44
アルゴリズムこうしん
{-# LANGUAGE RecursiveDo #-}
module Main where
import Control.Monad.Cont
import Control.Monad.State
import Data.IORef
import Data.List
data Action = Empty
@lotz84
lotz84 / Main.hs
Created November 9, 2018 15:17
カオスゲーム
module Main where
import Graphics.Gloss.Interface.IO.Game
import System.Random.MWC
vertexes :: [Point]
vertexes = [(0, 120), (-160, -120), (160, -120)]
type Model = [Point]
@lotz84
lotz84 / Main.hs
Last active November 4, 2018 12:14
ライフゲームのシミュレーション
module Main where
import Graphics.Gloss
class Functor w => Comonad w where
extract :: w a -> a
extend :: (w b -> a) -> w b -> w a
duplicate :: w a -> w (w a)
duplicate = extend id