openpgp4fpr:B2E1DC9AF16599BD2D873A227BABC58075EC4EE6
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- Generate (somewhat hard) test cases for ABC070 D | |
-- https://atcoder.jp/contests/abc070/tasks/abc070_d | |
module Main (main) where | |
type Input = (Int, [(Int, Int, Int)], Int, [(Int, Int)]) | |
main :: IO () | |
main = do | |
writeInputTo "abc070-d-10k-path.txt" (largePathGraph 10000) | |
writeInputTo "abc070-d-20k-path.txt" (largePathGraph 20000) |
type A :: Type
type X :: Type
type F :: Type -> Type
instance Functor F
p :: forall x. (F x, x -> A) -> X
newtype H a = H { runH :: (a -> A) -> X }
https://twitter.com/lotz84_/status/1787796266484908211
lotz @lotz84_
これを書いていて Vector n a 同士の sequenceA が distribute のように振る舞うのが気になった👀 一般に Traversable の distribute が Distributive の sequenceA に一致することが則を使って言えないだろうか?🤔 QuickCheck で少し探してみたけど反例はなさそう
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- Overkilling a cute li'l exercise | |
-- https://www.reddit.com/r/haskell/comments/v0mfkl/cute_lil_exercise/ | |
{-# LANGUAGE UnicodeSyntax, TypeOperators, ScopedTypeVariables, RankNTypes #-} | |
{-# LANGUAGE TypeApplications #-} | |
-- (this time without ImpredicativeTypes, but I'm not sure it's better or not) | |
module Isomorphisms2(goal, to, from) where | |
import Prelude hiding (id, (.)) | |
import Control.Category |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- https://twitter.com/mi12cp/status/1753203763211571656 | |
-- https://twitter.com/rsk0315_h4x/status/1753233137629646938 | |
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE ExistentialQuantification #-} | |
module Main where | |
import Data.IORef | |
-- trait Fn() |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE RankNTypes #-} | |
module PolymorphicState where | |
{- | |
-- https://twitter.com/Kory__3/status/1737757423673413635 | |
> forall s, a. Monad (a =>> s -> (s, a)) の値って一意なのでしょうか | |
-} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE GHC2021 #-} | |
{-# LANGUAGE TypeOperators #-} | |
{-# LANGUAGE PolyKinds, DataKinds #-} | |
{-# LANGUAGE TypeFamilies #-} | |
{-# LANGUAGE DerivingVia #-} | |
{-# LANGUAGE UndecidableInstances #-} | |
module InfiniteHigherOrderEffect where | |
import Data.Kind (Type) | |
import Data.Functor.Contravariant (Contravariant) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE ExplicitForAll #-} | |
-- With MonomorphismRestriction (which is ON by default,) | |
-- any constrained type variable (e.g. `m` in `Monad m`) | |
-- are not generalized | |
{-# LANGUAGE NoMonomorphismRestriction #-} | |
-- MonoLocalBinds prevents generalization of non-top-level binding | |
{-# LANGUAGE MonoLocalBinds #-} | |
-- Compare for |
NewerOlder