[Haskell-cafe] ANN: data-fin

2013-07-20 Thread wren ng thornton

-- data-fin 0.1.0


The data-fin package offers the family of totally ordered finite sets,
implemented as newtypes of Integer, etc. Thus, you get all the joys of:

data Nat = Zero | Succ !Nat

data Fin :: Nat - * where
FZero :: (n::Nat) - Fin (Succ n)
FSucc :: (n::Nat) - Fin n - Fun (Succ n)

But with the efficiency of native types instead of unary encodings.



-- Notes


I wrote this package for a linear algebra system I've been working on, but
it should also be useful for folks working on Agda, Idris, etc, who want
something more efficient to compile down to in Haskell. The package is
still highly experimental, and I welcome any and all feedback.

Note that we implement type-level numbers using [1] and [2], which works
fairly well, but not as nicely as true dependent types since we can't
express certain typeclass entailments. Once the constraint solver for
type-level natural numbers becomes available, we'll switch over to using
that.

[1] Oleg Kiselyov and Chung-chieh Shan. (2007) Lightweight static
resources: Sexy types for embedded and systems programming. Proc. Trends
in Functional Programming. New York, 2--4 April 2007.
http://okmij.org/ftp/Haskell/types.html#binary-arithm

[2] Oleg Kiselyov and Chung-chieh Shan. (2004) Implicit configurations:
or, type classes reflect the values of types. Proc. ACM SIGPLAN 2004
workshop on Haskell. Snowbird, Utah, USA, 22 September 2004. pp.33--44.
http://okmij.org/ftp/Haskell/types.html#Prepose



-- Links


Homepage:
http://code.haskell.org/~wren/

Hackage:
http://hackage.haskell.org/package/data-fin

Darcs:
http://community.haskell.org/~wren/data-fin

Haddock (Darcs version):
http://community.haskell.org/~wren/data-fin/dist/doc/html/data-fin

-- 
Live well,
~wren


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: data-textual: Human-friendly textual representations

2013-04-24 Thread Mikhail Vorozhtsov

Hello lists,

I'm pleased to announce the first release of data-textual[1], a library 
that provides human-friendly counterparts (called Printable/Textual) of 
the compiler-friendly Show/Read type classes. The library is intended to 
be used for printing and parsing of non-compound and non-polymorphic 
compound data (e.g. numbers, network and hardware addresses, date/time, 
etc).


A quick example (vs network-ip[2] library):

λ import Data.Maybe (fromJust)
λ import Data.Textual
λ import Network.IP.Addr

λ let x = fromString [dead::b:e:e:f]:123 :: Maybe Inet6Addr
λ x
Just (InetAddr {inetHost = ip6FromWords 0xdead 0x0 0x0 0x0 0xb 0xe 0xe 
0xf, inetPort = 123})

λ toString (fromJust x)
[dead::b:e:e:f]:123

λ let y = fromStringAs aNet4Addr 192.168.100.1/24
λ y
Just (netAddr (ip4FromOctets 192 168 100 1) 24)
λ toText (netPrefix $ fromJust y)
192.168.100.0

[1] http://hackage.haskell.org/package/data-textual
[2] http://hackage.haskell.org/package/network-ip

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-23 Thread Anton Kholomiov
I don't know how to express it. You need to have some dynamic
representation since
dag is a container of `(Int, f Int)`. I've tried to go along this road

type Exp a = Fix (E a)

data E c :: * - * where
  Lit :: Show a = a - E a c
  Op  :: Op a - E a c
  App :: Phantom (a - b) c - Phantom a c - E b c

data Op :: * - * where
  Add :: Num a = Op (a - a - a)
  Mul :: Num a = Op (a - a - a)
  Neg :: Num a = Op (a - a)

newtype Phantom a b = Phantom { unPhantom :: b }

But got stuck with the definition of

app :: Exp (a - b) - Exp a - Exp b
app f a = Fix $ App (Phantom f) (Phantom a)

App requires the arguments to be of the same type (in the second type
argument `c`).

2013/2/23 Conal Elliott co...@conal.net


 On Tue, Feb 19, 2013 at 9:28 PM, Anton Kholomiov 
 anton.kholom...@gmail.com wrote:


 Do you think the approach can be extended for non-regular (nested)
 algebraic types (where the recursive data type is sometimes at a different
 type instance)? For instance, it's very handy to use GADTs to capture
 embedded language types in host language (Haskell) types, which leads to
 non-regularity.


 I'm not sure I understand the case you are talking about. Can you write a
 simple example
 of the types like this?


 Here's an example of a type-embedded DSEL, represented as a GADT:

  data E :: * - * where
Lit :: Show a = a - E a
Op  :: Op a - E a
App :: E (a - b) - E a - E b
...
 
  data Op :: * - * where
Add :: Num a = E (a - a - a)
Mul :: Num a = E (a - a - a)
Neg :: Num a = E (a - a)
...

 -- Conal

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-22 Thread Conal Elliott
On Tue, Feb 19, 2013 at 9:28 PM, Anton Kholomiov
anton.kholom...@gmail.comwrote:


 Do you think the approach can be extended for non-regular (nested)
 algebraic types (where the recursive data type is sometimes at a different
 type instance)? For instance, it's very handy to use GADTs to capture
 embedded language types in host language (Haskell) types, which leads to
 non-regularity.


 I'm not sure I understand the case you are talking about. Can you write a
 simple example
 of the types like this?


Here's an example of a type-embedded DSEL, represented as a GADT:

 data E :: * - * where
   Lit :: Show a = a - E a
   Op  :: Op a - E a
   App :: E (a - b) - E a - E b
   ...

 data Op :: * - * where
   Add :: Num a = E (a - a - a)
   Mul :: Num a = E (a - a - a)
   Neg :: Num a = E (a - a)
   ...

-- Conal
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-21 Thread Emil Axelsson

This should be possible using higher-order terms, as in

http://hackage.haskell.org/packages/archive/compdata/latest/doc/html/Data-Comp-Multi-Term.html

The only complication I see is that the Dag nodes would get 
heterogeneous types requiring existential quantification with a 
`Typeable` constraint. A better representation might be typed ASGs [1]


Syntactic has typed ASTs and it has a module that does something similar 
to data-fix-cse (uses a combination of stable names and hashing), but it 
needs some fixing up.


/ Emil

[1]: http://dl.acm.org/citation.cfm?id=2426909


2013-02-20 01:58, Conal Elliott skrev:

Do you think the approach can be extended for non-regular (nested)
algebraic types (where the recursive data type is sometimes at a
different type instance)? For instance, it's very handy to use GADTs to
capture embedded language types in host language (Haskell) types, which
leads to non-regularity.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Anton Kholomiov
I'm glad to announce the package for Common subexpression elimination [1].
It's an implementation of the hashconsig algorithm as described in the
paper
'Implementing Explicit and Finding Implicit Sharing in EDSLs' by Oleg
Kiselyov.

Main point of the library is to define this algorithm in the most generic
way.
You can define the AST for your DSL as fixpoint type[2]. And then all you
need
to use the library is to define the instance for type class `Traversable`.
This idea is inspired by `data-reify` [3] package which you can use to
transform
your ASTs to DAGs too. But it relies on inspection of the references for
values
when `data-fix-cse` doesn't sacrifices the purity.

A short example:

Let's define a tiny DSL for signals

import Data.Fix

type Name = String

type E = Fix Exp

data Exp a = Const Double | ReadPort Name | Tfm Name [a] | Mix a a
  deriving (Show, Eq, Ord)

We can make constant signals, read them from some ports and transform them
(apply some named function to the list of signals) and mix two signals.

Let's define an instance of the Traversable (hence for the Functor and
Foldable)

import Control.Applicative

import Data.Monoid
import Data.Traversable
import Data.Foldable

instance Functor Exp where
  fmap f x = case x of
 Const d - Const d
 ReadPort n - ReadPort n
 Mix a b - Mix (f a) (f b)
 Tfm n as - Tfm n $ fmap f as

instance Foldable Exp where
  foldMap f x = case x of
 Mix a b - f a  f b
 Tfm n as - mconcat $ fmap f as
 _ - mempty

instance Traversable Exp where
   traverse f x = case x of
  Mix a b - Mix $ f a * f b
  Tfm n as - Tfm n $ traverse f as
  a - pure a

Now we can use the functio `cse`

cse :: 
(Eqhttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Eq.html#t:Eq(f
Inthttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Int.html#t:Int),
Ordhttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Ord.html#t:Ord(f
Inthttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Int.html#t:Int),
Traversablehttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Traversable.html#t:Traversablef)
=
Fixhttp://hackage.haskell.org/packages/archive/data-fix/0.0.1/doc/html/Data-Fix.html#t:Fixf
-
Daghttp://hackage.haskell.org/packages/archive/data-fix-cse/0.0.1/doc/html/Data-Fix-Cse.html#t:Dagf

to transform our AST to DAG. DAG is already sorted.

Later we can define a handy wrapper to hide the details from the client

newtype Sig = Sig { unSig :: E }

You can find examples in the package archive

Extra-Source-Files:
test/Exp.hs
test/Impl.hs
test/Expl.hs

If you want to see a real world example of usage you can find it
in the csound-expression[4]. An edsl for the Csound language.

One side-note form my experience: Fixpoint types can be very flexible.
It's easy to compose them. If suddenly we need to add some extra data
to all cases from the example above we can easily do it with just another
Functor:

Imagine that we want to use a SampleRate value with all signals.
Then we can do it like this:

type E = Fix SampledExp

data SampledExp a = SampledExp SampleRate (Exp a)

then we should define an instance of the type class Traversable
for our new type SampleRate. The Exp doesn't change.

[1] http://hackage.haskell.org/package/data-fix-cse-0.0.1
[2] http://hackage.haskell.org/package/data-fix-0.0.1
[3] http://hackage.haskell.org/package/data-reify
[4] http://hackage.haskell.org/package/csound-expression


Anton
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Emil Axelsson

2013-02-19 12:10, Anton Kholomiov skrev:

I'm glad to announce the package for Commonsubexpression elimination [1].
It's an implementation of the hashconsig algorithm as described in the
paper
'Implementing Explicit and Finding Implicit Sharing in EDSLs' by Oleg
Kiselyov.

Main point of the library is to define this algorithm in the most
generic way.
You can define the AST for your DSL as fixpoint type[2]. And then all
you need
to use the library is to define the instance for type class `Traversable`.


One way to make the library even more useful would have been to base it 
on compdata instead of data-fix. Compdata has support for composable 
types and lots of extra functionality. On the other hand, it's easy 
enough to translate from compdata terms to your `Fix`...





One side-note form my experience: Fixpoint types can be very flexible.
It's easy to compose them. If suddenly we need to add some extra data
to all cases from the example above we can easily do it with just another
Functor:

Imagine that we want to use a SampleRate value with all signals.
Then we can do it like this:

type E = Fix SampledExp

data SampledExp a = SampledExp SampleRate (Exp a)

then we should define an instance of the type class Traversable
for our new type SampleRate. The Exp doesn't change.


Very useful indeed! A more principled way to extend data types in this 
way is Data Types à la Carte:


  http://dx.doi.org/10.1017/S0956796808006758

(Implemented in compdata.)

/ Emil


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Anton Kholomiov
There are several packages that already define fixpoints (another one is
about unification), but all packages that I'm aware of define a lot of
functionality
that I don't need (and actually don't understand, packages with fixpoint
types
tend to be rather dense with math). I'd like it to be simple and
lightweight.
Just fixpoints, just folds and unfolds.


2013/2/19 Emil Axelsson e...@chalmers.se

 2013-02-19 12:10, Anton Kholomiov skrev:

 I'm glad to announce the package for Commonsubexpression elimination [1].

 It's an implementation of the hashconsig algorithm as described in the
 paper
 'Implementing Explicit and Finding Implicit Sharing in EDSLs' by Oleg
 Kiselyov.

 Main point of the library is to define this algorithm in the most
 generic way.
 You can define the AST for your DSL as fixpoint type[2]. And then all
 you need
 to use the library is to define the instance for type class `Traversable`.


 One way to make the library even more useful would have been to base it on
 compdata instead of data-fix. Compdata has support for composable types and
 lots of extra functionality. On the other hand, it's easy enough to
 translate from compdata terms to your `Fix`...




  One side-note form my experience: Fixpoint types can be very flexible.
 It's easy to compose them. If suddenly we need to add some extra data
 to all cases from the example above we can easily do it with just another
 Functor:

 Imagine that we want to use a SampleRate value with all signals.
 Then we can do it like this:

 type E = Fix SampledExp

 data SampledExp a = SampledExp SampleRate (Exp a)

 then we should define an instance of the type class Traversable
 for our new type SampleRate. The Exp doesn't change.


 Very useful indeed! A more principled way to extend data types in this way
 is Data Types à la Carte:

   
 http://dx.doi.org/10.1017/**S0956796808006758http://dx.doi.org/10.1017/S0956796808006758

 (Implemented in compdata.)

 / Emil


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Emil Axelsson
Fully understandable! Compdata would be quite a heavy dependency for 
your library.


I'm just generally fond of the idea of collecting all DSL implementation 
tricks under one umbrella. That requires using the same term representation.


/ Emil

2013-02-19 14:12, Anton Kholomiov skrev:

There are several packages that already define fixpoints (another one is
about unification), but all packages that I'm aware of define a lot of
functionality
that I don't need (and actually don't understand, packages with fixpoint
types
tend to be rather dense with math). I'd like it to be simple and
lightweight.
Just fixpoints, just folds and unfolds.


2013/2/19 Emil Axelsson e...@chalmers.se mailto:e...@chalmers.se

2013-02-19 12:10, Anton Kholomiov skrev:

I'm glad to announce the package for Commonsubexpression
elimination [1].

It's an implementation of the hashconsig algorithm as described
in the
paper
'Implementing Explicit and Finding Implicit Sharing in EDSLs' by
Oleg
Kiselyov.

Main point of the library is to define this algorithm in the most
generic way.
You can define the AST for your DSL as fixpoint type[2]. And
then all
you need
to use the library is to define the instance for type class
`Traversable`.


One way to make the library even more useful would have been to base
it on compdata instead of data-fix. Compdata has support for
composable types and lots of extra functionality. On the other hand,
it's easy enough to translate from compdata terms to your `Fix`...




One side-note form my experience: Fixpoint types can be very
flexible.
It's easy to compose them. If suddenly we need to add some extra
data
to all cases from the example above we can easily do it with
just another
Functor:

Imagine that we want to use a SampleRate value with all signals.
Then we can do it like this:

type E = Fix SampledExp

data SampledExp a = SampledExp SampleRate (Exp a)

then we should define an instance of the type class Traversable
for our new type SampleRate. The Exp doesn't change.


Very useful indeed! A more principled way to extend data types in
this way is Data Types à la Carte:

http://dx.doi.org/10.1017/__S0956796808006758
http://dx.doi.org/10.1017/S0956796808006758

(Implemented in compdata.)

/ Emil




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Conal Elliott
What a delightfully elegant approach to CSE! I've been thinking about CSE
for DSELs and about functor fixpoints, but it never occurred to me to put
the two together.

Do you think the approach can be extended for non-regular (nested)
algebraic types (where the recursive data type is sometimes at a different
type instance)? For instance, it's very handy to use GADTs to capture
embedded language types in host language (Haskell) types, which leads to
non-regularity.

- Conal


On Tue, Feb 19, 2013 at 3:10 AM, Anton Kholomiov
anton.kholom...@gmail.comwrote:

 I'm glad to announce the package for Common subexpression elimination [1].

 It's an implementation of the hashconsig algorithm as described in the
 paper
 'Implementing Explicit and Finding Implicit Sharing in EDSLs' by Oleg
 Kiselyov.

 Main point of the library is to define this algorithm in the most generic
 way.
 You can define the AST for your DSL as fixpoint type[2]. And then all you
 need
 to use the library is to define the instance for type class `Traversable`.
 This idea is inspired by `data-reify` [3] package which you can use to
 transform
 your ASTs to DAGs too. But it relies on inspection of the references for
 values
 when `data-fix-cse` doesn't sacrifices the purity.

 A short example:

 Let's define a tiny DSL for signals

 import Data.Fix

 type Name = String

 type E = Fix Exp

 data Exp a = Const Double | ReadPort Name | Tfm Name [a] | Mix a a
   deriving (Show, Eq, Ord)

 We can make constant signals, read them from some ports and transform them
 (apply some named function to the list of signals) and mix two signals.

 Let's define an instance of the Traversable (hence for the Functor and
 Foldable)

 import Control.Applicative

 import Data.Monoid
 import Data.Traversable
 import Data.Foldable

 instance Functor Exp where
   fmap f x = case x of
  Const d - Const d
  ReadPort n - ReadPort n
  Mix a b - Mix (f a) (f b)
  Tfm n as - Tfm n $ fmap f as

 instance Foldable Exp where
   foldMap f x = case x of
  Mix a b - f a  f b
  Tfm n as - mconcat $ fmap f as
  _ - mempty

 instance Traversable Exp where
traverse f x = case x of
   Mix a b - Mix $ f a * f b
   Tfm n as - Tfm n $ traverse f as
   a - pure a

 Now we can use the functio `cse`

 cse :: 
 (Eqhttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Eq.html#t:Eq(f
 Inthttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Int.html#t:Int),
 Ordhttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Ord.html#t:Ord(f
 Inthttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Int.html#t:Int),
 Traversablehttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Traversable.html#t:Traversablef)
  =
 Fixhttp://hackage.haskell.org/packages/archive/data-fix/0.0.1/doc/html/Data-Fix.html#t:Fixf
  -
 Daghttp://hackage.haskell.org/packages/archive/data-fix-cse/0.0.1/doc/html/Data-Fix-Cse.html#t:Dagf

 to transform our AST to DAG. DAG is already sorted.

 Later we can define a handy wrapper to hide the details from the client

 newtype Sig = Sig { unSig :: E }

 You can find examples in the package archive


 Extra-Source-Files:
 test/Exp.hs
 test/Impl.hs
 test/Expl.hs

 If you want to see a real world example of usage you can find it
 in the csound-expression[4]. An edsl for the Csound language.

 One side-note form my experience: Fixpoint types can be very flexible.
 It's easy to compose them. If suddenly we need to add some extra data
 to all cases from the example above we can easily do it with just another
 Functor:

 Imagine that we want to use a SampleRate value with all signals.
 Then we can do it like this:

 type E = Fix SampledExp

 data SampledExp a = SampledExp SampleRate (Exp a)

 then we should define an instance of the type class Traversable
 for our new type SampleRate. The Exp doesn't change.

 [1] http://hackage.haskell.org/package/data-fix-cse-0.0.1
 [2] http://hackage.haskell.org/package/data-fix-0.0.1
 [3] http://hackage.haskell.org/package/data-reify
 [4] http://hackage.haskell.org/package/csound-expression


 Anton

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Anton Kholomiov
 Do you think the approach can be extended for non-regular (nested)
 algebraic types (where the recursive data type is sometimes at a different
 type instance)? For instance, it's very handy to use GADTs to capture
 embedded language types in host language (Haskell) types, which leads to
 non-regularity.


I'm not sure I understand the case you are talking about. Can you write a
simple example
of the types like this?

Cheers,
Anton
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: data-dword: Long binary words from short ones

2012-10-11 Thread Mikhail Vorozhtsov

Hi.

I'm pleased to announce my new little library, data-dword[1]. It 
provides Template Haskell utilities for defining binary word data types 
from low and high halves, e.g.


data Word96 = Word96 Word32 Word64 -- strictness is configurable
data Int96 = Int96 Int32 Word64

-- All instances are fully implemented (including `quotRem`, etc)
instance Bounded, Enum, Eq, Integral, Num, Ord, Read,
 Real, Show, Ix, Bits, Hashable

-- Extra bit-manipulating functions, unwrapped addition and
-- multiplication, etc.
instance BinaryWord, DoubleWord

-- Rewrite rules for converting to/from the standard integral types
{-# RULES fromIntegral/... ... #-}

The library comes with a pretty thorough test suite (that ATM has some 
failures on x86-32 due to bug #7233[2] in the base library).


[1] http://hackage.haskell.org/package/data-dword
[2] http://hackage.haskell.org/trac/ghc/ticket/7233

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-dword: Long binary words from short ones

2012-10-11 Thread Henning Thielemann


On Thu, 11 Oct 2012, Mikhail Vorozhtsov wrote:

I'm pleased to announce my new little library, data-dword[1]. It provides 
Template Haskell utilities for defining binary word data types from low and 
high halves, e.g.


data Word96 = Word96 Word32 Word64 -- strictness is configurable
data Int96 = Int96 Int32 Word64


What is the advantage over 'largeword' which does the same with plain 
Haskell 98?


http://hackage.haskell.org/package/largeword

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-dword: Long binary words from short ones

2012-10-11 Thread Mikhail Vorozhtsov

On 10/11/2012 06:09 PM, Henning Thielemann wrote:


On Thu, 11 Oct 2012, Mikhail Vorozhtsov wrote:


I'm pleased to announce my new little library, data-dword[1]. It
provides Template Haskell utilities for defining binary word data
types from low and high halves, e.g.

data Word96 = Word96 Word32 Word64 -- strictness is configurable
data Int96 = Int96 Int32 Word64


What is the advantage over 'largeword' which does the same with plain
Haskell 98?

http://hackage.haskell.org/package/largeword

1) Control over strictness of the halves
2) Signed types
3) Extra instances/operations
4) Probably faster, due to specialization/inlining/rewrite rules.
5) Test suite


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: data-or

2012-01-28 Thread wren ng thornton


-- data-or 1.0.0


The data-or package offers a data type for non-exclusive disjunction. 
This is helpful for things like a generic merge function on sets/maps 
which could be union, mutual difference, etc. based on which 'Or' value 
a function argument returns. Also useful for non-truncating zips (cf. 
'zipOr') and other cases where you sometimes want an 'Either' and 
sometimes want a pair.



-- Links


Homepage:
http://code.haskell.org/~wren/

Hackage:
http://hackage.haskell.org/package/data-or

Darcs:
http://community.haskell.org/~wren/data-or

Haddock (Darcs version):
http://community.haskell.org/~wren/data-or/dist/doc/html/data-or

--
Live well,
~wren

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-category, restricted categories

2010-03-30 Thread Edward Kmett
Very true. I oversimplified matters by mistake.

One question, I suppose, is does seq distinguish the arrows, or does it
distinguish the exponential objects in the category? since you are using it
as an object in order to apply seq, and does that distinction matter? I'd
hazard not, but its curious to me.

2010/3/26 David Menendez d...@zednenem.com

 On Fri, Mar 26, 2010 at 11:07 AM, Edward Kmett ekm...@gmail.com wrote:
 
  On Fri, Mar 26, 2010 at 11:04 AM, Edward Kmett ekm...@gmail.com wrote:
 
  -- as long as you're ignoring 'seq'
  terminateSeq :: a - Unit
  terminateSeq a = a `seq` unit
 
 
  Er ignore that language about seq. a `seq` unit is either another bottom
 or
  undefined, so there remains one canonical morphism even in the presence
 of
  seq (ignoring unsafePerformIO) =)

 It all depends on how you define equality for functions. If you mean
 indistinguishable in contexts which may involve seq, then there are at
 least two values of type Unit - ().

 foo :: (Unit - ()) - ()
 foo x = x `seq` ()

 foo terminate = ()
 foo undefined = undefined

 Even this uses the convention that undefined = error whatever =
 loop, which isn't technically true, since you can use exception
 handling to write code which treats them differently.

 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/ http://www.eyrie.org/%7Ezednenem/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-category, restricted categories

2010-03-26 Thread Edward Kmett
On Fri, Mar 26, 2010 at 11:04 AM, Edward Kmett ekm...@gmail.com wrote:


 -- as long as you're ignoring 'seq'
 terminateSeq :: a - Unit
 terminateSeq a = a `seq` unit


Er ignore that language about seq. a `seq` unit is either another bottom or
undefined, so there remains one canonical morphism even in the presence of
seq (ignoring unsafePerformIO) =)


 -- discounting the extraneous
 terminateUnitSeq a = a `seq` undefined



-- and here I should have said.
terminateUnitSeq a = a `seq` ()

-Edward Kmett
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-category, restricted categories

2010-03-26 Thread David Menendez
On Fri, Mar 26, 2010 at 11:07 AM, Edward Kmett ekm...@gmail.com wrote:

 On Fri, Mar 26, 2010 at 11:04 AM, Edward Kmett ekm...@gmail.com wrote:

 -- as long as you're ignoring 'seq'
 terminateSeq :: a - Unit
 terminateSeq a = a `seq` unit


 Er ignore that language about seq. a `seq` unit is either another bottom or
 undefined, so there remains one canonical morphism even in the presence of
 seq (ignoring unsafePerformIO) =)

It all depends on how you define equality for functions. If you mean
indistinguishable in contexts which may involve seq, then there are at
least two values of type Unit - ().

foo :: (Unit - ()) - ()
foo x = x `seq` ()

foo terminate = ()
foo undefined = undefined

Even this uses the convention that undefined = error whatever =
loop, which isn't technically true, since you can use exception
handling to write code which treats them differently.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: data-category, restricted categories

2010-03-22 Thread Sjoerd Visscher
Hi everybody,

At ZuriHac I released data-category. It is an implementation of several 
category-theoretical constructions.

I started this library to learn about both category theory and type level 
programming, so I wanted to implement the CT concepts as directly as possible. 
This in contrast to the excellent category-extras library, which (I think) also 
tries to be as useful as possible.

CT is about studying categories, so for data-category I wanted to implement all 
kinds of categories. The Control.Category module unfortunately requires you to 
implement id :: cat a a (for all a), which means it only supports categories 
that have exactly the same objects as Hask. So Data.Category contains an 
implementation of restricted categories, using inspiration from Oleg's 
restricted monads.

It is well known that the Functor class also is a bit limited, as it only 
supports endofunctors in Hask. But there's another problem, if you want to 
define the identity functor, or the composition of 2 functors, then you have to 
use newtype wrappers, which can get in the way. Data.Category has an 
implementation of functors which solves this by using type families. Functors 
are represented by labels, and the type family F turns the label into the 
actual functor. F.e. type instance F List a = [a], type instance F Id a = a.

The current version contains:
- categories
  - Void, Unit, Pair (discrete categories with 0, 1 and 2 objects respectively)
  - Boolean
  - Omega, the natural numbers as an ordered set (ω)
  - Monoid
  - Functor, the category of functors from one category to another
  - Hask
  - Kleisli
  - Alg, the category of F-Algebras
- functors
  - the identity functor
  - functor composition
  - the constant functor
  - the co- and contravariant Hom-functors
  - the diagonal functor
- natural transformations
- universal arrows
- limits and colimits (as universal arrows from/to the diagonal functor)
  - using Void as index category this gives initial and terminal objects
- f.e. in Alg the arrows from the initial object are catamorphisms
  - using Pair as index category this gives products and coproducts
- f.e. in Omega they are the minimum and maximum and in Boolean and and or.
- adjunctions

Of course the are still a lot of things missing, especially in the details. And 
I'm a category theory beginner, so there will probably be some mistakes in 
there as well. F.e. Edward Kmett doesn't like () being the terminal object in 
Hask, which I thought I understood, but after thinking about it a bit more I 
don't.

You can find data-category on hackage and on github:
http://hackage.haskell.org/package/data-category
http://github.com/sjoerdvisscher/data-category

greetings,
Sjoerd Visscher
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-ordlist-0.2

2010-02-07 Thread Ross Paterson
Why not wrap lists as Set and Bag abstract datatypes?  An added bonus
is that you could make them instances of Monoid.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-ordlist-0.2

2010-02-07 Thread Leon Smith
On Sun, Feb 7, 2010 at 6:43 AM, Ross Paterson r...@soi.city.ac.uk wrote:

 Why not wrap lists as Set and Bag abstract datatypes?  An added bonus
 is that you could make them instances of Monoid.

Well,  my current thinking is that if you really want an abstract
datatype for bags and sets,  hackage (and the standard GHC
distribution) offer a multitude of options.   Previous versions of the
code in data-ordlist dates back 9 years or more;  I extracted and
refurbished data-ordlist from a mess of miscellaneous list functions I
use.

Personally,  I've never really used this code as an abstract datatype;
 my typical use cases break the set and bag abstractions to some
