This file contains hidden or 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
-- Inspired by the level-monad package by Sebastian Fischer | |
module Lib | |
( search | |
) where | |
import Data.Foldable (fold) | |
import Data.Monoid (First(..)) | |
newtype Levels m = Levels { levels :: [m] } |
This file contains hidden or 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 BlockArguments #-} | |
{-# LANGUAGE GADTs #-} | |
{-# LANGUAGE LinearTypes #-} | |
{-# LANGUAGE QualifiedDo #-} | |
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE TypeOperators #-} | |
module Parallel where | |
import Control.Concurrent (forkIO) |
This file contains hidden or 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 TypeOperators #-} | |
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE DataKinds #-} | |
{-# LANGUAGE PolyKinds #-} | |
{-# LANGUAGE GADTs #-} | |
module IndexedOptic where | |
import Data.Kind (Type) | |
type f ~> g = forall i. f i -> g i |
This file contains hidden or 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 #-} | |
{-# LANGUAGE PolyKinds #-} | |
{-# LANGUAGE GADTs #-} | |
{-# LANGUAGE DeriveFunctor #-} | |
{-# LANGUAGE StandaloneDeriving #-} | |
{-# LANGUAGE MultiParamTypeClasses #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
module Cofreer where | |
import Data.Kind (Type) |
This file contains hidden or 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://www.youtube.com/watch?v=YpklMn5yNA0 | |
{-# LANGUAGE RankNTypes, QuantifiedConstraints #-} | |
{-# LANGUAGE UndecidableInstances #-} | |
{-# LANGUAGE GADTs #-} | |
import Prelude (id, (.), ($), Functor(..), (<$>), fst) | |
import Data.Functor.Identity (Identity(..)) | |
import Data.Void | |
import Data.Bifunctor (second) | |
class Feedback m where |
This file contains hidden or 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/paf31/status/1362207106703630338 | |
{-# LANGUAGE BlockArguments #-} | |
{-# LANGUAGE DefaultSignatures #-} | |
{-# LANGUAGE DeriveFunctor #-} | |
{-# LANGUAGE LinearTypes #-} | |
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE TypeFamilies #-} | |
{-# LANGUAGE TypeOperators #-} | |
{-# LANGUAGE FlexibleContexts #-} | |
{-# LANGUAGE LambdaCase #-} |
This file contains hidden or 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://github.com/viercc/functor-monad/tree/main/day-comonoid | |
{-# LANGUAGE GHC2021 #-} | |
import Data.Functor.Day | |
import Control.Comonad | |
data Multi f a where | |
MZ :: a -> Multi f a | |
MS :: Multi f (b -> a) -> f b -> Multi f a | |
fromMulti :: Applicative f => Multi f a -> f a |
This file contains hidden or 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 PolyKinds #-} | |
{-# LANGUAGE TypeFamilies #-} | |
{-# LANGUAGE TypeOperators #-} | |
{-# LANGUAGE FlexibleContexts #-} | |
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
{-# LANGUAGE StandaloneKindSignatures #-} | |
{-# LANGUAGE GADTs #-} | |
{-# LANGUAGE UndecidableInstances #-} | |
{-# LANGUAGE TypeApplications #-} |
This file contains hidden or 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 PolyKinds #-} | |
{-# LANGUAGE TypeFamilies #-} | |
{-# LANGUAGE TypeOperators #-} | |
{-# LANGUAGE FlexibleContexts #-} | |
{-# LANGUAGE MultiParamTypeClasses #-} | |
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
{-# LANGUAGE StandaloneKindSignatures #-} | |
{-# LANGUAGE GADTs #-} | |
{-# LANGUAGE UndecidableInstances #-} |
This file contains hidden or 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 #-} | |
import Prelude hiding (id, (.)) | |
import Control.Category | |
import Data.Functor.Coyoneda | |
import Data.Bifunctor (first) | |
newtype Object f g = Object { runObject :: forall a. f a -> g (Object f g, a) } | |
newtype Obj f g = Obj { runObj :: forall a. f a -> Coyoneda g (Obj f g, a) } | |
to :: Object f g -> Obj f g |
NewerOlder