Skip to content

Instantly share code, notes, and snippets.

-- RHS size: {terms: 109, types: 51, coercions: 0, joins: 3/6}
$wvarianceNoInline :: forall {v :: * -> *}. (v Double -> Int) -> (v Double -> Int# -> Box Double) -> v Double -> Double#
$wvarianceNoInline
= \ (@(v_ :: * -> *))
(basicLen :: v_ Double -> Int)
(basicIndex :: v_ Double -> Int# -> Box Double)
(xs_s2g2 :: v_ Double) ->
case xs_s2g2 of vec { __DEFAULT ->
case basicLen vec of { I# len_i ->
let {

Making lens from Traversable

Usually explanation of val Laarhoven lens is started from lens. But for me such construction feels completely artificial. Nothing motivates writing function with such weird type. Why would anyone wants to write functions with weird type signature? How could anyone come up with such idea? Traversable is much better starting point. It's part of base and it's likely that reader is familiar with this type class and appreciates its usefulness.

Traversals

{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
@Shimuuar
Shimuuar / console.txt
Created January 11, 2020 17:20
IEEE754 WAT
$ ghc -fforce-recomp -O2 wat.hs && ./wat
[1 of 1] Compiling Main ( wat.hs, wat.o )
Linking wat ...
NaN
-Infinity
Infinity
-0.0
NaN
-Infinity
Infinity
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
@Shimuuar
Shimuuar / overload.hs
Created August 13, 2019 16:58
Override data types in instance
-- This is an approach to refine ability to selectively override
-- instances when deriving using deriving via method. Idea was first
-- presented here:
--
-- http://caryrobbins.com/dev/overriding-type-class-instances/
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
module TySet where
type InsertRes x set = If (Member x set) set (x ': set)
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Sum where
import Data.Vector.Fixed (S,Z,Fun(..))
import Data.Vector.Fixed.Cont (Fn,Arity(..))
-- Trick for expressing contexts like (∀ a. Binary a => Binary (f a))
--
-- This type class says that if we have dictionary for data type `a' we can
-- construct dictionary for `f a' or equivalently that if `a' is instance of
-- Binary `f a' is instance too.
class Binary2 f where
binaryDict :: BinaryDict a -> BinaryDict (f a)
data BinaryDict a where
BinaryDict :: Binary a => BinaryDict a