extent. I use a few functions when I happen to know the lists I'm
dealing with are ordered,  and want a simple and efficient way to
manipulate them.  The functions I most often use are sortOn,  sortOn',
 nubSort,  and to a somewhat lesser extent,  the set-like operators.

I put this package on hackage as much for my own personal convenience
as for others;  but I do hope that other people will find it useful.
I realize that others might use it in rather different ways than I do,
 and am open to suggestions and proposals.

Cheers,
Leon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: data-ordlist-0.2

2010-02-06 Thread Leon Smith
I have released data-ordlist 0.2,  with a number of changes:

1.  The module name is now Data.List.Ordered,  instead of Data.OrdList

2.  Three bugfixes: (ack!)  insertSet and insertBag assumed reverse-ordered
lists,   nub failed to remove duplicates.   Thanks to Topi Karvonen for
reporting the first problem.

3.  One semantic change:  old_nubBy f == new_nubBy (not . f).   The new
version is better keeping with the spirit of the rest of the library,  and
makes the old nub bug much more obvious.  Now nubBy is the greedy algorithm
that returns a sublist such that for all binary predicates:

   isSortedBy pred (nubBy pred xs) == True

4.  Improved documentation,  I hope!   Please consider taking a look and
letting me know what you think.

http://hackage.haskell.org/package/data-ordlist

Cheers,
Leon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-spacepart - space partitioning data structure[s] (initial release)

2009-01-28 Thread Corey O'Connor
No solid plans yet. Mostly I wanted to get some kind of start on a
collection of space partitioning data structures.

Some ideas
 - haddock documentation
 - automated tests
 - bounding volume hierarchies.
 - Extend into 3D

My current use of the quadtree is for collision detection. Though also
being able to effectively satisfy other types of requests would be
great.

-Corey O'Connor



On Tue, Jan 27, 2009 at 7:52 PM, Artyom Shalkhakov
artyom.shalkha...@gmail.com wrote:
 Hello,

 2009/1/27 Corey O'Connor coreyocon...@gmail.com:
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-spacepart

 The goal of this package is to be a collection of space partitioning
 data structures. Currently, however, there is only a simple quadtree
 implementation.

 Are you going to experiment with kd-trees, octrees and other spatial
 acceleration data structures? Is it for raytracing or for collision
 detection, or
 maybe for 3d graphics on consumer hardware?

 Cheers,
 Artyom Shalkhakov.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: data-spacepart - space partitioning data structure[s] (initial release)

2009-01-27 Thread Corey O'Connor
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-spacepart

The goal of this package is to be a collection of space partitioning
data structures. Currently, however, there is only a simple quadtree
implementation.

The package neither has real documentation or tests I'd like for a
quality release. However, if you need a quadtree implementation then
hopefully this will help.

Cheers,
Corey O'Connor
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-spacepart - space partitioning data structure[s] (initial release)

2009-01-27 Thread Artyom Shalkhakov
Hello,

2009/1/27 Corey O'Connor coreyocon...@gmail.com:
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-spacepart

 The goal of this package is to be a collection of space partitioning
 data structures. Currently, however, there is only a simple quadtree
 implementation.

Are you going to experiment with kd-trees, octrees and other spatial
acceleration data structures? Is it for raytracing or for collision
detection, or
maybe for 3d graphics on consumer hardware?

Cheers,
Artyom Shalkhakov.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: data-spacepart - space partitioning data structure[s] (initial release)

2009-01-27 Thread Jeff Heard
I'll be releasing an R-Tree fairly soon...  not sure whether it'll fit
into this package or not, but we might conisder merging.

On Tue, Jan 27, 2009 at 10:52 PM, Artyom Shalkhakov
artyom.shalkha...@gmail.com wrote:
 Hello,

 2009/1/27 Corey O'Connor coreyocon...@gmail.com:
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-spacepart

 The goal of this package is to be a collection of space partitioning
 data structures. Currently, however, there is only a simple quadtree
 implementation.

 Are you going to experiment with kd-trees, octrees and other spatial
 acceleration data structures? Is it for raytracing or for collision
 detection, or
 maybe for 3d graphics on consumer hardware?

 Cheers,
 Artyom Shalkhakov.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe