[Haskell-cafe] Re: Is anyone using Haddock's support for frames?

2010-05-05 Thread Tristan Allwood
+1 to keep it until equivalent functionality is made mainline

I've had tinyurl.com/haskelldoc aliased to the main frame page
(http://www.haskell.org/ghc/docs/6.12.2/html/libraries/frames.html) and
used it extensively on a daily basis for GHC libraries and GHC API
browsing.  Navigating the current non-framed, disparate, seperate
documetation feels painful and slow.  I would note though that the
frames pages arn't currently working on hackage:
e.g. 
http://hackage.haskell.org/packages/archive/text/0.7.1.0/doc/html/frames.html).

BTW, I would point out the two best documentation systems I've seen in
other languages (javadoc[1] and rubydock[2]) are frame based and (IMO)
very easy to navigate.

[1] http://java.sun.com/javase/6/docs/api/ 
[2] http://www.ruby-doc.org/core/

Cheers,

Tris


On Tue, May 04, 2010 at 08:19:45PM +0200, David Waern wrote:
 Hi
 
 Since version 2.4.0 Haddock has generated HTML output that uses frames
 (index-frames.html) in addition to the normal output. We'd like to
 deprecate this feature unless there is a significant amount of users.
 The reason is two-fold:
 
   * We probably want to replace the frames with something more modern
 (like a sidebar on the same page) in the future
 
   * We are rewriting the HTML backend and it would be nice to avoid
 unnecessary work
 
 So if you're using this feature and want to keep it, please speak up!
 
 cc:ing cvs-ghc@ in case they have any users of the frames due to the
 size of the GHC code base. (This might have been the the original
 motivation for the feature).
 
 Thanks,
 David
 
 ___
 Cvs-ghc mailing list
 cvs-...@haskell.org
 http://www.haskell.org/mailman/listinfo/cvs-ghc
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problems with Unicode Symbols as Infix Function Names in Propositional Calculus Haskell DSL

2008-01-09 Thread Tristan Allwood
Hi,

Attached works fine for me (ghc 6.8.2)

You'll have trouble with → though, as ghc steals that symbol for type
signature declarations.  

A ghc expert could probably shed more light;

Cheers,

Tris

GHCi also doesn't (at least for me) print symbol names correctly, but
that's a different issue.

ghci Bloop.hs 
GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( Bloop.hs, interpreted )
Ok, modules loaded: Main.
*Main :browse
(�) :: Bool - Bool
(� :: Bool - Bool - Bool
(� :: Bool - Bool - Bool
(�) :: Bool - Bool - Bool
*Main False ˅ True
True



On Wed, Jan 09, 2008 at 06:17:13PM +0100, Cetin Sert wrote:
 I want to design a DSL in Haskell for propositional calculus. But instead of 
 using natural language names for functions like or, and, implies etc. I want 
 to use Unicode symbols as infix functions ¬, ˅, ˄, →, ↔ But I keep getting 
 error messages from the GHC parser. Is there a way to make GHC parse my 
 source files correctly? If it is not possible yet, please consider this as a 
 “feature request”.
 
  
 
 Best Regards,
 
 Cetin Sert
 
 INF 521, 4-6-2
 
 69120 Heidelberg
 
 Germany
 
  
 
 http://www.corsis.de
 

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


-- 
Tristan Allwood
PhD Student
Department of Computing
Imperial College London
{-# OPTIONS_GHC -fglasgow-exts #-}

( ¬ ) :: Bool → Bool
( ¬ ) = not

(˅) :: Bool → Bool → Bool
(˅) = (||)

(˄) :: Bool → Bool → Bool
(˄) = ()

(↔) :: Bool → Bool → Bool
(↔) = (==)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type vs TypeClass duality

2007-10-24 Thread Tristan Allwood
On Wed, Oct 24, 2007 at 11:00:14AM +0800, TJ wrote:
 Tristan Allwood:
 
 Very cool. I don't understand some (a lot of) parts though:
 
  instance Show a = Reify (ShowConstraint a) where reify = ShowC
 
 ShowC has type (Show a) = ShowConstraint a, whereas reify is
 supposed to have type ShowConstraint a.
Yes.  ShowC is a constant that wraps up the knowledge of (Show a =) for
ShowConstraint.  So (in this case) 

reify :: ShowConstraint a
reify = ShowC  

(since ShowC is the only non-bottom value ShowConstraint can take)

But in order to return ShowC, we must know that a 'is in' Show, which is
why the instance declaration requires that at the point you use reify
you can demonstrate that a is in Show:

instance Show a = Reify (ShowConstraint a) where
 ^

If the Show a = bit is removed, then the type checker rightly
complains, because the ShowC doesn't have a Show a context that it
needs.

So the trick is that in the cons (#) function which uses reify, you need
to prove 'Reify (a b)', and it just so happens that by the instance
declaration above, wherever you have 'Show a' then you have 'Reify
(ShowConstraint a)' which is why testList needs nothing more than the
values to put into it like a normal list.

 
  data SingleList (a :: * - *) where Cons :: (a b) - b - SingleList
  a - SingleList a Nil :: SingleList a
 
 Cons has a type variable b in its signature, but no forall. I
 suppose it comes from the * - * in SingleList's type?
Nope.  The (a :: * - *) is a kind annotation and means that the a is a
type that is parameterised by a type (e.g. Maybe :: * - *, whereas
Maybe Int :: *), which is why you can write (a b).  I think technically
it's a redundant annotation here as it can be inferred from the (a b)
useage.

The b is 'just' a normal, exisistentially quantified variable - GADTs
don't require you to write forall in their declarations - see the very
last sentence on
http://www.haskell.org/ghc/docs/latest/html/users_guide/gadt.html
 
 
 That's all I can come up with for now. A great deal of high level
 coding flying around above my head now.
Hope that helps some, 

Regards,

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


Re: [Haskell-cafe] Type vs TypeClass duality

2007-10-23 Thread Tristan Allwood

  Why can't it automatically construct them then? Assuming we do have
  a syntax for A list of objects, each of which is of some possibly
  different type 'a', subject only to the restriction that a is a
  member of typeclass Show, as the following:
  
  ls :: [a where Show a]
  
  Then I would think that all the type checker has to do would be to
  check that, a) everything you cons onto ls is an instance of class
  Show b) where you extract items from ls, you only use them as you
  would use any instance of class Show.
Not sure if anyone has mentioned something similar, and it's not quite
what people have been suggesting - but with minimal boilerplate (that
I'm sure a TH hacker could derive for you) you can get close to
typeclass parameterised lists using GADTs ( ghc 6.8 snapshots ;)) at
the moment.

Regards,

Tris

{-# LANGUAGE EmptyDataDecls, ScopedTypeVariables, PatternSignatures, GADTs, 
RankNTypes, KindSignatures, TypeOperators #-}

{- A list where all elements are in class Show -}
testList :: SingleList ShowConstraint
testList = () # (LT,EQ,GT) # False # 'a' # (3.0 :: Double) # hello # nil

{- My user functions over that list -}
test  = map'   (\ShowC - show) testList
test2 = foldr' (\ShowC - (+) . length . show) 0 testList


{- A tiny bit of boilerplate for Show, later rinse repeat for other typeclasses 
-}
data ShowConstraint a where
  ShowC :: (Show a) = ShowConstraint a

instance Show a = Reify (ShowConstraint a) where
  reify = ShowC

{-
*Main test
[(),(LT,EQ,GT),False,'a',3.0,\hello\]
*Main test2
30
-}



{- The bit that is a library -}

{- A generic list definition,
 - (a b) is the witness of the type class for this type,
 - b is the actual value we put in the list -}
data SingleList (a :: * - *) where
  Cons :: (a b) - b - SingleList a - SingleList a
  Nil :: SingleList a

{- helper functions to avoid having to pass in the witness explicitly -}
nil :: SingleList a
nil = Nil

infixr 5 #

(#) :: (Reify (a b)) = b - SingleList a - SingleList a
val # rest = Cons reify val rest

{- A way to get the type class constraint witness automagically -}
class Reify a where
  reify :: a

{- traditional(ish) map, note the function is passed the witness so it can use 
that
 - to get the typeclass constraint back into scope by pattern matching on it -}
map' :: forall a c . ((forall b . a b - b - c) - SingleList a - [c])
map' _ Nil  = []
map' f (Cons r v rest) = f r v : map' f rest


{- and foldr -}
foldr' :: forall a c . (forall b . a b - b - c - c) - c - SingleList a - c
foldr' f d = go 
  where
go Nil = d
go (Cons r v rest) = (f r v) (go rest)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] isWHNF :: a - IO Bool ?

2007-09-27 Thread Tristan Allwood
Hi,

Does anyone know if there is a function that tells you if a haskell
value has been forced or not?

e.g. 
isWHNF :: a - IO Bool

let x = (map succ [0..]) in do
  putStrLn . show (isWHNF x)-- False
  putStrLn . show . head $ x
  putStrLn . show (isWHNF x)-- True
  putStrLn . show (isWHNF (Just undefined)) -- True


If not, would it be hard/easy/possible to implement on-top-of or using
GHC?  I'm happy (if it's possible) to have a stab at implementing it
myself, so any pointers to right directions would be helpful.

I'm thinking it could be useful to allow creation of sparse-check [1]
like libraries without needing a separate logic encoding, or things
along those lines / in that area.

Cheers,

Tris

[1] http://www-users.cs.york.ac.uk/~mfn/sparsecheck/index.html#lim

-- 
Tristan Allwood
PhD Student
Department of Computing
Imperial College London
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: isWHNF :: a - IO Bool ?

2007-09-27 Thread Tristan Allwood
On Thu, Sep 27, 2007 at 05:31:51PM +0200, apfelmus wrote:
 Tristan Allwood wrote:
 Does anyone know if there is a function that tells you if a haskell
 value has been forced or not?  e.g. isWHNF :: a - IO Bool let x =
 (map succ [0..]) in do putStrLn . show (isWHNF x)--
 False putStrLn . show . head $ x putStrLn . show (isWHNF x)
 -- True putStrLn . show (isWHNF (Just undefined)) -- True

 Note that this function is not referentially transparent since

   isWHNF 2 = True

 but

   isWHNF (1+1) = False

 although 1+1 = 2. In other words, it messes up the language semantics
 (extensional equality) which is bad.
Indeed.  Does it still mess up with the result in IO Bool (as was my
intent)? 

Ah, I do realise my example use case above needs some ='s inserting
into it which may have led to some confusion.

Tris

-- 
Tristan Allwood
PhD Student
Department of Computing
Imperial College London
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Tristan Allwood
On Tue, Sep 25, 2007 at 10:31:34AM +0100, Dougal Stanton wrote:
 On 25/09/2007, Andrew Coppin [EMAIL PROTECTED] wrote:
 In this instance I would suggest:
 
 (1) Text.Printf
 (2) Pull out some of those things into separate functions with
 where/let clauses.
 
 If it's a matrix you should probably have something like
 
  showMatrix = concatMap showRow
 
 Since you'll be applying the same procedures to each line of digits.

Just to follow those sentiments, the version I knocked out quickly
looked like:
(It's not quite the same as the original function, I think I'm lacking a
map (map (take 8)) on the first line).

showSystems :: Show a = [[a]] - String
showSystems = unlines . zipWith showSystem [1..] 
  where
showSystem n as = Eq ++ (show n) ++ :  ++ sum ++  =  ++ val
  where
sum = concat . intersperse  +  . zipWith showNum [1..] $ (init as)
val = show . last $ as
showNum n a = show a ++  x ++ show n


Pointsfree and explicit lambda notation I find can be very concise in
places, but make it quite hard to reuse or refactor code later - if you
can't read it, make a function/variable with a useful name so you can
later.

Regards,

T

-- 
Tristan Allwood
PhD Student
Department of Computing
Imperial College London
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Tristan Allwood
On Tue, Sep 25, 2007 at 10:53:55AM +0100, Andrew Coppin wrote:
 Tristan Allwood wrote:

 Just to follow those sentiments, the version I knocked out quickly
 looked like:
 (It's not quite the same as the original function, I think I'm lacking a
 map (map (take 8)) on the first line).

 showSystems :: Show a = [[a]] - String
 showSystems = unlines . zipWith showSystem [1..]   
   where
 showSystem n as = Eq ++ (show n) ++ :  ++ sum ++  =  ++ val
   where
 sum = concat . intersperse  +  . zipWith showNum [1..] $ (init 
 as)
 val = show . last $ as
 showNum n a = show a ++  x ++ show n

   

 I'm puzzled - do we have 2 seperate where clauses?

Yes there are 2 and no they arn't seperate.  The second where clause is
nested and is a set of definitioins local to showSystem, and as such can
use the bound values of n and as. (But it can also see any values
bound by showSystems and its where clause (which in this case is just
the definition of showSystem).

Clear as mud?

T
-- 
Tristan Allwood
PhD Student
Department of Computing
Imperial College London
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe