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 BangPatterns #-} | |
{-# language LinearTypes #-} | |
{-# language GADTs #-} | |
{-# language StandaloneKindSignatures #-} | |
{-# language KindSignatures #-} | |
{-# language TypeApplications #-} | |
{-# language DataKinds #-} | |
{-# language ScopedTypeVariables #-} | |
-- | Pairing heap loosely based on one Donnacha Oisín Kidney wrote for |
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 EmptyCase #-} | |
{-# language FlexibleContexts #-} | |
{-# language FlexibleInstances #-} | |
{-# language InstanceSigs #-} | |
{-# language MultiParamTypeClasses #-} | |
{-# language PolyKinds #-} | |
{-# language QuantifiedConstraints #-} | |
{-# language ScopedTypeVariables #-} | |
{-# language StandaloneKindSignatures #-} | |
{-# language TypeApplications #-} |
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 GADTs, ScopedTypeVariables, DeriveTraversable #-} | |
module ChallengeTransform where | |
import Data.Typeable | |
import Data.Proxy | |
import Data.Coerce | |
data Scheme a where | |
Res :: Typeable a => !(Proxy a) -> Scheme a | |
Arg :: Typeable a => !(Proxy a) -> Scheme b -> Scheme (a -> b) |
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
-- | This module defines a function that produces a complete binary tree | |
-- from a breadth-first list of its (internal) node labels. It is an | |
-- optimized version of an implementation by Will Ness that avoids | |
-- any "impossible" cases. See | |
-- | |
-- https://stackoverflow.com/a/60561480/1477667 | |
module Bftr (Tree (..), bft, list, deftest) where | |
import Data.Function (fix) | |
import Data.Monoid (Endo (..)) |
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
zipRev :: [a] -> [b] -> [(a,b)] | |
zipRev xs ys = fr where | |
(fr, allbs) = go [] allbs xs ys | |
go acc ~(b':bs') (a:as) (b:bs) = ((a,b') : res, bss) | |
where | |
(res, bss) = go (b:acc) bs' as bs | |
go acc _ _ _ = ([], acc) |
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 TypeInType, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, | |
GADTs, UndecidableInstances, NoStarIsType, TemplateHaskell, InstanceSigs, | |
TypeSynonymInstances, FlexibleInstances, BangPatterns #-} | |
module SingMap (module SingMap, module P, module F) where | |
import GHC.TypeLits hiding (type (<=)) | |
import Data.Type.Bool | |
import Data.Type.Equality | |
import Data.Singletons | |
import Data.Traversable |
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 DataKinds, TypeFamilies, TypeOperators, GADTs, | |
ScopedTypeVariables, TypeOperators #-} | |
-- | Type-level natural numbers and singletons, with proofs of | |
-- a few basic properties. | |
module BasicNat ( | |
-- | Type-level natural numbers | |
Nat (..) | |
, type (+) |
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 GADTs #-} | |
{-# LANGUAGE TypeFamilies #-} | |
{-# LANGUAGE TypeOperators #-} | |
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE ScopedTypeVariables #-} | |
{-# LANGUAGE DataKinds #-} | |
{-# LANGUAGE InstanceSigs #-} | |
{-# OPTIONS_GHC -Wall -fwarn-incomplete-uni-patterns #-} | |
module AS2 where |
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
ix :: Applicative f => Int -> (a -> f a) -> Seq a -> f (Seq a) | |
ix i@(I# i') f (Seq xs) | |
| 0 <= i && i < size xs = Seq <$> ixTreeE (\_ (Elem a) -> Elem <$> f a) i' xs | |
| otherwise = pure (Seq xs) | |
unInt :: Int -> Int# | |
unInt (I# n) = n | |
ixTreeE :: Applicative f | |
=> (Int# -> Elem a -> f (Elem a)) -> Int# -> FingerTree (Elem a) -> f (FingerTree (Elem 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 DeriveFunctor, BangPatterns #-} | |
module Queues.LazyMonadic where | |
import Data.Word | |
import Control.Applicative | |
import Control.Monad | |
data Result e a = Result | |
{ rval :: a | |
, rlen :: Word | |
, rremains :: [e] |
NewerOlder